|
- subroutine TD_BOPDiamCalculation
-
- Use TD_DrillStemComponents
- Use TD_WellElements
- Use TD_WellGeometry
- Use TD_GeneralData
- Use TD_StringConnectionData
- Use CBopStackVariables
- Use VARIABLES
-
-
- Integer :: i , j , n , m , TD_Numbs
- Real(8) :: TD_LimitUp , TD_LimitDown , TD_OldFillingValue , TD_AnnTjDiff , TD_AnnularFilling
- Real(8) :: TD_ElToolJoints(2,2)
-
-
-
-
-
- !TD_ToolJointRange = 0.4005d0*3.28 ! [ft]
-
- !====================================================
- ! Read BOP Data
- !====================================================
-
- TD_BOPHeight(5) = AboveAnnularHeight
- TD_BOPHeight(1) = AnnularPreventerHeight
- TD_BOPHeight(2) = UpperRamHeight
- TD_BOPHeight(3) = BlindRamHeight
- TD_BOPHeight(6) = KillHeight
- TD_BOPHeight(4) = LowerRamHeight
-
-
- TD_BOPRamDiam(1) = IDAnnularfinal
- TD_BOPRamDiam(2) = IDPipeRam1final
- TD_BOPRamDiam(3) = IDshearBopfinal
- TD_BOPRamDiam(4) = IDPipeRam2final
-
-
-
-
-
-
- !====================================================
- ! Element Counts in BOPStack Domain
- !====================================================
-
- !if (TD_DrillStemComponentsNumbs>5) then
- TD_Numbs = TD_DrillStemComponentsNumbs-7 ! 7 Elements from the Top of DrillStem
- !else
- ! TD_Numbs = 1
- !end if
-
-
-
-
-
-
-
-
-
- !====================================================
- ! Determination of Elements Diameter in BOPStack Domain
- !====================================================
-
- TD_BOPDiam = 0.d0
- TD_OldFillingValue = 0.d0
- Do i = TD_DrillStemComponentsNumbs,TD_Numbs,-1
-
- TD_LimitUp = TD_DrillStems(i)%TopDepth+TD_DrillStems(i)%ToolJointRange
- TD_LimitDown = TD_DrillStems(i)%DownDepth-TD_DrillStems(i)%ToolJointRange
- TD_ElToolJoints(1,1) = TD_DrillStems(i)%TopDepth ! TD_ElToolJoints(i,j) , i=top & down tooljoints of element , j=top & down tooljoints Depth
- TD_ElToolJoints(1,2) = TD_LimitUp
- TD_ElToolJoints(2,1) = TD_LimitDown
- TD_ElToolJoints(2,2) = TD_DrillStems(i)%DownDepth
-
-
- !===> che meghdar az fazaye annular ba tooljoint por mishavad (for BOP Module)
- Do m = 1,2
- TD_AnnTjDiff = min(TD_ElToolJoints(m,2),(TD_BOPHeight(1)+TD_BOPThickness))-max(TD_ElToolJoints(m,1),(TD_BOPHeight(1)-TD_BOPThickness))
- if (TD_AnnTjDiff<0.) then ! tooljoint is not in the annular range
- TD_AnnTjDiff = 0.d0
- end if
- TD_AnnularFilling = TD_OldFillingValue+(TD_AnnTjDiff/(TD_BOPThickness*2.d0)) ! 0=<TD_AnnularFilling<=1
- TD_OldFillingValue = TD_AnnularFilling
- End Do
-
-
- do j = 1,6
- if ( (TD_BOPHeight(j)-TD_BOPThickness)>TD_LimitUp .and. (TD_BOPHeight(j)+TD_BOPThickness)<TD_LimitDown ) then
- TD_BOPDiam(j) = TD_DrillStems(i)%Od
- TD_BOPElementNo(j) = i
- if ( TD_DrillStems(i)%ComponentType==3 .and. j/=1 .and. TD_DrillStemRotVelocity==0. ) then
- TD_BOPConnectionPossibility(j) = 1
- else if ( j==1 ) then
- TD_BOPConnectionPossibility(j) = 1
- else
- TD_BOPConnectionPossibility(j) = 0
- end if
- !print* , 'T.DP. , B.DP. 1=' , TD_DrillStems(i)%TopDepth , TD_DrillStems(i)%DownDepth
- !print* , 'T.R. , B.R. , LimitUp , LimitDown 1=' , (TD_BOPHeight(j)-TD_BOPThickness) , (TD_BOPHeight(j)+TD_BOPThickness) , TD_LimitUp , TD_LimitDown
- !print* , 'stringNo , ramsNo , Possibility , BOPDiam 1=' , i , j , TD_BOPConnectionPossibility(j) , TD_BOPDiam(j)
- else if ( (TD_BOPHeight(j)+TD_BOPThickness)>=TD_DrillStems(i)%TopDepth .and. (TD_BOPHeight(j)-TD_BOPThickness)<=TD_DrillStems(i)%DownDepth ) then
- TD_BOPDiam(j) = TD_DrillStems(i)%RtoolJoint*2.d0
- TD_BOPElementNo(j) = i
- if ( j==1 ) then
- TD_BOPConnectionPossibility(j) = 1
- else
- TD_BOPConnectionPossibility(j) = 0
- end if
- !print* , 'T.DP. , B.DP. 2=' , TD_DrillStems(i)%TopDepth , TD_DrillStems(i)%DownDepth
- !print* , 'T.R. , B.R. , LimitUp , LimitDown 2=' , (TD_BOPHeight(j)-TD_BOPThickness) , (TD_BOPHeight(j)+TD_BOPThickness) , TD_LimitUp , TD_LimitDown
- !print* , 'stringNo , ramsNo , Possibility , BOPDiam 2=' , i , j , TD_BOPConnectionPossibility(j) , TD_BOPDiam(j)
- end if
- end do
-
- End Do
- TD_AnnularFillingFinal = TD_AnnularFilling
-
- TD_AboveAnnularDiam = TD_BOPDiam(5)
- TD_AnnularPreventerDiam = TD_BOPDiam(1)
- TD_UpperRamDiam = TD_BOPDiam(2)
- TD_BlindRamDiam = TD_BOPDiam(3)
- TD_KillDiam = TD_BOPDiam(6)
- TD_LowerRamDiam = TD_BOPDiam(4)
-
-
- !print* , 'TD_BOPElementNo=' , TD_BOPElementNo
- !print* , 'TD_BOPConnectionPossibility=' , TD_BOPConnectionPossibility
- !print* , 'TD_BOPDiam=' , TD_BOPDiam
-
-
-
-
- !!===> BOP RAMs Condition *** TD_BOPCondition: 0=open , 1=close
- !do j = 1,4
- ! if ( TD_BOPDiam(j)>=TD_BOPRamDiam(j) ) then
- ! TD_BOPCondition(j) = 1
- ! else
- ! TD_BOPCondition(j) = 0
- ! end if
- !end do
-
-
-
-
-
-
-
-
- !====================================================
- ! String Elements Configuration in BOPStack Domain
- !====================================================
-
- !if ( allocated(TD_BOPElement) ) deallocate (TD_BOPElement)
- !allocate(TD_BOPElement())
- n = 0
- TD_BOPElement%ElementType = 0.d0
- TD_BOPElement%ElementStart = 0.d0
- TD_BOPElement%ElementEnd = 0.d0
- do k = TD_DrillStemComponentsNumbs,TD_Numbs,-1
- if( ((TD_DrillStems(k)%TopDepth>=TD_BOPHeight(5)).and.(TD_DrillStems(k)%TopDepth<=TD_BOPHeight(4))) .or. ((TD_DrillStems(k)%DownDepth>=TD_BOPHeight(5)).and.(TD_DrillStems(k)%DownDepth<=TD_BOPHeight(4))) ) then
- n = n+1
- TD_BOPElement(n)%ElementType = TD_DrillStems(k)%ComponentType
- TD_BOPElement(n)%ElementStart = TD_DrillStems(k)%TopDepth
- TD_BOPElement(n)%ElementEnd = TD_DrillStems(k)%DownDepth
- else if ( TD_DrillStems(k)%TopDepth<=TD_BOPHeight(5) .and. TD_DrillStems(k)%DownDepth>=TD_BOPHeight(4) ) then
- n = n+1
- TD_BOPElement(n)%ElementType = TD_DrillStems(k)%ComponentType
- TD_BOPElement(n)%ElementStart = TD_DrillStems(k)%TopDepth
- TD_BOPElement(n)%ElementEnd = TD_DrillStems(k)%DownDepth
- end if
- end do
-
- Call SetBopElements(TD_BOPElement)
-
-
-
-
- end subroutine
|