SUBROUTINE FlowStartup USE Fluid_Flow_Startup_Vars USE CStringConfigurationVariables USE CMudPropertiesVariables USE FricPressDropVars USE KickVariables USE MudSystemVARIABLES USE PressureDisplayVARIABLES USE CShoeVariables USE TD_DrillStemComponents USE TD_WellGeometry, pi3 => pi USE CPathGenerationVariables USE CWellSurveyDataVariables Use CHOKEVARIABLES, pi4 => pi IMPLICIT NONE INTEGER :: i PressureGauges(:) = 0.0 KickSinglePocket = Reservoir%MakeKickSinglePacket IF (KickSinglePocket) THEN MaxGasPocket = 1 ELSE MaxGasPocket = 4 END IF MaxChokeDensityChange = 25.0 ! [ppg/min] ChokeMinDensity = 2.0 ChokeDensity = MudProperties%ActiveDensity MinKickVol = 0.5 ! USGal SecondaryKickVol = 0.0 SecondaryKickWeight = 0.0 NoGasPocket = 0 ! No Kick WellHeadOpen = .TRUE. WellHeadWasOpen = .TRUE. BackPressure = 0.0 GasKickPumpFlowRate = 0.0 DownHole%KickVolume = 0.0 DownHole%InfluxRate = 0.0 ExitMass = 0.0 MinAllowableKickVol = 1.0 * (42.0 / Convft3toUSgal) ! 1 bbl * 42 gal/bbl / 7.48 gal/ft^3 = ... ft^3 StCompressedMudVol = 0.0 AnnCompressedMudVol = 0.0 KickFlux = .FALSE. KickOffBottom = .FALSE. KickWasExitingThroughChoke = .FALSE. FloatValveOpen = .TRUE. Choke%ChokeAreaFullyOpen = 123.0 / 64.0 ! fully open area is 123/64 in^2 = 0.01334635 ft^2 ChokeBypassArea = PI / 4.0 * BopStackSpecification%ChokeLineId**2 BHPSafetyMargin = 150.0 AChBHPTol = 15.0 ManChoke1Plug = 0 ManChoke2Plug = 0 ManChoke1Washout = 0 ManChoke2Washout = 0 BitJetsPlugged = 0 BitJetsWashedOut = 0 CasingPressure_DataDisplayMalF = 0 SoundSpeed = 1530.0 / Convfttom PressureTimeStepDelay(1) = INT(2.0 * SUM(StringConfiguration%StringConfigurations(2:)%ComponentLength) / SoundSpeed / dt) PressureTimeStepDelay(2) = INT(PathGeneration%Items(SIZE(PathGeneration%Items))%MeasuredDepth / SoundSpeed / dt) PressureTimeStepDelay(3) = INT(Shoe%ShoeDepth / SoundSpeed / dt) !WRITE (*,*) SUM(StringConfigurations(2:)%ComponentLength), PathGenerations(SIZE(PathGenerations))%TotalVerticalDepth!, WellSurveyData(SIZE(WellSurveyData))%TotalVerticalDepth !WRITE (*,*) PathGenerations(SIZE(PathGenerations))%MeasuredDepth!, WellSurveyData(SIZE(WellSurveyData))%MeasuredDepth WRITE (*,*) 'time step delay', PressureTimeStepDelay DO i = 1 , PressureTimeStepDelay(1) CALL PumpPressureDelay%AddToFirst(0.0) END DO DO i = 1 , PressureTimeStepDelay(2) CALL BottomHolePressureDelay%AddToFirst(REAL(0.052 * MudProperties%ActiveDensity * PathGeneration%Items(SIZE(PathGeneration%Items))%TotalVerticalDepth)) END DO DO i = 1 , PressureTimeStepDelay(3) CALL ShoePressureDelay%AddToFirst(REAL(0.052 * MudProperties%ActiveDensity * Shoe%ShoeDepth)) END DO !!!!!!! Methane Information GasType(1)%CritPress = 673.0 GasType(1)%CritTemp = 344.0 GasType(1)%MolarWt = 16.04 GasType(1)%StDensity = 0.04238 GasType(1)%GasConstant = RUniversal / GasType(1)%MolarWt !!!!!!!! H2S Information GasType(2)%CritPress = 1306.0 GasType(2)%CritTemp = 673.0 GasType(2)%MolarWt = 34.08 GasType(2)%StDensity = 0.09087 GasType(2)%GasConstant = RUniversal / GasType(2)%MolarWt !!!!!!!! CO2 Information GasType(3)%CritPress = 1072.0 GasType(3)%CritTemp = 548.0 GasType(3)%MolarWt = 44.01 !GasType(3)%StDensity = 00 GasType(3)%GasConstant = RUniversal / GasType(2)%MolarWt !!!!!!!! Mud density and viscosity Theta600Refrence = MudProperties%ActiveThetaSixHundred Theta300Refrence = MudProperties%ActiveThetaThreeHundred DensityRefrence = MudProperties%ActiveDensity END SUBROUTINE