Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How can i draw elliptical figures in a circle

Status
Not open for further replies.

ssv123

Programmer
Oct 7, 2003
6
US
i am having a cirlce with an elliptical figures in side the circumference of the circle. I now want to draw these ellipticalfigures .But I am not able to draw these different shape of figures could any one help me with the code
The figure i want to draw are a rectangle with 2 semi circles attached to the ends (|__|) like this there is no gap.
I have implemented with circular figures inside the circumference like this


SUBROUTINE Hole_Profile_Calc(dtheta_hole,hole_profile,AxialHole,n_slice_net)
!
! Calculation of circular axial hole profile (effective width) via radial slices
IMPLICIT NONE

!-- Input Variables
TYPE(AxialHoleType), INTENT(IN) :: AxialHole
REAL, INTENT(IN) :: dtheta_hole ! angular increment per slice, rad
INTEGER, INTENT(IN) :: n_slice_net ! net number slices per 360deg detailing hole profile

!-- Output Variables
REAL, INTENT(OUT) :: hole_profile(maxRadialSlices) ! chord distance of radial slices through holes over 360 deg

!-- Internal Variables
REAL c ! radial (chord) length of each slice, m
REAL d ! circumferential distance from hole center to slice, m
REAL w_slice_hole ! width of each hole slice
REAL tmp ! temporary variable
REAL theta_hole_width ! one half angular width of each hole, rad
REAL theta_hole(maxAxialHoles) ! angular location of each hole center, rad

INTEGER j,jj,k
INTEGER center_index ! array index at center of hole
INTEGER CW_index,CCW_index ! array indices at position on both sides of hole center
INTEGER nn


!-----------------------------------------------------------------------
!-----------------------------------------------------------------------

!-- One half angular span of each hole ---
theta_hole_width = PI2*(0.5*AxialHole.OD)/(PI2*AxialHole.radius_to_center)

!-- Number of slices per half hole --
nn = NINT(theta_hole_width/dtheta_hole)

!-- Width of each slice --
w_slice_hole = AxialHole.OD/(2*nn)

!-- hole Locations assuming Uniform Distribution ---
DO jj = 1,AxialHole.n_holes
theta_hole(jj) = AxialHole.theta_to_center + (jj-1)*2*PI/AxialHole.n_holes
ENDDO

!-- Initialize hole_profile
hole_profile = 0.0

DO jj = 1, AxialHole.n_holes
d = 0

! index locating hole center
center_index = NINT(theta_hole(jj)/dtheta_hole)+1

DO k = 1, nn
! distance from hole center to slice, m
d = d + w_slice_hole

! radial length of slice (chord) inc. bolt, m
tmp = 0.25*AxialHole.OD**2 - d*d
IF (tmp < 0 )then
c = 0
ELSE
c = 2.0*sqrt(tmp)
ENDIF
CW_index = center_index - k + 1
CCW_index = center_index + k
IF (CW_index < 1)then
CW_index = CW_index + n_slice_net
ENDIF

! radial slice length in CCW direction from center, m
hole_profile(CCW_index) = c
! radial slice length in CW direction from center, m
hole_profile(CW_index) = c
ENDDO
ENDDO

END SUBROUTINE Hole_Profile_Calc


SUBROUTINE DISPLAY _HOLES
USE DFLIB
USE SimulationSettingsModule
USE DefineGlobalVarsModule
IMPLICIT NONE

!-------------------------------------------------------------------------------
! Local Variables
!-------------------------------------------------------------------------------
INTEGER j
INTEGER k
INTEGER(2) status
REAL theta

REAL(8) wx1,wy1
REAL(8) wx2,wy2
REAL(8) wx00,wy00
REAL(8) wx0,wy0

!-----------------------------------------------------------------------
! Set & Display Stator Axial Circular Holes and Bolts
!-----------------------------------------------------------------------
!status = SETCOLOR(4) ! Red
DO k = 1,StatorCore.n_axial_hole_sets

! Coordinates of first stator hole of type k
wx00 = StatorCore.AxialHole(k).radius_to_center
wy00 = 0.0

DO j = 1,StatorCore.AxialHole(k).n_holes
! Rotate center coordinate for each stator hole
theta = StatorCore.AxialHole(k).theta_to_center &
+ (j-1)*PI2/StatorCore.AxialHole(k).n_holes
wx0 = wx00*cos(theta) - wy00*sin(theta)
wy0 = wx00*sin(theta) + wy00*cos(theta)
! Calculate new coordinates for each stator hole
wx1 = wx0 - 0.5*StatorCore.AxialHole(k).OD
wy1 = wy0 + 0.5*StatorCore.AxialHole(k).OD
wx2 = wx0 + 0.5*StatorCore.AxialHole(k).OD
wy2 = wy0 - 0.5*StatorCore.AxialHole(k).OD

! Display each rotated hole
status = ELLIPSE_W($GBORDER, wx1,wy1,wx2,wy2)

ENDDO
ENDDO

!-----------------------------------------------------------------------
END SUBROUTINE DISPLAY_HOLES
!-----------------------------------------------------------------------
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top