|
- subroutine TD_WellReadData
-
- Use CPathGenerationVariables
- Use TD_WellGeometry
-
- implicit none
-
- Integer :: i
-
-
-
- TD_WellIntervalsCount = PathGenerationCount + 1 ! +1 is belong to ROP hole
-
- if (Allocated(TD_WellGeo)) deAllocate (TD_WellGeo)
- Allocate (TD_WellGeo(TD_WellIntervalsCount))
-
-
-
-
- !====================================================
- ! Set Well Geometry Data
- !====================================================
-
- TD_WellGeo(1)%HoleType = PathGenerations(1)%HoleType
- TD_WellGeo(1)%StartAngle = 0.d0 ![rad]
- TD_WellGeo(1)%EndAngle = PathGenerations(1)%FinalAngle*(pi/180.d0) ![rad]
- TD_WellGeo(1)%IntervalLength= PathGenerations(1)%TotalLength ![ft]
- !TD_WellGeo(1)%VerticalDepth = PathGenerations(1)%TotalVerticalDepth
- TD_WellGeo(1)%TopDepth = 0.d0
- TD_WellGeo(1)%DownDepth = PathGenerations(1)%MeasuredDepth
-
-
-
- Do i=2,TD_WellIntervalsCount-1
-
- TD_WellGeo(i)%HoleType = PathGenerations(i)%HoleType
- TD_WellGeo(i)%StartAngle = PathGenerations(i-1)%FinalAngle*(pi/180.d0)
- TD_WellGeo(i)%EndAngle = PathGenerations(i)%FinalAngle*(pi/180.d0)
- TD_WellGeo(i)%IntervalLength= PathGenerations(i)%TotalLength
- !TD_WellGeo(i)%VerticalDepth = PathGenerations(i)%TotalVerticalDepth
- TD_WellGeo(i)%TopDepth = PathGenerations(i-1)%MeasuredDepth
- TD_WellGeo(i)%DownDepth = PathGenerations(i)%MeasuredDepth
-
- !=====> Radius Of Curvature Calculation
- if (TD_WellGeo(i)%HoleType/=0) then
- TD_WellGeo(i)%RCurvature = ((TD_WellGeo(i)%IntervalLength)/abs(TD_WellGeo(i)%EndAngle-TD_WellGeo(i)%StartAngle))
- end if
-
- End Do
-
-
-
-
-
- !=====> Set ROP Hole Data
- TD_WellGeo(TD_WellIntervalsCount)%HoleType = 0 !Straight
- TD_WellGeo(TD_WellIntervalsCount)%StartAngle = TD_WellGeo(TD_WellIntervalsCount-1)%EndAngle
- TD_WellGeo(TD_WellIntervalsCount)%EndAngle = TD_WellGeo(TD_WellIntervalsCount)%StartAngle
- TD_WellGeo(TD_WellIntervalsCount)%IntervalLength= 0.d0
- !TD_WellGeo(TD_WellIntervalsCount)%VerticalDepth = TD_WellGeo(TD_WellIntervalsCount-1)%VerticalDepth
- TD_WellGeo(TD_WellIntervalsCount)%TopDepth = TD_WellGeo(TD_WellIntervalsCount-1)%DownDepth
- TD_WellGeo(TD_WellIntervalsCount)%DownDepth = TD_WellGeo(TD_WellIntervalsCount)%TopDepth+TD_WellGeo(TD_WellIntervalsCount)%IntervalLength
-
-
-
-
-
-
- !=====> Vertical Depth Calculation
- if ( TD_WellGeo(1)%HoleType==0 ) then
- TD_WellGeo(1)%VerticalDepth = TD_WellGeo(1)%IntervalLength*cos(TD_WellGeo(1)%StartAngle)
- else if ( TD_WellGeo(1)%HoleType==1 ) then
- TD_WellGeo(1)%VerticalDepth = (TD_WellGeo(1)%RCurvature*sin(abs(TD_WellGeo(1)%EndAngle)-abs(TD_WellGeo(1)%StartAngle))*cos(abs(TD_WellGeo(1)%StartAngle)))-(TD_WellGeo(1)%RCurvature*(1.-cos(abs(TD_WellGeo(1)%EndAngle)-abs(TD_WellGeo(1)%StartAngle)))*sin(abs(TD_WellGeo(1)%StartAngle)))
- else if ( TD_WellGeo(1)%HoleType==2 ) then
- TD_WellGeo(1)%VerticalDepth = (TD_WellGeo(1)%RCurvature*sin(abs(abs(TD_WellGeo(1)%EndAngle)-abs(TD_WellGeo(1)%StartAngle)))*cos(abs(TD_WellGeo(1)%StartAngle)))+(TD_WellGeo(1)%RCurvature*(1.-cos(abs(abs(TD_WellGeo(1)%EndAngle)-abs(TD_WellGeo(1)%StartAngle))))*sin(abs(TD_WellGeo(1)%StartAngle)))
- End if
- Do i= 2,TD_WellIntervalsCount
- if ( TD_WellGeo(i)%HoleType==0 ) then
- TD_WellGeo(i)%VerticalDepth = TD_WellGeo(i-1)%VerticalDepth+TD_WellGeo(i)%IntervalLength*cos(TD_WellGeo(i)%StartAngle)
- else if ( TD_WellGeo(i)%HoleType==1 ) then
- TD_WellGeo(i)%VerticalDepth = TD_WellGeo(i-1)%VerticalDepth+(TD_WellGeo(i)%RCurvature*sin(abs(TD_WellGeo(i)%EndAngle)-abs(TD_WellGeo(i)%StartAngle))*cos(abs(TD_WellGeo(i)%StartAngle)))-(TD_WellGeo(i)%RCurvature*(1.-cos(abs(TD_WellGeo(i)%EndAngle)-abs(TD_WellGeo(i)%StartAngle)))*sin(abs(TD_WellGeo(i)%StartAngle)))
- else if ( TD_WellGeo(i)%HoleType==2 ) then
- TD_WellGeo(i)%VerticalDepth = TD_WellGeo(i-1)%VerticalDepth+(TD_WellGeo(i)%RCurvature*sin(abs(abs(TD_WellGeo(i)%EndAngle)-abs(TD_WellGeo(i)%StartAngle)))*cos(abs(TD_WellGeo(i)%StartAngle)))+(TD_WellGeo(i)%RCurvature*(1.-cos(abs(abs(TD_WellGeo(i)%EndAngle)-abs(TD_WellGeo(i)%StartAngle))))*sin(abs(TD_WellGeo(i)%StartAngle)))
- End if
- End Do
- !Do i=1,TD_WellIntervalsCount
- ! print*, 'TD_WellGeo(i)%TopDepth=' , i , TD_WellGeo(i)%TopDepth
- ! print*, 'TD_WellGeo(i)%DownDepth=' , i , TD_WellGeo(i)%DownDepth
- ! print*, 'TD_WellGeo(i)%HoleType=' , i , TD_WellGeo(i)%HoleType
- ! print*, 'TD_WellGeo(i)%RCurvature=' , i , TD_WellGeo(i)%RCurvature
- ! print*, 'TD_WellGeo(i)%EndAngle=' , i , TD_WellGeo(i)%EndAngle
- ! print*, 'TD_WellGeo(i)%StartAngle=' , i , TD_WellGeo(i)%StartAngle
- ! print*, 'TD_WellGeo(i)%VerticalDepth=' , i , TD_WellGeo(i)%VerticalDepth
- !end do
-
-
-
-
-
-
-
- !=====> Well Total Length Calculation
- TD_WellTotalLength = TD_WellGeo(TD_WellIntervalsCount)%DownDepth
- TD_WellTotalVerticalLength = TD_WellGeo(TD_WellIntervalsCount)%VerticalDepth
-
-
-
-
-
-
- end subroutine
|