|
- subroutine PlotFinalMudElements ! is called in subroutine CirculationCodeSelect
-
- Use GeoElements_FluidModule
- USE CMudPropertiesVariables
- USE MudSystemVARIABLES
- USE Pumps_VARIABLES
- Use TD_StringConnectionData
- !USE CHOKEVARIABLES
- !USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure
- !use CManifolds
- use CDrillWatchVariables
- !use CHOKEVARIABLES
- !use CChokeManifoldVariables
- !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
- USE sROP_Other_Variables
- USE sROP_Variables
- Use KickVariables
- USE CKellyConnectionEnumVariables
- USE UTUBEVARS
- use CLog1
- Use CError
- Use , intrinsic :: IEEE_Arithmetic
-
- implicit none
-
- integer jelement, jmud, jsection,ielement,i
- integer jopelement,jopmud,jopsection
- character(len=120) :: temp1, temp2
-
-
-
-
- if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
- write(*,*) 'well cap=' , sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections)) + sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
- MudSystemDotDeltaWellCap= sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections)) + sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts)) - MudSystemDotWellCapOld
- MudSystemDotWellCapOld= sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections)) + sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
- write(*,*) 'cap_reset,DeltaWellCap=' , MudSystemDotDeltaWellCap
- endif
-
-
-
-
- !========================ANNULUS END=================
- if ((Ann_Mud_Forehead_X%Last() - BopStackSpecification%AboveAnnularHeight) > 0.8 .or. Ann_Density%Last()==0.0) then ! for Line (BellNippleToWell-NonFullWell)
- MudSystemDotWellisNOTFull= .true.
- else
- MudSystemDotWellisNOTFull= .false.
- endif
-
- !WRITE(*,*) 'Ann_Mud_Forehead_X%Last() , KillHeight', Ann_Mud_Forehead_X%Last() , KillHeight
- if ((Ann_Mud_Forehead_X%Last() - BopStackSpecification%KillHeight)>0.8 .or. Ann_Density%Last()==0.0) then ! for Line j4 , WellToChokeManifold(Through 26)
- MudSystemDotChokeLineNOTFull= .true.
- else
- MudSystemDotChokeLineNOTFull= .false.
- endif
-
-
-
- !=========================================================
-
- jmud= 1
- jsection= 1
- jelement= 0 ! number of final mud elements
-
-
-
- call Xend_MudElement%Empty()
- call TVDend_MudElement%Empty()
- call Density_MudElement%Empty()
- call MudGeoType%Empty()
- call PipeID_MudElement%Empty()
- call PipeOD_MudElement%Empty()
- !call Angle_MudElement%Empty()
- call MudType_MudElement%Empty()
-
-
-
- DO WHILE(jmud <= MudSystemDotHz_Mud_Forehead_X%Length() .and. jsection<=1)
-
- jelement= jelement+1
- TrueMinValue= min(MudSystemDotHz_Mud_Forehead_X%Array(jmud), MudSystemDotXend_PipeSection(jsection))
-
- call Xend_MudElement%Add(TrueMinValue)
- call TVD_Calculator(TrueMinValue,MudSystemDotMudCircVerticalDepth)
- call TVDend_MudElement%Add(MudSystemDotMudCircVerticalDepth)
- call Density_MudElement%Add(MudSystemDotHz_Density%Array(jmud))
- call PipeID_MudElement%Add(MudSystemDotID_PipeSectionInch(jsection))
- call PipeOD_MudElement%Add(MudSystemDotOD_PipeSectionInch(jsection))
- !call Angle_MudElement%Add(Angle_PipeSection(jsection))
- call MudType_MudElement%Add(Hz_MudOrKick%Array(jmud))
-
-
- if (Xend_MudElement%Array(jelement)== MudSystemDotHz_Mud_Forehead_X%Array(jmud)) then
- jmud= jmud+1
- else
- jsection= jsection+1
- endif
-
- ENDDO
-
- MudSystemDotNoHorizontalMudElements= jelement
-
-
-
-
- jmud= 1
- jsection= 2
-
- DO WHILE(jmud <= MudSystemDotSt_Mud_Forehead_X%Length() .and. jsection<=F_StringIntervalCounts)
-
- jelement= jelement+1
- TrueMinValue= min(MudSystemDotSt_Mud_Forehead_X%Array(jmud), MudSystemDotXend_PipeSection(jsection))
-
- call Xend_MudElement%Add(TrueMinValue)
- call TVD_Calculator(TrueMinValue,MudSystemDotMudCircVerticalDepth)
- call TVDend_MudElement%Add(MudSystemDotMudCircVerticalDepth)
- call Density_MudElement%Add(St_Density%Array(jmud))
- call PipeID_MudElement%Add(MudSystemDotID_PipeSectionInch(jsection))
- call PipeOD_MudElement%Add(MudSystemDotOD_PipeSectionInch(jsection))
- !call Angle_MudElement%Add(Angle_PipeSection(jsection))
- call MudType_MudElement%Add(St_MudOrKick%Array(jmud))
-
-
- if (Xend_MudElement%Array(jelement)== MudSystemDotSt_Mud_Forehead_X%Array(jmud)) then
- jmud= jmud+1
- else
- jsection= jsection+1
- endif
-
- ENDDO
-
- MudSystemDotNoStringMudElements= jelement- MudSystemDotNoHorizontalMudElements
-
-
-
-
-
- jmud= 1
- jsection= F_StringIntervalCounts+1
- DO WHILE(jmud<= Ann_Mud_Forehead_X%Length() .and. jsection<=MudSystemDotNoPipeSections)
-
- jelement= jelement+1
- TrueMinValue= max(Ann_Mud_Forehead_X%Array(jmud), MudSystemDotXend_PipeSection(jsection))
-
- call Xend_MudElement%Add(TrueMinValue)
- call TVD_Calculator(TrueMinValue,MudSystemDotMudCircVerticalDepth)
- call TVDend_MudElement%Add(MudSystemDotMudCircVerticalDepth)
- call Density_MudElement%Add(Ann_Density%Array(jmud))
- call PipeID_MudElement%Add(MudSystemDotID_PipeSectionInch(jsection))
- call PipeOD_MudElement%Add(MudSystemDotOD_PipeSectionInch(jsection))
- !call Angle_MudElement%Add(Angle_PipeSection(jsection))
- call MudType_MudElement%Add(Ann_MudOrKick%Array(jmud))
-
-
- if (Xend_MudElement%Array(jelement)== Ann_Mud_Forehead_X%Array(jmud)) then
- jmud= jmud+1
- else
- jsection= jsection+1
- endif
-
- ENDDO
-
- do i= 2, Xend_MudElement%Length()
- if ( i== MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+1) then
- call Xstart_MudElement%Add (Ann_Mud_Backhead_X%Array(1)) ! start of annulus
- call TVD_Calculator(Ann_Mud_Backhead_X%Array(1),MudSystemDotMudCircVerticalDepth)
- call TVDstart_MudElement%Add(MudSystemDotMudCircVerticalDepth)
- elseif ( i== MudSystemDotNoHorizontalMudElements+1 ) then
- call Xstart_MudElement%Add (MudSystemDotSt_Mud_Backhead_X%Array(1)) ! start of stirng
- call TVD_Calculator(MudSystemDotSt_Mud_Backhead_X%Array(1),MudSystemDotMudCircVerticalDepth)
- call TVDstart_MudElement%Add(MudSystemDotMudCircVerticalDepth)
- else
- call Xstart_MudElement%Add(Xend_MudElement%Array(i-1)) ! normal calculation
- call TVDstart_MudElement%Add(TVDend_MudElement%Array(i-1)) ! normal calculation
- endif
-
- enddo
-
- MudSystemDotNoCasingMudElements = jelement- MudSystemDotNoStringMudElements- MudSystemDotNoHorizontalMudElements
-
-
- !=========================For Torque and Drag========================
- if (allocated(MudSystemDotTDXstart_MudElementArray)) deallocate(MudSystemDotTDXstart_MudElementArray)
- allocate(MudSystemDotTDXstart_MudElementArray(MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+MudSystemDotNoCasingMudElements))
- if (allocated(MudSystemDotTDXend_MudElementArray)) deallocate(MudSystemDotTDXend_MudElementArray)
- allocate(MudSystemDotTDXend_MudElementArray(MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+MudSystemDotNoCasingMudElements))
- if (allocated(MudSystemDotTDDensity_MudElementArray)) deallocate(MudSystemDotTDDensity_MudElementArray)
- allocate(MudSystemDotTDDensity_MudElementArray(MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+MudSystemDotNoCasingMudElements))
-
- MudSystemDotTDNoHorizontalMudElements= MudSystemDotNoHorizontalMudElements
- MudSystemDotTDNoStringMudElements= MudSystemDotNoStringMudElements
- MudSystemDotTDNoCasingMudElements= MudSystemDotNoCasingMudElements
-
-
- MudSystemDotTDXstart_MudElementArray(:) = Xstart_MudElement%Array(:)
- MudSystemDotTDXend_MudElementArray(:) = Xend_MudElement%Array(:)
- MudSystemDotTDDensity_MudElementArray(:) = Density_MudElement%Array(:)
- !=====================================================================
-
-
- !do i=NoHorizontalMudElements+1, NoHorizontalMudElements+NoStringMudElements ! 2-string elements
- ! write(*,333) 'STRING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
- !enddo
-
-
-
- !================================================================
-
- ! Open Hole Mud Elements
- jopmud= 1
- jopsection= 1
- jopelement= 0 ! number of final mud elements
-
-
- call Xend_OpMudElement%Empty()
- call TVDend_OpMudElement%Empty()
- call Density_OpMudElement%Empty()
- call PipeID_OpMudElement%Empty()
- call PipeOD_OpMudElement%Empty()
- !call Angle_OpMudElement%Empty()
- call MudTypeOp_MudElement%Empty()
-
-
-
- DO WHILE(jopmud<= MudSystemDotOp_Mud_Forehead_X%Length() .and. jopsection<=F_BottomHoleIntervalCounts)
-
- jopelement= jopelement+1
- TrueMinValue= max(MudSystemDotOp_Mud_Forehead_X%Array(jopmud), MudSystemDotXend_OpSection(jopsection))
- call Xend_OpMudElement%Add(TrueMinValue)
- call TVD_Calculator(TrueMinValue,MudSystemDotMudCircVerticalDepth)
- call TVDend_OpMudElement%Add(MudSystemDotMudCircVerticalDepth)
- call Density_OpMudElement%Add(MudSystemDotOp_Density%Array(jopmud))
- call PipeID_OpMudElement%Add(MudSystemDotID_OpSectionInch(jopsection))
- call PipeOD_OpMudElement%Add(MudSystemDotOD_OpSectionInch(jopsection))
- !call Angle_MudElement%Add(Angle_PipeSection(jopsection))
- call MudTypeOp_MudElement%Add(Op_MudOrKick%Array(jopmud))
-
-
- if (Xend_OpMudElement%Array(jopelement)== MudSystemDotOp_Mud_Forehead_X%Array(jopmud)) then
- jopmud= jopmud+1
- else
- jopsection= jopsection+1
- endif
-
- ENDDO
-
- do i= 2, Xend_OpMudElement%Length()
- call Xstart_OpMudElement%Add(Xend_OpMudElement%Array(i-1))
- call TVDstart_OpMudElement%Add(TVDend_OpMudElement%Array(i-1))
- enddo
-
- MudSystemDotNoBottomHoleMudElements = jopelement
-
-
- !================================================================
-
-
-
- if(allocated(StringMudElement)) deallocate(StringMudElement)
- allocate(StringMudElement(MudSystemDotNoStringMudElements))
-
- if(allocated(CasingMudElement)) deallocate(CasingMudElement)
- allocate(CasingMudElement(MudSystemDotNoCasingMudElements+MudSystemDotNoBottomHoleMudElements))
-
- MudSystemDotistring=0
- MudSystemDoticasing=0
-
- MudSystemDotBitMudDensity= Density_MudElement%Array(MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements) ! (for ROP module)
- !================================================================
-
- !============================ UTUBE =============================
-
- !IF (UtubePossibility== .true. .and. Get_KellyConnection() /= KELLY_CONNECTION_STRING .and. WellHeadIsOpen) THEN
- IF (MudSystemDotUtubePossibility== .true. .and. TD_FluidStringConnectionMode==0 .and. WellHeadIsOpen .AND. NoGasPocket == 0) THEN
- CALL WellPressureDataTransfer
- !WRITE (*,*) ' U-Tube Done 1'
- CALL Utube
- !WRITE (*,*) ' U-Tube Done 2'
- if (QUtubeInput> 0.0) call Utube1_and_TripIn
- if (QUtubeOutput> 0.0) call Utube2_and_TripIn
- END IF
-
- !========================== UTUBE- end =========================
-
- ! do imud=1, st_MudDischarged_Volume%Length()
- ! write(*,*) 'st-plot:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud)
- !enddo
- !==================== Display ========================
- !do i=1, St_MudOrKick%Length()
- ! write(*,555) i,'St_Volume(i), type=' ,St_MudDischarged_Volume%Array(i),St_MudOrKick%Array(i)
- !
- ! IF (IEEE_Is_NaN(St_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in St Volume-Plot')
- ! IF (St_MudDischarged_Volume%Array(i)<0.) call ErrorStop('St Volume <0' , St_MudDischarged_Volume%Array(i))
- !enddo
-
-
- IF (ANY(IEEE_Is_NaN(MudSystemDotOp_MudDischarged_Volume%Array(:))) .OR. ANY(MudSystemDotOp_MudDischarged_Volume%Array(:) <= 0.0)) THEN
- do i = 1 , Op_MudOrKick%Length()
- write(*,555) i,'Op_Volume(i), type=' ,MudSystemDotOp_MudDischarged_Volume%Array(i) , Op_MudOrKick%Array(i) , MudSystemDotOp_Density%Array(i)
- end do
- call ErrorStop('NaN in Op Volume-Plot or Op Volume <=0')
- END IF
-
-
- IF (ANY(IEEE_Is_NaN(MudSystemDotAnn_MudDischarged_Volume%Array(:))) .OR. ANY(MudSystemDotAnn_MudDischarged_Volume%Array(:) <= 0.0)) THEN
- do i = 1 , Ann_MudOrKick%Length()
- write(*,555) i,'Ann_Volume(i), type=' ,MudSystemDotAnn_MudDischarged_Volume%Array(i) , Ann_MudOrKick%Array(i) , Ann_Density%Array(i)
- end do
- call ErrorStop('NaN in Ann Volume-Plot or Ann Volume <=0')
- END IF
-
- !do i=1, Ann_MudOrKick%Length()
- ! !write(*,555) i,'Ann_Volume(i), type=' ,Ann_MudDischarged_Volume%Array(i),Ann_MudOrKick%Array(i),Ann_Density%Array(i)
- !
- ! IF (IEEE_Is_NaN(Ann_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in Ann Volume-Plot')
- ! IF (Ann_MudDischarged_Volume%Array(i)<=0.) call ErrorStop('Ann Volume <=0' , Ann_MudDischarged_Volume%Array(i))
- !enddo
-
- 555 FORMAT(I3,5X,A42,(f12.5),5X,I3,5X,(f12.5))
-
- MudSystemDotNoStringMudElementsForPlot= MudSystemDotNoStringMudElements
-
- ! 1-Horizontal Mud Elements are not shown
- !write(*,333) 'Horiz:', 1,'Xstart\=', Xstart_MudElement%Array(1), 'Xend=' , Xend_MudElement%Array(1), 'Density=' , Density_MudElement%Array(1), 'MudType=' , MudType_MudElement%Array(1)
-
- do i=MudSystemDotNoHorizontalMudElements+1, MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements ! 2-string elements
- if (Xend_MudElement%Array(i) <= 0.0) then
- MudSystemDotNoStringMudElementsForPlot= MudSystemDotNoStringMudElementsForPlot-1
- cycle
- endif
- MudSystemDotistring= MudSystemDotistring+1
- StringMudElement(MudSystemDotistring)%StartMd = Xstart_MudElement%Array(i)
- StringMudElement(MudSystemDotistring)%EndMd = Xend_MudElement%Array(i)
- !StringMudElement(istring)%Id = PipeID_MudElement%Array(i)
- !StringMudElement(istring)%Od = PipeOD_MudElement%Array(i)
- StringMudElement(MudSystemDotistring)%Density = Density_MudElement%Array(i)
-
- if (MudType_MudElement%Array(i) == 104) then
- MudType_MudElement%Array(i)= 4 ! air
- elseif (MudType_MudElement%Array(i) > 0 .and. MudType_MudElement%Array(i) < 100) then ! all kicks
- MudType_MudElement%Array(i)= 1 ! gas kick
- endif
-
- StringMudElement(MudSystemDotistring)%MudType = MudType_MudElement%Array(i)
- !write(*,333) 'STRING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
- enddo
-
-
-
- do i=Xend_MudElement%Length(), MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+1 , -1 ! 3-casing elements
- MudSystemDoticasing= MudSystemDoticasing+1
- CasingMudElement(MudSystemDoticasing)%StartMd = Xend_MudElement%Array(i)
- CasingMudElement(MudSystemDoticasing)%EndMd = Xstart_MudElement%Array(i)
- !CasingMudElement(icasing)%Id = PipeID_MudElement%Array(i)
- !CasingMudElement(icasing)%Od = PipeOD_MudElement%Array(i)
- !write(*,333) 'CASING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
- !call Log_1(temp1)
- !write(*,444) 'CASING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'PipeID_MudElement%Array(i)=' , PipeID_MudElement%Array(i), 'PipeOD_MudElement%Array(i)=' , PipeOD_MudElement%Array(i)
- CasingMudElement(MudSystemDoticasing)%Density = Density_MudElement%Array(i)
-
- if (MudType_MudElement%Array(i) == 104) then
- MudType_MudElement%Array(i)= 4 ! air
- elseif (MudType_MudElement%Array(i) > 0 .and. MudType_MudElement%Array(i) < 100) then
- MudType_MudElement%Array(i)= 1 ! gas kick
- endif
-
- CasingMudElement(MudSystemDoticasing)%MudType = MudType_MudElement%Array(i)
-
- enddo
-
- do i= MudSystemDotNoBottomHoleMudElements, 1 , -1 ! 4-open hole elements
- MudSystemDoticasing= MudSystemDoticasing+1
- CasingMudElement(MudSystemDoticasing)%StartMd = Xend_OpMudElement%Array(i)
- CasingMudElement(MudSystemDoticasing)%EndMd = Xstart_OpMudElement%Array(i)
- !CasingMudElement(icasing)%Id = PipeID_OpMudElement%Array(i)
- !CasingMudElement(icasing)%Od = PipeOD_OpMudElement%Array(i)
- !write(*,333) 'OpenHole:',i,'Xstart\=', Xstart_OpMudElement%Array(i), 'Xend=' , Xend_OpMudElement%Array(i), 'Density=' , Density_OpMudElement%Array(i), 'MudType=' , MudTypeOp_MudElement%Array(i)
- !call Log_1(temp2)
- !write(*,444) 'OpenHole:',i,'Xstart\=', Xstart_OpMudElement%Array(i), 'Xend=' , Xend_OpMudElement%Array(i), 'PipeID_MudElement%Array(i)=' , PipeID_MudElement%Array(i), 'PipeOD_MudElement%Array(i)=' , PipeOD_MudElement%Array(i)
- CasingMudElement(MudSystemDoticasing)%Density = Density_OpMudElement%Array(i)
-
- if (MudTypeOp_MudElement%Array(i) == 104) then
- MudTypeOp_MudElement%Array(i)= 4 ! air
- elseif (MudTypeOp_MudElement%Array(i) > 0 .and. MudTypeOp_MudElement%Array(i) < 100) then
- MudTypeOp_MudElement%Array(i)= 1 ! gas kick
- endif
-
- CasingMudElement(MudSystemDoticasing)%MudType = MudTypeOp_MudElement%Array(i)
- enddo
-
-
-
- 333 FORMAT(A10,I3,5X,A8,(f12.5),5X,A8,(f12.5),5X,A8,(f12.5),5X,A8,I3)
- 444 FORMAT(A10,I2,5X,A8,(f12.3),5X,A8,(f12.3),5X,A8,(f12.3),5X,A8,(f12.3))
-
-
-
- ! shomare gozari be tartib HZ mud, ST mud, Casing
- ! shomare gzari OpenHole jodagane ast az 1
-
- call SetStringFluids(MudSystemDotNoStringMudElementsForPlot, StringMudElement) !for data display in string
- call SetAnnalusFluids(MudSystemDotNoCasingMudElements+MudSystemDotNoBottomHoleMudElements, CasingMudElement) !for data display in casing
-
-
- !===========================================================================================================================
- !===========================================================================================================================
-
-
- end subroutine PlotFinalMudElements
-
-
-
|