|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501 |
- SUBROUTINE NormalCirculation_StartUp() ! is called in module FluidFlowMain
-
- USE MudSystemVARIABLES
- use CTanksVariables
- USE CMudPropertiesVariables
- Use GeoElements_FluidModule
- Use KickVariables
- Use CUnityOutputs
- Use CShoeVariables
- USE Pump_VARIABLES
-
- implicit none
-
- ! temporary varibales for solving pressure jerks -- 1399-11-09
- !Pump1BlownInTimeStep = 0
- !Pump2BlownInTimeStep = 0
- !Pump3BlownInTimeStep = 0
-
- !Pump1BlownStarted = .FALSE.
- !Pump2BlownStarted = .FALSE.
- !Pump3BlownStarted = .FALSE.
-
- Pump1BlownCount = 0
- Pump2BlownCount = 0
- Pump3BlownCount = 0
-
-
- DeltaWellCap=0.
- WellCapOld = 0.
- AnnCapOld=0.
- DeltaAnnCap=0.
-
-
- Total_Stroke_Counter_For_Plot = 0.0
-
- DeltaT_Mudline=0.1 !second
-
- Call Set_FlowKellyDisconnect(.false.)
- Call Set_FlowPipeDisconnect(.false.)
-
- !HZ_ADD= 0.d0
- Flow_timeCounter= 0
- MudSys_timeCounter= 0
- FluidFlowCounter = 0
- !========================================================================
- ! MUD CIRCULATION STARTUP
- !========================================================================
-
- FormationLostPressure= LeakOff * ShoeDepth
- ShoeFractured= .false.
-
- UGBOSuccessionCounter = 0 ! also in starup
- UGBOSuccessionCounterOld = 0 ! also in starup
-
-
-
- ChokeLineFlowRate= 0.0
- StringFlowRate= 0.0
- AnnulusFlowRate= 0.0
-
- MudVolume_InjectedFromAnn= 0.D0
- MudVolume_InjectedToBH= 0.D0
-
- DensityMixTol= 0.1 !(ppg)
- CuttingDensityMixTol= 0.5
- NewPipeFilling= 1
- UtubeFilling= 1
- UtubeEmptyVolume= 0.0
-
- UtubeMode1Activated= .false.
- UtubeMode2Activated= .false.
- UtubePossibility= .false.
-
-
- !KickMigration_2SideBit = .FALSE.
-
- KickDx= (AutoMigrationRate/3600.)*DeltaT_Mudline !AutoMigrationRate (ft/h)= ft per DeltaT_Mudline
-
-
- NewInfluxElementCreated= 0
- NewInfluxNumber= 0
-
- !KickVolumeinAnnulus= 0.0
- KickDeltaVinAnnulus= 0.0
- GasKickPumpFlowRate= 0.0
-
- FirstMudSet= 0
- FirstSetUtube1=0
- FirstSetUtube2=0
- SuctionMud=1
- ImudCount= 1
- imud=1
- iLoc= 1 ! for Kick
-
- Suction_Density_MudSystem= ActiveDensity
- SuctionDensity_Old= ActiveDensity ! initial(ppg)
- StringDensity_Old= ActiveDensity ! initial(ppg)
- AnnulusSuctionDensity_Old= ActiveDensity ! initial(ppg)
- ChokeLineDensity_Old= ActiveDensity ! initial(ppg)
-
- TotalAddedVolume= 0.
-
-
- xx=0.
-
-
-
- END SUBROUTINE NormalCirculation_StartUp
-
-
-
-
-
-
-
- SUBROUTINE MudSystem_StartUp()
- USE CMudPropertiesVariables
- USE MudSystemVARIABLES
- USE CDataDisplayConsoleVariables
- USE CHOKEVARIABLES
- USE Pump_VARIABLES
- USE CBopStackVariables
- USE CPumpsVariables
- use CTanksVariables
- USE KickVariables
- implicit none
-
-
-
-
-
- CALL MUDLINE_LOSS_INPUTS()
-
- !Total_Pump_Gpm=10. ! Initial Value
- MUD%Q=0. ! Initial Value
-
- Q_flow32=0.
- Q_flow33=0.
- Q_flow34=0.
- Q_flow35=0.
-
- DeltaT_Mudline=0.1 !second
-
- GasKickPumpFlowRate= 0.
- BellNippleVolume= 0.
- BellNippleDensity= 0.
- MudBucketVolume= 0.
- MudBucketDensity= 0.
- BellNippleDumpVolume= 0.
- !BellNippleDumpRate= 0.
- !BellNippleToPitsRate= 0.0
- MudChecked= .true.
-
- condition32Final= .TRUE.
- condition33Final= .TRUE.
- condition34Final= .TRUE.
-
-
- PressureGauge75= 0.0
- PressureGauge76 = 0.0
-
-
- !!======================================================================
- !! TRIP TANK
- !!======================================================================
-
- TripTank_MinVol_Allowded= 50.*42. !(bbl to gal, initial value)
- TripTank_MaxVol_Allowded= 50. *42. !(bbl to gal, initial value)
-
-
- ActiveTankFloorArea= (ActiveTotalTankCapacityGal) / (7.48051948*100./12.) ! (ft^2) - Tank Height= 100 inch , 12=inch to ft 7.48051948=gal to ft^3
- TripTankFloorArea= (50.*42.) / (7.48051948*100./12.) ! (ft^2) - 50.*42.=Trip Tank Capacity in BBl*42= Gal , Tank Height= 100 inch , 12=inch to ft 7.48051948=gal to ft^3
-
-
-
- TripTank_Vol= InitialTripTankMudVolumeGal !(gal)
- TripTank_Dens= 1.
- TripTankGauge=0.
-
-
-
- ReturnToTrip_Q= 1.
- ActiveToTrip_Q= 1.
-
-
- TripTankPump_Q= .8
-
-
- ReturnToTrip_Dens=1.0 ! ppg(lbm/gal)
- ActiveToTrip_Dens=1.0
-
- !!======================================================================
- !! MUD VOLUME TOTALIZER
- !!======================================================================
-
- Mp1Density= 0.0 !(VALVE82)
- Mp2Density= 0.0 !(VALVE83)
- Mp3Density= 0.0 !(VALVE84)
-
-
- ReserveTankVolume= ReserveMudVolumeGal ! initial volume (gal)
- ReserveTankDensity= ReserveDensity ! initial
-
-
-
- CementTankVolumeCalc= CementTankVolume !movaghat--- initial volume (gal)
- CementTankDensityCalc= CementTankDensity !movaghat--- initial
-
- PumpsDumpVolume=0.0
- PumpsDumpFlowRate= 0.0
-
-
-
- ActiveTankVolume= ActiveMudVolumeGal ! initial volume (gal)
- RefrencePitVolume= ActiveTankVolume/42. !(bbl)
- RefrencePitVolume_DrillWatch= ActiveTankVolume/42. !(bbl)
-
- MVT_MinVol_Allowded= 0.
- MVT_MaxVol_Allowded= 0.
-
- MudTank1_vol= ActiveMudVolumeGal/3. ! (gal)
- MudTank2_vol= ActiveMudVolumeGal/3. ! (gal)
- MudTank3_vol= ActiveMudVolumeGal/3. ! (gal)
- ActiveTankSettled= ActiveSettledContentsGal ! (gal)
- MudTank4_vol= InitialTripTankMudVolumeGal ! (gal)
-
- TripTankVolumeCalc= InitialTripTankMudVolumeGal ! initial volume (gal)
- ActiveTankDensity= ActiveDensity ! initial(ppg)
- TripTankDensityCalc= TripTankDensity ! initial(ppg)
-
- ChokeManifoldDumpVolume= 0.0
-
- PitGainLossZero= 0.
- PitGainLossZero_Old= PitGainLossZero
- MVTCoarseKnob_Old= MVTCoarseKnob
- MVTFineKnob_Old= MVTFineKnob
- FirstSet_Time= .true.
-
-
-
- PedalMeter= PedalFlowMeter !1600. !(gpm)
- ReturnFlowRate=0.
-
-
-
- TotalStrokes1MFFI =0.
- TotalStrokes2MFFI =0.
-
- TotalStrokesPump1=0.
- TotalStrokesPump2=0.
- GraphTotalStrokes=0.
-
-
- TotalStrokes1 =0.
- TotalStrokes2 =0.
-
-
-
-
-
-
- end
-
-
-
-
-
-
-
-
-
-
-
- SUBROUTINE MUDLINE_LOSS_INPUTS()
- USE MudSystemVARIABLES
- USE CBopStackVariables
- USE CPumpsVariables
- implicit none
- INTEGER I
-
-
-
- !===========================================================================
- ! MUDLINE MINOR LOSSES INPUT
- !===========================================================================
-
- NO_MudMinors=4
-
- ALLOCATE (MudMinors(NO_MudMinors,4))
-
- ! ID(INCH) LF CV NOTE(BAR) DESCRIPTION
- MudMinors(1,1)= MudPump1Output
- MudMinors(1,2:4)= (/1.5*8., 0., 0./) !elbow (MLnumber=1,,PumpsToString)
- MudMinors(2,1)= MudPump1Output
- MudMinors(2,2:4)= (/1.5*6., 0., 0./) !elbow (MLnumber=2,,STGaugeToString)
- MudMinors(3,1:4)= (/0., 0., 0., 0./) !elbow (MLnumber=3,,WellToPits)
- MudMinors(4,1)= ChokeLineId
- MudMinors(4,2:4)= (/1.5*7., 0., 0./) !elbow (MLnumber=4,,WellToChokeManifold)
-
-
-
- ALLOCATE (MINORDIAMETER_MUDLINE(NO_MudMinors),AREAMINOR_MUDLINE(NO_MudMinors),LF_MUDLINE(NO_MudMinors),CV_MUDLINE(NO_MudMinors) &
- ,NOTE_MUDLINE(NO_MudMinors))
-
-
-
- DO I=1,NO_MudMinors
- MINORDIAMETER_MUDLINE(I)=MudMinors(I,1)
- LF_MUDLINE(I)=MudMinors(I,2)
- CV_MUDLINE(I)=MudMinors(I,3)
- NOTE_MUDLINE(I)=MudMinors(I,4)
-
-
- AREAMINOR_MUDLINE(I)=PII*(MINORDIAMETER_MUDLINE(I)*0.0254)**2/4. !D(in), AREA(m^2)
- ENDDO
-
- !===========================================================================
- ! MUDLINE PIPNING LOSSES INPUT
- !===========================================================================
- NO_PIPINGSMUDLINE=4
-
- ALLOCATE (PIPINGS_MUDLINE(NO_PIPINGSMUDLINE,3))
-
- ! ID(INCH) L(FEET) ROUGHNESS(MM)=e DESCRIPTION
- PIPINGS_MUDLINE(1,1)= MudPump1Output
- PIPINGS_MUDLINE(1,2:3)= (/265., 0.03/) !(MLnumber=1,,PumpsToString)
- PIPINGS_MUDLINE(2,1)= MudPump1Output
- PIPINGS_MUDLINE(2,2:3)= (/100., 0.03/) !(MLnumber=2,,STGaugeToString)
- PIPINGS_MUDLINE(3,1:3)= (/0., 0., 0./) !(MLnumber=3,,WellToPits)
- PIPINGS_MUDLINE(4,1)= ChokeLineId
- PIPINGS_MUDLINE(4,2)= ChokeLineLength
- PIPINGS_MUDLINE(4,3)= 0.03 !(MLnumber=4,,WellToChokeManifold)
-
- Area_ChokeLineFt= PII*((ChokeLineId/12.)**2)/4. !D(in), AREA(ft^2)
- ChokeLine_VolumeCapacity= Area_ChokeLineFt* ChokeLineLength* 7.48051948 ! (gal)
-
- ALLOCATE (DIAM_MUDLINE_INCH(NO_PIPINGSMUDLINE), &
- AREA_MUDLINE(NO_PIPINGSMUDLINE),LENGT_MUDLINE(NO_PIPINGSMUDLINE),ROUGHNESS_MUDLINE(NO_PIPINGSMUDLINE),RELROUGH_MUDLINE(NO_PIPINGSMUDLINE))
-
-
- DO I=1,NO_PIPINGSMUDLINE
- DIAM_MUDLINE_INCH(I)=PIPINGS_MUDLINE(I,1)
- LENGT_MUDLINE(I)=PIPINGS_MUDLINE(I,2)
- ROUGHNESS_MUDLINE(I)=PIPINGS_MUDLINE(I,3)
-
-
-
- AREA_MUDLINE(I)=PII*(DIAM_MUDLINE_INCH(I)*0.0254)**2/4 !D(in), AREA(m^2)
- RELROUGH_MUDLINE(I)=ROUGHNESS_MUDLINE(I)/(DIAM_MUDLINE_INCH(I)*25.4) !e/D
- !DIAM_MUDLINE_MM(I)=DIAM_MUDLINE_MM(I)*.001 ! (m)
- LENGT_MUDLINE(I)=LENGT_MUDLINE(I)*.3048 ! (m)
- ENDDO
-
-
- !===========================================================================
- ! MUDLINE STATIC LOSSES INPUT
- !===========================================================================
-
- ! Height are in (meter)
- Pumps_Height= 0.
- STpipeGauge_Height= 2. !(m)
- Pits_Height= 1. !(m)
- ChokeManifold_Height= 1.*0.3048 !(ft to meter)
- WellChokeExit_Height= GroundLevel-KillHeight
-
-
-
-
-
-
-
-
-
-
-
-
-
- END
-
-
-
-
- SUBROUTINE MUDLINE_LOSSES(MLnumber)
-
- USE MudSystemVARIABLES
- implicit none
- integer I
- INTEGER MLnumber
-
-
- !===============================PIPE LOSS===================================
- MUD(MLnumber)%Re_MUDline=MUD(MLnumber)%Q*6.30902e-5*DIAM_MUDLINE_INCH(MLnumber)*0.0254/(AREA_MUDLINE(MLnumber)*MUD(MLnumber)%nu) !<<<<<< nu: DOROST SHAVAD.ALAN DAR STARTUP SET SHODE
- !write(*,*) 'MUD(MLnumber)%Re_MUDline=' , MUD(MLnumber)%Re_MUDline
- ! Q*6.30902e-5 for (gpm) to (m^3/sec)
- if ( MUD(MLnumber)%Re_MUDline<Re_cr) then
- MUD(MLnumber)%fric=64/ MUD(MLnumber)%Re_MUDline
- else
-
- MUD(MLnumber)%fric=1/(-1.8*log10((RELROUGH_MUDLINE(MLnumber)/3.7)**1.11+6.9/ MUD(MLnumber)%Re_MUDline))**2
- endif
-
- MUD(MLnumber)%fricloss=((MUD(MLnumber)%fric*(wdens*MUD(MLnumber)%Mud_SG*LENGT_MUDLINE(MLnumber)*(MUD(MLnumber)%Q*6.30902e-5/AREA_MUDLINE(MLnumber))**2))/(2*DIAM_MUDLINE_INCH(MLnumber)*0.0254))/6895
-
-
- !==============================MINOR LOSS===================================
-
- if (LF_MUDLINE(MLnumber)/=0) then
- MUD(MLnumber)%minlosspa_MUDLINE=LF_MUDLINE(MLnumber)*wdens*MUD(MLnumber)%Mud_SG*(MUD(MLnumber)%Q*6.30902e-5/AREAMINOR_MUDLINE(MLnumber))**2/2 !(Pa)
- MUD(MLnumber)%minloss_MUDLINE= MUD(MLnumber)%minlosspa_MUDLINE/6895 !(psi)
- elseif (CV_MUDLINE(MLnumber)/=0) then
- MUD(MLnumber)%minlosspa_MUDLINE=1000*MUD(MLnumber)%Mud_SG*((11.7*MUD(MLnumber)%Q*6.30902e-5*3600)/(CV_MUDLINE(MLnumber)))**2 !(pa)
- MUD(MLnumber)%minloss_MUDLINE= MUD(MLnumber)%minlosspa_MUDLINE/6895 !(psi)
- else
- MUD(MLnumber)%minlosspa_MUDLINE=NOTE_MUDLINE(MLnumber)*1e5 !(pa)
- MUD(MLnumber)%minloss_MUDLINE= MUD(MLnumber)%minlosspa_MUDLINE/6895 !(psi)
- endif
-
-
- !==========================STATIC & KINETIC LOSS=============================
-
- String_Height= 50.*0.3048 !<<<<<<<<<<<<<<< (foot) to (meter). az khanom tarmigh
- MUD(1)%static_loss=(String_Height- Pumps_Height)*0.0 !(MLnumber=1,,PumpsToString)
- MUD(2)%static_loss=(String_Height- STpipeGauge_Height)*MUD(2)%Mud_SG*wdens*gravity/6895 ! (psi) (MLnumber=2,,STGaugeToString)
- MUD(3)%static_loss=0. !(MLnumber=1,,WellToPits)
- MUD(4)%static_loss=(ChokeManifold_Height- WellChokeExit_Height)*MUD(4)%Mud_SG*wdens*gravity/6895 !(MLnumber=4,,WellToChokeManifold)
-
-
-
- ! RAM(RNUMBER)%kinetic_loss1=MUD(MLnumber)%Mud_SG*MUD(MLnumber)%Mud_Density*(RAM(RNUMBER)%Q*6.30902e-5/((1/4.)*pi*(.72*0.254e-1)**2))**2/(2*6895) !(psi)
-
-
-
- !============================TOTAL LOSS=======================================
- MUD(MLnumber)%total_loss= MUD(MLnumber)%fricloss+ MUD(MLnumber)%minloss_MUDLINE+ MUD(MLnumber)%static_loss!+ RAM(RNUMBER)%kinetic_loss1 !(psi)
-
-
- END
-
-
-
-
-
-
- SUBROUTINE DEALLOCATE_ARRAYS_MudSystem()
- USE MudSystemVARIABLES
- implicit none
- !===========================================================================
- ! RAMLINE MINOR LOSSES INPUT
- !===========================================================================
- if (allocated(MudMinors)) DEALLOCATE (MudMinors)
- !===========================================================================
- ! RAMLINE PIPNING LOSSES INPUT
- !===========================================================================
- if (allocated(MINORDIAMETER_MUDLINE)) DEALLOCATE (MINORDIAMETER_MUDLINE)
- if (allocated(AREAMINOR_MUDLINE)) DEALLOCATE (AREAMINOR_MUDLINE)
- if (allocated(LF_MUDLINE)) DEALLOCATE (LF_MUDLINE)
- if (allocated(CV_MUDLINE)) DEALLOCATE (CV_MUDLINE)
- if (allocated(NOTE_MUDLINE)) DEALLOCATE (NOTE_MUDLINE)
-
- !===========================================================================
- ! ANNULAR MINOR LOSSES INPUT
- !===========================================================================
- if (allocated(PIPINGS_MUDLINE)) DEALLOCATE (PIPINGS_MUDLINE)
- !===========================================================================
- ! ANNULAR PIPNING LOSSES INPUT
- !===========================================================================
- if (allocated(DIAM_MUDLINE_INCH)) DEALLOCATE (DIAM_MUDLINE_INCH)
- if (allocated(AREA_MUDLINE)) DEALLOCATE (AREA_MUDLINE)
- if (allocated(LENGT_MUDLINE)) DEALLOCATE (LENGT_MUDLINE)
- if (allocated(ROUGHNESS_MUDLINE)) DEALLOCATE (ROUGHNESS_MUDLINE)
- if (allocated(RELROUGH_MUDLINE)) DEALLOCATE (RELROUGH_MUDLINE)
-
- END
-
-
-
-
-
-
- subroutine AddDynamicArray(array, value)
- implicit none
- REAL, allocatable, intent(inout) :: array(:)
- REAL, intent(in) :: value
- REAL, allocatable :: tempArr(:)
- integer :: i, isize
-
- !if(allocated(array)) then
- ! isize = size(array)
- ! allocate(tempArr(isize+1))
- ! do i=1,isize
- ! tempArr(i) = array(i)
- ! end do
- ! tempArr(isize+1) = value
- ! deallocate(array)
- ! call move_alloc(tempArr, array)
- !else
- ! allocate(array(1))
- ! array(1) = value
- !end if
-
- end subroutine
|