|
- subroutine CirculationCodeSelect ! is called in subroutine Fluid_Flow_Solver
-
- Use KickVariables
- Use MudSystemVARIABLES
- USE TD_DrillStemComponents
- Use CUnityInputs
- Use CUnityOutputs
- USE CKellyConnectionEnumVariables
- USE UTUBEVARS
- use sROP_Variables
- USE PressureDisplayVARIABLES
-
-
-
- implicit none
-
-
- Integer i
-
- !NewInfluxNumber = NoGasPocket
-
- MudSystemDotFlow_timeCounter= MudSystemDotFlow_timeCounter+1
-
- !if (ChokePanelStrokeResetSwitch == 1) then
- ! Flow_timeCounter= 0
- !endif
-
-
- !write(*,*) 'Flow_timeCounter' , Flow_timeCounter
-
- !===========================Shoe Lost===============================
-
- call ShoeLostSub
-
- !===================================================================
-
-
- MudSystemDotiLoc= 1 ! will be changed in KickFlux and Migration or Pump and TripIn (save OP Mud data)
- !KickMigration_2SideBit= .false.
- Call Set_FlowPipeDisconnect(.false.)
- Call Set_FlowKellyDisconnect(.false.)
-
- call ElementsCreation
-
-
-
-
- if (MUD(8)%Q > 0.0) call FillingWell_By_BellNipple ! Filling Well Through BellNipple ( Path j11 )
- !if (MUD(10)%Q > 0.0) call FillingWell_By_Pumps ! Filling Well Through Pumps ( Path j19 )
-
- !write(*,*) 'TD_RemoveVolume,Get_JointConnectionPossible=' , TD_RemoveVolume,Get_JointConnectionPossible()
-
- if (TD_RemoveVolume > 0.) call DisconnectingPipe !! .and. Get_JointConnectionPossible() == .false.) call DisconnectingPipe
-
-
- IF (KickFlux .AND. NOT(KickOffBottom)) THEN
- call Kick_Influx
- endif
-
-
-
-
- IF ( MudSystemDotNewInfluxNumber > 0 ) THEN
- !write(*,*) 'KickOffBottom , ROP=' , KickOffBottom , Rate_of_Penetration
- call Kick_Migration
- endif
-
- ! ============================ must be after migration ==============================
-
- DO MudSystemDotKickNumber= MudSystemDotNewInfluxNumber-NoGasPocket+1 , MudSystemDotNewInfluxNumber
- ! FINDING NEW KICK LOCATIONS:
- MudSystemDotAnn_KickLoc= 0
- MudSystemDotOp_KickLoc= 0
- MudSystemDotChokeLine_KickLoc= 0
-
- do i = 1, Ann_MudOrKick%Length ()
- if (Ann_MudOrKick%Array(i) == MudSystemDotKickNumber) then
- MudSystemDotAnn_KickLoc = i
- exit
- endif
- end do
-
- do i = 1, Op_MudOrKick%Length ()
- if (Op_MudOrKick%Array(i) == MudSystemDotKickNumber) then
- MudSystemDotOp_KickLoc = i
- exit
- endif
- end do
-
- do i = 1, ChokeLine_MudOrKick%Length ()
- if (ChokeLine_MudOrKick%Array(i) == MudSystemDotKickNumber) then
- MudSystemDotChokeLine_KickLoc = i
- exit
- endif
- end do
-
- ! ============================ must be after migration-end ===========================
-
- IF (ALLOCATED(GasPocketWeight%Array) .and. MudSystemDotKickNumber == MudSystemDotNewInfluxNumber .AND. NOT(KickOffBottom) .AND. WellHeadIsOpen) THEN
-
- cycle
-
- ELSE IF (ALLOCATED(GasPocketWeight%Array)) THEN
-
- if (((GasPocketDeltaVol%Array(MudSystemDotNewInfluxNumber - MudSystemDotKickNumber + 1) > 0.0 .AND. WellHeadIsOpen) .or. MudSystemDotKickexpansion_DueToMudLost) ) call Kick_Expansion
-
- if ((GasPocketDeltaVol%Array(MudSystemDotNewInfluxNumber - MudSystemDotKickNumber + 1) < 0.0 ) .OR. WellHeadIsOpen == .FALSE.) CALL Kick_Contraction
-
- ENDIF
-
-
- ENDDO
-
-
-
-
- MudSystemDotLostInTripOutIsDone= .false.
-
- if( MudSystemDotDeltaVolumeOp >= 0.0 .and. Get_KellyConnection()==KELLY_CONNECTION_STRING) then
- !write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp
- call Pump_and_TripIn
- elseif (MudSystemDotDeltaVolumeOp < 0.0) then
- ! when we have Utube and tripping out simultaneously, it uses "TripOut_and_Pump" subroutine, and then Utube code is done
- ! "Utube" and "Pump_and_TripIn" subroutines, not to be used simultaneously because "Utube" code supports trip in
- call TripOut_and_Pump
- endif
-
- WellOutletDensity= Ann_Density%Last() ! (ppg) used in MudSystem
-
-
-
- if (MUD(4)%Q > 0.) then ! ( j4 > 0 ) ! THIS CIRCULATION CODE IS JUST FOR LINE J4, AND NOT NEEDED FOR LINE J18
- call ChokeLineMud
- endif
-
-
- call Choke_GasSound
-
- !WRITE(*,*) 'CIRCU-Ann_Saved_MudDischarged_Volume' , Ann_Saved_MudDischarged_Volume
-
- ! ****Utube is called in Plot Subroutine****
-
- Call Instructor_CirculationMud_Edit
-
-
-
- call PlotFinalMudElements
-
- MudChecked= .true.
- MudSystemDotUtubePossibility= .true.
-
-
- !WRITE(*,*) '***********************************************************************'
-
-
-
-
- end subroutine CirculationCodeSelect
|