|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371 |
- # 1 "/home/admin/SimulationCore2/Equipments/MudSystem/Trip_Out_andPump.f90"
- subroutine TripOut_and_Pump ! is called in subroutine CirculationCodeSelect
-
- Use GeoElements_FluidModule
- USE CMudPropertiesVariables
- USE MudSystemVARIABLES
- use SimulationVariables !@@@
- use SimulationVariables
- USE CHOKEVARIABLES
- !use ConfigurationVariables !@
- !use CDataDisplayConsole
- !!@ use ConfigurationVariables , StandPipePressureDataDisplay=>StandPipePressure
- !use CManifolds
- use SimulationVariables !@
- USE CHOKEVARIABLES
- !use ConfigurationVariables !@
- !use CChokeManifoldVariables
- use SimulationVariables
- !use CTanks
- !@use ConfigurationVariables, TripTankVolume2 => data%Equipments%DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
- USE sROP_Other_Variables
- USE sROP_Variables
- use KickVARIABLESModule
- Use CShoeVariables
- use CError
-
- implicit none
-
- integer i,ii,AddLocation, iloc_edited, iloc_changedTo2
- Real(8) ExcessMudVolume_Remained,SavedDensityForOp
-
- !===========================================================WELL============================================================
- !===========================================================WELL============================================================
-
- data%State%MudSystem%StringFlowRate= data%State%MUD(2)%Q
- data%State%MudSystem%AnnulusFlowRate= data%State%MUD(2)%Q
- !write(*,*) 'data%State%MUD(2)%Q=====' , data%State%MUD(2)%Q
-
-
- write(*,*) 'Trip Out'
-
- ! write(*,*) 'check point 1=='
- !
- !
- !
- ! do imud=1, Ann_MudDischarged_Volume%Length()
- ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
- ! enddo
- !
- ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
- !
- !
- !write(*,*) '==check point 1'
-
- !========================Horizontal PIPE ENTRANCE=================
-
- if (ABS(data%State%MudSystem%SuctionDensity_Old - data%State%MudSystem%Suction_Density_MudSystem) >= data%State%MudSystem%DensityMixTol) then ! new mud is pumped
-
- call data%State%MudSystem%Hz_Density%AddToFirst (data%State%MudSystem%Suction_Density_MudSystem)
- call data%State%MudSystem%Hz_MudDischarged_Volume%AddToFirst (0.0d0)
- call data%State%MudSystem%Hz_Mud_Forehead_X%AddToFirst (data%State%MudSystem%Xstart_PipeSection(1))
- call data%State%MudSystem%Hz_Mud_Forehead_section%AddToFirst (1)
- call data%State%MudSystem%Hz_Mud_Backhead_X%AddToFirst (data%State%MudSystem%Xstart_PipeSection(1))
- call data%State%MudSystem%Hz_Mud_Backhead_section%AddToFirst (1)
- call data%State%MudSystem%Hz_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call data%State%MudSystem%Hz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call data%State%MudSystem%Hz_MudOrKick%AddToFirst (0)
-
- data%State%MudSystem%SuctionDensity_Old= data%State%MudSystem%Suction_Density_MudSystem
- endif
-
- !========================Horizontal PIPE STRING=================
-
- data%State%MudSystem%Hz_MudDischarged_Volume%Array(1)= data%State%MudSystem%Hz_MudDischarged_Volume%Array(1)+ ((data%State%MudSystem%StringFlowRate/60.0d0)*data%State%MudSystem%DeltaT_Mudline) !(gal)
-
-
- data%State%MudSystem%total_add = data%State%MudSystem%total_add + ((data%State%MudSystem%StringFlowRate/60.0d0)*data%State%MudSystem%DeltaT_Mudline)
-
-
- if (data%Equipments%ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
- data%State%MudSystem%total_add= 0.
- endif
-
- !write(*,*) ' total decrease(add to HZ)=' , total_add
- !write(*,*) ' add to HZ=' , ((data%State%MudSystem%StringFlowRate/60.0d0)*DeltaT_Mudline)
-
-
-
- imud=0
- do while (imud < data%State%MudSystem%Hz_Mud_Forehead_X%Length())
- imud = imud + 1
-
- if (imud> 1) then
- data%State%MudSystem%Hz_Mud_Backhead_X%Array(imud)= data%State%MudSystem%Hz_Mud_Forehead_X%Array(imud-1)
- data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud)= data%State%MudSystem%Hz_Mud_Forehead_section%Array(imud-1)
- endif
-
-
- data%State%MudSystem%DirectionCoef= (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud))-data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud))) &
- / ABS(data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud))-data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud)))
- ! +1 for string , -1 for annulus
-
-
- data%State%MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%DirectionCoef* (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud))- data%State%MudSystem%Hz_Mud_Backhead_X%Array(imud))* &
- data%State%MudSystem%Area_PipeSectionFt(data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud)) !(ft^3)
- data%State%MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
-
-
- if ( data%State%MudSystem%Hz_MudDischarged_Volume%Array(imud) <= data%State%MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)) then
- data%State%MudSystem%Hz_Mud_Forehead_section%Array(imud)= data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud)
- data%State%MudSystem%Hz_Mud_Forehead_X%Array(imud)= data%State%MudSystem%Hz_Mud_Backhead_X%Array(imud)+ data%State%MudSystem%DirectionCoef*(data%State%MudSystem%Hz_MudDischarged_Volume%Array(imud)/7.48051948d0)/data%State%MudSystem%Area_PipeSectionFt(data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud))
-
- else
-
-
- data%State%MudSystem%isection= data%State%MudSystem%Hz_Mud_Backhead_section%Array(imud)+1
- data%State%MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%Hz_MudDischarged_Volume%Array(imud)- data%State%MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)
-
- do
- if (data%State%MudSystem%isection > 1) then ! (horizontal pipe exit)
- data%State%MudSystem%Hz_MudDischarged_Volume%Array(imud)= data%State%MudSystem%Hz_MudDischarged_Volume%Array(imud)- data%State%MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)
- data%State%MudSystem%Hz_Mud_Forehead_X%Array(imud)= data%State%MudSystem%Xend_PipeSection(1)
- data%State%MudSystem%Hz_Mud_Forehead_section%Array(imud)= 1
-
- if (data%State%MudSystem%Hz_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
- call RemoveHzMudArrays(imud)
- endif
-
- exit
- endif
-
- data%State%MudSystem%xx= data%State%MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)/ data%State%MudSystem%PipeSection_VolumeCapacity(data%State%MudSystem%isection) !(gal)
-
- if (data%State%MudSystem%xx<= 1.0) then
- data%State%MudSystem%Hz_Mud_Forehead_section%Array(imud)= data%State%MudSystem%isection
- data%State%MudSystem%Hz_Mud_Forehead_X%Array(imud)= (data%State%MudSystem%xx * (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%isection)- data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%isection)))+ data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%isection)
- exit
- else
- data%State%MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)- data%State%MudSystem%PipeSection_VolumeCapacity(data%State%MudSystem%isection)
- data%State%MudSystem%isection= data%State%MudSystem%isection+ 1
-
- endif
-
- enddo
-
- endif
-
- enddo
- !========================Horizontal PIPE END=================
-
-
-
- !========================Utube1 Air Element Removing=================
-
- !if (UtubeMode1Activated== .true.) then ! StringUpdate == .true.
- !
- ! StringDensity_Old= data%State%MudSystem%St_Density%Array(2)
- !
- ! UtubeMode1Activated= .false.
- !endif
-
- !========================Utube1 Air Element Removing=================
-
-
- !========================Utube2 Removing from Annulus=================
-
- if (data%State%MudSystem%UtubeMode2Activated== .true.) then ! StringUpdate == .true.
- data%State%MudSystem%TotalAddedVolume=0.
-
- if (data%State%MudSystem%Ann_MudOrKick%Last() == 104) then !movaghati. albate age merge anjam shode bashe moshkeli nist
- call RemoveAnnulusMudArrays(data%State%MudSystem%Ann_MudOrKick%Length())
- endif
-
- data%State%MudSystem%UtubeMode2Activated= .false.
- endif
-
-
- !========================Utube2 Removing from Annulus End=================
-
- !========================New Pipe Filling=================
-
- if (data%State%MudSystem%AddedElementsToString > 0) then ! StringUpdate == .true.
-
- !NoPipeAdded= F_StringIntervalCounts - F_StringIntervalCountsOld
-
-
- data%State%MudSystem%NewPipeFilling=0
-
- IF (data%State%MudSystem%St_MudOrKick%First() == 104) then
- data%State%MudSystem%St_MudDischarged_Volume%Array(1) = data%State%MudSystem%St_MudDischarged_Volume%Array(1) + sum(data%State%MudSystem%PipeSection_VolumeCapacity(2:1+data%State%MudSystem%AddedElementsToString)) ! new pipe is filled by air
- else
- call data%State%MudSystem%St_Density%AddToFirst (0.d0)
- call data%State%MudSystem%St_MudDischarged_Volume%AddToFirst (sum(data%State%MudSystem%PipeSection_VolumeCapacity(2:1+data%State%MudSystem%AddedElementsToString)))
- call data%State%MudSystem%St_Mud_Forehead_X%AddToFirst (data%State%MudSystem%Xstart_PipeSection(2))
- call data%State%MudSystem%St_Mud_Forehead_section%AddToFirst (2)
- call data%State%MudSystem%St_Mud_Backhead_X%AddToFirst (data%State%MudSystem%Xstart_PipeSection(2))
- call data%State%MudSystem%St_Mud_Backhead_section%AddToFirst (2)
- call data%State%MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.d0)
- call data%State%MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.d0)
- call data%State%MudSystem%St_MudOrKick%AddToFirst (104)
- endif
-
- endif
-
- !F_StringIntervalCountsOld= F_StringIntervalCounts
-
-
-
- if (data%State%MudSystem%NewPipeFilling == 0) then ! 2= is the first element of string (1= is for Hz pipe)
-
-
- data%State%MudSystem%LackageMudVolume= data%State%MudSystem%St_MudDischarged_Volume%Array(1) ! = Air element
-
-
- !write(*,*) 'LackageMudVolume=' , LackageMudVolume
-
-
-
- if (ABS(data%State%MudSystem%St_Density%Array(2) - data%State%MudSystem%Hz_Density%Last()) >= data%State%MudSystem%DensityMixTol) then ! new mud is pumped
- call data%State%MudSystem%St_Density%AddTo (2,data%State%MudSystem%Hz_Density%Last())
- call data%State%MudSystem%St_MudDischarged_Volume%AddTo (2,0.d0)
- call data%State%MudSystem%St_Mud_Forehead_X%AddTo (2,data%State%MudSystem%Xstart_PipeSection(2))
- call data%State%MudSystem%St_Mud_Forehead_section%AddTo (2 , 2)
- call data%State%MudSystem%St_Mud_Backhead_X%AddTo (2,data%State%MudSystem%Xstart_PipeSection(2))
- call data%State%MudSystem%St_Mud_Backhead_section%AddTo (2 ,2)
- call data%State%MudSystem%St_RemainedVolume_in_LastSection%AddTo (2,0.d0)
- call data%State%MudSystem%St_EmptyVolume_inBackheadLocation%AddTo (2,0.d0)
- call data%State%MudSystem%St_MudOrKick%AddTo (2,0)
-
- !StringDensity_Old= Hz_Density%Last()
- endif
-
-
- data%State%MudSystem%St_MudDischarged_Volume%Array(2)= data%State%MudSystem%St_MudDischarged_Volume%Array(2)+ min( ((data%State%MudSystem%StringFlowRate/60.0d0)*data%State%MudSystem%DeltaT_Mudline), data%State%MudSystem%LackageMudVolume) !(gal)
-
- data%State%MudSystem%St_MudDischarged_Volume%Array(1)= data%State%MudSystem%St_MudDischarged_Volume%Array(1)- min( ((data%State%MudSystem%StringFlowRate/60.0d0)*data%State%MudSystem%DeltaT_Mudline), data%State%MudSystem%LackageMudVolume) ! air(gal)
-
- !LackageMudVolumeAfterFilling= sum(PipeSection_VolumeCapacity(2:F_StringIntervalCounts)) - sum(St_MudDischarged_Volume%Array(:))
-
- data%State%MudSystem%LackageMudVolumeAfterFilling= data%State%MudSystem%St_MudDischarged_Volume%Array(1) ! last time it should be zero
-
-
-
- if (data%State%MudSystem%LackageMudVolumeAfterFilling == 0.) then
- data%State%MudSystem%NewPipeFilling= 1
- call RemoveStringMudArrays(1)
- data%State%MudSystem%St_Mud_Backhead_X%Array(1) = data%State%MudSystem%Xstart_PipeSection(2)
- data%State%MudSystem%St_Mud_Backhead_section%Array(1) = 2
- endif
-
- endif
-
- !========================New Pipe Filling End=================
-
-
- if (data%State%MudSystem%NewPipeFilling == 0) then
- data%State%MudSystem%StringFlowRate= 0.
- data%State%MudSystem%AnnulusFlowRate= 0.
- endif
-
- data%State%MudSystem%StringFlowRateFinal= data%State%MudSystem%StringFlowRate
- data%State%MudSystem%AnnulusFlowRateFinal= data%State%MudSystem%AnnulusFlowRate
-
-
- !========================STRING ENTRANCE=================
- if (data%State%MudSystem%StringFlowRateFinal > 0.0 .and. ABS(data%State%MudSystem%St_Density%First() - data%State%MudSystem%Hz_Density%Last()) >= data%State%MudSystem%DensityMixTol) then ! new mud is pumped
- !if (ABS(StringDensity_Old - Hz_Density%Last()) >= DensityMixTol) then ! new mud is pumped
- call data%State%MudSystem%St_Density%AddToFirst (data%State%MudSystem%Hz_Density%Last())
- call data%State%MudSystem%St_MudDischarged_Volume%AddToFirst (0.0d0)
- call data%State%MudSystem%St_Mud_Forehead_X%AddToFirst (data%State%MudSystem%Xstart_PipeSection(2))
- call data%State%MudSystem%St_Mud_Forehead_section%AddToFirst (2)
- call data%State%MudSystem%St_Mud_Backhead_X%AddToFirst (data%State%MudSystem%Xstart_PipeSection(2))
- call data%State%MudSystem%St_Mud_Backhead_section%AddToFirst (2)
- call data%State%MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call data%State%MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call data%State%MudSystem%St_MudOrKick%AddToFirst (0)
-
- !StringDensity_Old= Hz_Density%Last()
- endif
- data%State%MudSystem%St_MudDischarged_Volume%Array(1)= data%State%MudSystem%St_MudDischarged_Volume%Array(1)+ ((data%State%MudSystem%StringFlowRate/60.0d0)*data%State%MudSystem%DeltaT_Mudline) !(gal)
-
- !=============== save String Mud data===========
- data%State%MudSystem%StMudVolumeSum= 0.d0
- !St_MudSaved_Density= 0.d0
- data%State%MudSystem%St_Saved_MudDischarged_Volume= 0.d0
- !Saved_St_MudOrKick= 0
- !Ann_to_Choke_2mud= .false.
-
- do imud=1, data%State%MudSystem%St_MudDischarged_Volume%Length()
- data%State%MudSystem%StMudVolumeSum= data%State%MudSystem%StMudVolumeSum + data%State%MudSystem%St_MudDischarged_Volume%Array(imud)
- if ( data%State%MudSystem%StMudVolumeSum > sum(data%State%MudSystem%PipeSection_VolumeCapacity(2:data%State%F_Counts%StringIntervalCounts)) ) then
- !IF (St_MudOrKick%Array(imud) == 0) THEN
- data%State%MudSystem%St_MudSaved_Density = data%State%MudSystem%St_Density%Array(imud)
- data%State%MudSystem%St_Saved_MudDischarged_Volume = data%State%MudSystem%StMudVolumeSum - sum(data%State%MudSystem%PipeSection_VolumeCapacity(2:data%State%F_Counts%StringIntervalCounts))
- !ELSEIF (St_MudOrKick%Array(imud) > 0 .AND. St_MudOrKick%Array(imud) <100) THEN ! 104= AIR
- ! St_Kick_Saved_Volume = StMudVolumeSum - sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- ! Saved_St_MudOrKick= St_MudOrKick%Array (imud)
- ! St_KickSaved_Density= data%State%MudSystem%St_Density%Array(imud)
- !END IF
-
- do ii= imud + 1, data%State%MudSystem%St_MudDischarged_Volume%Length()
- !IF (St_MudOrKick%Array(ii) == 0) THEN
- data%State%MudSystem%St_MudSaved_Density = ((data%State%MudSystem%St_MudSaved_Density * data%State%MudSystem%St_Saved_MudDischarged_Volume) + (data%State%MudSystem%St_Density%Array(ii) * data%State%MudSystem%St_MudDischarged_Volume%Array(ii))) / (data%State%MudSystem%St_Saved_MudDischarged_Volume + data%State%MudSystem%St_MudDischarged_Volume%Array(ii))
- data%State%MudSystem%St_Saved_MudDischarged_Volume = data%State%MudSystem%St_Saved_MudDischarged_Volume + data%State%MudSystem%St_MudDischarged_Volume%Array(ii)
-
- !ELSEIF (St_MudOrKick%Array(imud) > 0 .AND. St_MudOrKick%Array(imud) <100) THEN ! 104= AIR
- ! St_Kick_Saved_Volume = St_Kick_Saved_Volume + St_MudDischarged_Volume%Array(ii)
- ! Saved_St_MudOrKick= St_MudOrKick%Array (ii)
- ! St_KickSaved_Density= data%State%MudSystem%St_Density%Array(ii)
- !END IF
- enddo
-
-
- !WRITE (*,*) 'St_Saved_Mud_Volume, St_Kick_Saved_Volume', St_Saved_MudDischarged_Volume, St_Kick_Saved_Volume
- exit ! exits do
-
- endif
-
- enddo
- data%State%MudSystem%St_Saved_MudDischarged_Volume_Final= data%State%MudSystem%St_Saved_MudDischarged_Volume
-
- IF (data%State%MudSystem%WellHeadIsOpen) data%State%MudSystem%MudVolume_InjectedToBH = data%State%MudSystem%St_Saved_MudDischarged_Volume_Final
-
- !======================================================================
-
-
- !========================STRING=================
-
- imud=0
- do while (imud < data%State%MudSystem%St_Mud_Forehead_X%Length())
- imud = imud + 1
-
- if (imud> 1) then
- data%State%MudSystem%St_Mud_Backhead_X%Array(imud)= data%State%MudSystem%St_Mud_Forehead_X%Array(imud-1)
- data%State%MudSystem%St_Mud_Backhead_section%Array(imud)= data%State%MudSystem%St_Mud_Forehead_section%Array(imud-1)
- endif
-
- data%State%MudSystem%DirectionCoef= (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%St_Mud_Backhead_section%Array(imud))-data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%St_Mud_Backhead_section%Array(imud))) &
- / ABS(data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%St_Mud_Backhead_section%Array(imud))-data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%St_Mud_Backhead_section%Array(imud)))
- ! +1 for string , -1 for annulus
-
-
- data%State%MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%DirectionCoef* (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%St_Mud_Backhead_section%Array(imud))- data%State%MudSystem%St_Mud_Backhead_X%Array(imud))* &
- data%State%MudSystem%Area_PipeSectionFt(data%State%MudSystem%St_Mud_Backhead_section%Array(imud)) !(ft^3)
- data%State%MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
-
- if ( data%State%MudSystem%St_MudDischarged_Volume%Array(imud) <= data%State%MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)) then
- data%State%MudSystem%St_Mud_Forehead_section%Array(imud)= data%State%MudSystem%St_Mud_Backhead_section%Array(imud)
- data%State%MudSystem%St_Mud_Forehead_X%Array(imud)= data%State%MudSystem%St_Mud_Backhead_X%Array(imud)+ data%State%MudSystem%DirectionCoef*(data%State%MudSystem%St_MudDischarged_Volume%Array(imud)/7.48051948d0)/data%State%MudSystem%Area_PipeSectionFt(data%State%MudSystem%St_Mud_Backhead_section%Array(imud))
- ! 7.48 is for gal to ft^3
-
- else
-
- data%State%MudSystem%isection= data%State%MudSystem%St_Mud_Backhead_section%Array(imud)+1
- data%State%MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%St_MudDischarged_Volume%Array(imud)- data%State%MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)
-
- do
- if (data%State%MudSystem%isection > data%State%F_Counts%StringIntervalCounts) then ! last pipe section(string exit)
- data%State%MudSystem%St_MudDischarged_Volume%Array(imud)= data%State%MudSystem%St_MudDischarged_Volume%Array(imud)- data%State%MudSystem%St_RemainedVolume_in_LastSection%Array(imud)
- data%State%MudSystem%St_Mud_Forehead_X%Array(imud)= data%State%MudSystem%Xend_PipeSection(data%State%F_Counts%StringIntervalCounts)
- data%State%MudSystem%St_Mud_Forehead_section%Array(imud)= data%State%F_Counts%StringIntervalCounts
-
- if (data%State%MudSystem%St_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
- call RemoveStringMudArrays(imud)
- endif
-
- exit
- endif
-
- data%State%MudSystem%xx= data%State%MudSystem%St_RemainedVolume_in_LastSection%Array(imud)/ data%State%MudSystem%PipeSection_VolumeCapacity(data%State%MudSystem%isection) !(gal)
-
- if (data%State%MudSystem%xx<= 1.0) then
- data%State%MudSystem%St_Mud_Forehead_section%Array(imud)= data%State%MudSystem%isection
- data%State%MudSystem%St_Mud_Forehead_X%Array(imud)= (data%State%MudSystem%xx * (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%isection)- data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%isection)))+ data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%isection)
- exit
- else
- data%State%MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%St_RemainedVolume_in_LastSection%Array(imud)- data%State%MudSystem%PipeSection_VolumeCapacity(data%State%MudSystem%isection)
- data%State%MudSystem%isection= data%State%MudSystem%isection+ 1
-
-
- endif
-
- enddo
-
- endif
-
- enddo
- !========================STRING END=================
-
- !write(*,*) ' a before=='
- !
- ! do imud=1, Op_MudDischarged_Volume%Length()
- ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
- ! enddo
- !
- ! do imud=1, Ann_MudDischarged_Volume%Length()
- ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
- ! enddo
- !
- ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
- !
- !
- !write(*,*) '==== a before'
-
- iloc_changedTo2 = 0
-
- IF (data%State%MudSystem%Op_MudOrKick%Last() /= 0 .and. data%State%MudSystem%Op_MudOrKick%Last()==data%State%MudSystem%Ann_MudOrKick%First()) then
- data%State%MudSystem%iLoc=2 ! it may be 1,2,3 or more, all of them are kick
- iloc_changedTo2= 1
- endif
-
-
-
- iloc_edited= 0
- !write(*,*) sum(Op_MudDischarged_Volume%Array(:)) , ((data%State%MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline) , Ann_MudDischarged_Volume%First() , sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
- if (data%State%MudSystem%iLoc==2 .and. sum(data%State%MudSystem%Op_MudDischarged_Volume%Array(:))+((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline)+data%State%MudSystem%Ann_MudDischarged_Volume%First() < sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts)) ) then
- data%State%MudSystem%iLoc = 1
- iloc_edited = 1
- !write(*,*) 'hellooooooo'
- endif
-
-
- !write(*,*) 'ann-cap:' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1 :F_StringIntervalCounts+F_AnnulusIntervalCounts) )
-
-
- !write(*,*) 'iloc====' , iloc
- !MudVolume_InjectedToBH
-
-
- !=============================Add PumpFlowRate to Bottom Hole ==============================
- !if ( data%State%MudSystem%AnnulusFlowRate>0.0 ) then
- if ( data%State%MudSystem%MudVolume_InjectedToBH > 0.0 ) then
-
-
- if (KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the
- AddLocation= data%State%MudSystem%Op_Density%Length()-data%State%MudSystem%iLoc+1+1 ! well, thus pumped mud should be placed above the kick
- else
- AddLocation= data%State%MudSystem%Op_Density%Length()+1
- endif
- !write(*,*) 'AddLocation====' , AddLocation
- if ( AddLocation== 0) CALL ErrorStop ('AddLocation=0')
-
-
- if ( ABS(data%State%MudSystem%St_Density%Last() - data%State%MudSystem%Op_Density%Array(AddLocation-1)) >= data%State%MudSystem%DensityMixTol ) then
- !write(*,*) 'new pocket**'
- !write(*,*) 'data%State%MudSystem%St_Density%Last()=' , data%State%MudSystem%St_Density%Last()
- !write(*,*) 'Op_Density%Array(AddLocation-1)=' , Op_Density%Array(AddLocation-1)
-
-
- call data%State%MudSystem%Op_Density% AddTo (AddLocation,data%State%MudSystem%St_Density%Last())
- !call Op_MudDischarged_Volume%AddTo (AddLocation,((data%State%MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline))
- call data%State%MudSystem%Op_MudDischarged_Volume%AddTo (AddLocation,data%State%MudSystem%MudVolume_InjectedToBH)
- call data%State%MudSystem%Op_Mud_Forehead_X%AddTo (AddLocation,data%State%MudSystem%Xstart_OpSection(1))
- call data%State%MudSystem%Op_Mud_Forehead_section%AddTo (AddLocation,1)
- call data%State%MudSystem%Op_Mud_Backhead_X%AddTo (AddLocation,data%State%MudSystem%Xstart_OpSection(1))
- call data%State%MudSystem%Op_Mud_Backhead_section%AddTo (AddLocation,1)
- call data%State%MudSystem%Op_RemainedVolume_in_LastSection%AddTo (AddLocation,0.0d0)
- call data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%AddTo (AddLocation,0.0d0)
- call data%State%MudSystem%Op_MudOrKick%AddTo (AddLocation,0)
- else
- !write(*,*) 'merge**'
- !write(*,*) 'density before=' , Op_Density%Array(AddLocation-1)
- !write(*,*) 'data%State%MudSystem%St_Density%Last() for mix=' , data%State%MudSystem%St_Density%Last()
-
- !Op_Density%Array(AddLocation-1)= (Op_Density%Array(AddLocation-1)*Op_MudDischarged_Volume%Array(AddLocation-1)+data%State%MudSystem%St_Density%Last()*((data%State%MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline))/(Op_MudDischarged_Volume%Array(AddLocation-1)+((data%State%MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline))
- !Op_MudDischarged_Volume%Array(AddLocation-1)= Op_MudDischarged_Volume%Array(AddLocation-1) + ((data%State%MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline)
-
- data%State%MudSystem%Op_Density%Array(AddLocation-1)= (data%State%MudSystem%Op_Density%Array(AddLocation-1)*data%State%MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1)+data%State%MudSystem%St_Density%Last()*data%State%MudSystem%MudVolume_InjectedToBH)/(data%State%MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1)+data%State%MudSystem%MudVolume_InjectedToBH)
- data%State%MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1)= data%State%MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1) + data%State%MudSystem%MudVolume_InjectedToBH
- !write(*,*) 'density after=' , Op_Density%Array(AddLocation-1)
-
- endif
-
- endif
- !=======================Add PumpFlowRate to Bottom Hole- End ==============================
-
- !write(*,*) 'pump added-before add to ann=='
- !
- ! do imud=1, Op_MudDischarged_Volume%Length()
- ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
- ! enddo
- !
- ! do imud=1, Ann_MudDischarged_Volume%Length()
- ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
- ! enddo
- !
- ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
- !
- !
- !
- !write(*,*) 'pump added====before add to ann'
-
-
- !=============== save OP Mud data to transfer to the annulus enterance due to tripin or kick
- data%State%MudSystem%OpMudVolumeSum= 0.d0
- !Op_MudSaved_Density= 0.d0
- !Op_KickSaved_Density= 0.d0
- data%State%MudSystem%Op_Saved_MudDischarged_Volume= 0.d0
- data%State%MudSystem%Op_Kick_Saved_Volume= 0.d0
- data%State%MudSystem%Saved_Op_MudOrKick= 0
- data%State%MudSystem%Op_NeededVolume_ToFill= 0.d0
-
-
-
-
- do imud=1, data%State%MudSystem%Op_MudDischarged_Volume%Length()
-
- data%State%MudSystem%OpMudVolumeSum= data%State%MudSystem%OpMudVolumeSum + data%State%MudSystem%Op_MudDischarged_Volume%Array(imud)
-
- if ( data%State%MudSystem%OpMudVolumeSum > sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts)) ) then !1st mode
-
- IF (data%State%MudSystem%Op_MudOrKick%Array(imud) == 0) THEN
- data%State%MudSystem%Op_MudSaved_Density = data%State%MudSystem%Op_Density%Array(imud)
- data%State%MudSystem%Op_Saved_MudDischarged_Volume = data%State%MudSystem%OpMudVolumeSum - sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts))
- ELSE
-
- data%State%MudSystem%Op_Kick_Saved_Volume = data%State%MudSystem%OpMudVolumeSum - sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts))
- data%State%MudSystem%Saved_Op_MudOrKick= data%State%MudSystem%Op_MudOrKick%Array (imud)
- data%State%MudSystem%Op_KickSaved_Density= data%State%MudSystem%Op_Density%Array(imud)
- data%State%MudSystem%iLoc= 2
- iloc_changedTo2= 2
- END IF
-
- do ii= imud + 1, data%State%MudSystem%Op_MudDischarged_Volume%Length()
- IF (data%State%MudSystem%Op_MudOrKick%Array(ii) == 0) THEN
- data%State%MudSystem%Op_MudSaved_Density = ((data%State%MudSystem%Op_MudSaved_Density * data%State%MudSystem%Op_Saved_MudDischarged_Volume) + (data%State%MudSystem%Op_Density%Array(ii) * data%State%MudSystem%Op_MudDischarged_Volume%Array(ii))) / (data%State%MudSystem%Op_Saved_MudDischarged_Volume + data%State%MudSystem%Op_MudDischarged_Volume%Array(ii))
- data%State%MudSystem%Op_Saved_MudDischarged_Volume = data%State%MudSystem%Op_Saved_MudDischarged_Volume + data%State%MudSystem%Op_MudDischarged_Volume%Array(ii)
- ELSE
- data%State%MudSystem%Op_Kick_Saved_Volume = data%State%MudSystem%Op_Kick_Saved_Volume + data%State%MudSystem%Op_MudDischarged_Volume%Array(ii)
- data%State%MudSystem%Saved_Op_MudOrKick= data%State%MudSystem%Op_MudOrKick%Array (ii)
- data%State%MudSystem%Op_KickSaved_Density= data%State%MudSystem%Op_Density%Array(ii)
- data%State%MudSystem%iLoc= 2
- iloc_changedTo2= 3
- END IF
- enddo
-
- exit ! exits do
-
- endif
-
- enddo
-
- if ( sum(data%State%MudSystem%Op_MudDischarged_Volume%Array(:)) < sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts)) ) then !2nd & 3rd mode
-
- data%State%MudSystem%Op_NeededVolume_ToFill= sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts)) - sum(data%State%MudSystem%Op_MudDischarged_Volume%Array(:))
- endif
-
-
- !
- !write(*,*) 'Op_NeededVolume_ToFill=' , Op_NeededVolume_ToFill
- !write(*,*) 'Op_Saved_MudDischarged_Volume=' , Op_Saved_MudDischarged_Volume
- !write(*,*) 'Op_Kick_Saved_Volume=' , Op_Kick_Saved_Volume
- !
- !write(*,*) 'op cap=' , sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
- !write(*,*) ' op sum mud=' , sum(Op_MudDischarged_Volume%Array(:))
-
-
-
-
-
- !======================================================================
-
-
-
-
- !========================Tripping Out- 1st & 3rd Mode====================
-
-
-
- if ( (data%State%MudSystem%Op_Kick_Saved_Volume > 0.0 .or. data%State%MudSystem%Op_Saved_MudDischarged_Volume> 0.0) .or. & ! 1st Mode-Pump flow is more than trip out so fluid Level in Annulus Increases
- (data%State%MudSystem%Op_NeededVolume_ToFill < ABS(data%State%MudSystem%DeltaVolumeAnnulusCapacity)) ) then !3rd Mode-fluid Level in Annulus Increases
-
-
- !if ( Op_Kick_Saved_Volume > 0.0 .or. Op_Saved_MudDischarged_Volume> 0.0 ) write(*,*) 'trip out 1st mode'
-
- if ( data%State%MudSystem%Op_NeededVolume_ToFill > 0.0 .and. data%State%MudSystem%Op_NeededVolume_ToFill < ABS(data%State%MudSystem%DeltaVolumeAnnulusCapacity) ) then
- ! write(*,*) 'trip out 3rd mode'
-
- data%State%MudSystem%NewVolume= 0.d0 ! for condition iloc=1
-
- SavedDensityForOp= data%State%MudSystem%Ann_Density%Array(1)
-
- ExcessMudVolume_Remained= data%State%MudSystem%Op_NeededVolume_ToFill
-
-
- imud=1
-
- Do
-
- if(data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud) < ExcessMudVolume_Remained) then
- ExcessMudVolume_Remained= ExcessMudVolume_Remained- data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)
- call data%State%MudSystem%Ann_MudDischarged_Volume%Remove (imud)
- call data%State%MudSystem%Ann_Mud_Backhead_X%Remove (imud)
- call data%State%MudSystem%Ann_Mud_Backhead_section%Remove (imud)
- call data%State%MudSystem%Ann_Mud_Forehead_X%Remove (imud)
- call data%State%MudSystem%Ann_Mud_Forehead_section%Remove (imud)
- call data%State%MudSystem%Ann_Density%Remove (imud)
- call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Remove (imud)
- call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Remove (imud)
- call data%State%MudSystem%Ann_MudOrKick%Remove (imud)
-
- elseif(data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud) > ExcessMudVolume_Remained) then
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)- ExcessMudVolume_Remained
- exit
-
- else !(Ann_MudDischarged_Volume%Array(imud) == ExcessMudVolume_Remained)
- call data%State%MudSystem%Ann_MudDischarged_Volume%Remove (imud)
- call data%State%MudSystem%Ann_Mud_Backhead_X%Remove (imud)
- call data%State%MudSystem%Ann_Mud_Backhead_section%Remove (imud)
- call data%State%MudSystem%Ann_Mud_Forehead_X%Remove (imud)
- call data%State%MudSystem%Ann_Mud_Forehead_section%Remove (imud)
- call data%State%MudSystem%Ann_Density%Remove (imud)
- call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Remove (imud)
- call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Remove (imud)
- call data%State%MudSystem%Ann_MudOrKick%Remove (imud)
- exit
-
- endif
-
- enddo
-
-
- !write(*,*) 'Op_NeededVolume_ToFill=' ,Op_NeededVolume_ToFill
- !write(*,*) 'ABS(DeltaVolumeAnnulusCapacity)=' ,ABS(DeltaVolumeAnnulusCapacity)
- !write(*,*) 'Op_MudOrKick%Last()=' ,Op_MudOrKick%Last()
- !write(*,*) 'iloc=' ,iloc
- !write(*,*) 'iloc_edited=' ,iloc_edited
-
-
- endif
-
-
- ! (data%State%MudSystem%AnnulusFlowRate/60.)*DeltaT_Mudline) - DeltaVolumeOp will be added to annulus
-
- !if (iLoc == 1) then
- data%State%MudSystem%MudSection= data%State%F_Counts%StringIntervalCounts+1
- data%State%MudSystem%BackheadX= data%State%MudSystem%Xstart_PipeSection(data%State%F_Counts%StringIntervalCounts+1)
- !elseif (iLoc == 2) then
- ! MudSection= Kick_Forehead_section
- ! BackheadX= Kick_Forehead_X
- !endif
-
- !========================ANNULUS ENTRANCE====================
- !if (KickMigration_2SideBit == .FALSE.) then
- ! if ( ABS(AnnulusSuctionDensity_Old - data%State%MudSystem%St_Density%Last()) >= DensityMixTol ) then ! new mud is pumped
- ! call Ann_Density%AddTo (iLoc,data%State%MudSystem%St_Density%Last())
- ! call Ann_MudDischarged_Volume%AddTo (iLoc,0.0d0)
- ! call Ann_Mud_Forehead_X%AddTo (iLoc,BackheadX)
- ! call Ann_Mud_Forehead_section%AddTo (iLoc,MudSection)
- ! call Ann_Mud_Backhead_X%AddTo (iLoc,BackheadX)
- ! call Ann_Mud_Backhead_section%AddTo (iLoc,MudSection)
- ! call Ann_RemainedVolume_in_LastSection%AddTo (iLoc,0.0d0)
- ! call Ann_EmptyVolume_inBackheadLocation%AddTo (iLoc,0.0d0)
- ! call Ann_MudOrKick%AddTo (iLoc,0)
- ! call Ann_CuttingMud%AddTo (iLoc,0)
- !
- ! AnnulusSuctionDensity_Old= data%State%MudSystem%St_Density%Last()
- !
- ! MudIsChanged= .true.
- ! endif
- !
- ! Ann_MudDischarged_Volume%Array(iLoc)= Ann_MudDischarged_Volume%Array(iLoc)+ ((data%State%MudSystem%AnnulusFlowRate/60.0d0)*DeltaT_Mudline) - ((2-iloc)*ABS(DeltaVolumePipe)) !(gal)
- !
- !endif
-
-
-
-
- data%State%MudSystem%Ann_Mud_Backhead_section%Array(1)= data%State%MudSystem%MudSection !it is needed to be updated for (a condition that one pipe is removed from Annulus due to trip out)- (and add pipe)
- data%State%MudSystem%Ann_Mud_Backhead_X%Array(1)= data%State%MudSystem%BackheadX
-
-
-
- !iloc=1 : (2-iloc)=1 normal
- !iloc=2 : (2-iloc)=0 kick influx or migration is in annulus
-
- !========================Same to Tripping In====================
-
- !write(*,*) 'Op_Kick_Saved_Volume,Op_Saved_MudDischarged_Volume=' , Op_Kick_Saved_Volume,Op_Saved_MudDischarged_Volume
-
-
- if (data%State%MudSystem%Op_Kick_Saved_Volume > 0.0 .and. data%State%MudSystem%Ann_MudOrKick%First() == 0) then !1st Mode
- write(*,*) 'Kick influx enters Annulus'
- call data%State%MudSystem%Ann_Density%AddToFirst (data%State%MudSystem%Op_KickSaved_Density)
- call data%State%MudSystem%Ann_MudDischarged_Volume%AddToFirst (data%State%MudSystem%Op_Kick_Saved_Volume)
- call data%State%MudSystem%Ann_Mud_Forehead_X%AddToFirst (data%State%MudSystem%Xstart_PipeSection(data%State%F_Counts%StringIntervalCounts+1))
- call data%State%MudSystem%Ann_Mud_Forehead_section%AddToFirst (data%State%F_Counts%StringIntervalCounts+1)
- call data%State%MudSystem%Ann_Mud_Backhead_X%AddToFirst (data%State%MudSystem%Xstart_PipeSection(data%State%F_Counts%StringIntervalCounts+1))
- call data%State%MudSystem%Ann_Mud_Backhead_section%AddToFirst (data%State%F_Counts%StringIntervalCounts+1)
- call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call data%State%MudSystem%Ann_MudOrKick%AddToFirst (data%State%MudSystem%Saved_Op_MudOrKick) !<<<<<<<<
- call data%State%MudSystem%Ann_CuttingMud%AddToFirst (0)
- elseif (data%State%MudSystem%Op_Kick_Saved_Volume > 0.0 .and. data%State%MudSystem%Ann_MudOrKick%First() /= 0) then
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(1)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(1) + data%State%MudSystem%Op_Kick_Saved_Volume
- endif
-
-
-
- if ( data%State%MudSystem%Op_NeededVolume_ToFill > 0.0 .and. (data%State%MudSystem%Op_NeededVolume_ToFill < ABS(data%State%MudSystem%DeltaVolumeAnnulusCapacity)) .and. data%State%MudSystem%Op_MudOrKick%Last() == 0 .and. (data%State%MudSystem%iLoc==2 .or. iloc_edited==1)) then !3rd Mode
- !write(*,*) 'checkpoint 0'
- !! for avoid kick separation -Op_MudOrKick%Last() == 0: because of pump
- data%State%MudSystem%NewVolume= ((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline) ! =volume that should be added to iloc=2 in Ann
- call RemoveOpMudArrays(data%State%MudSystem%Op_Density%Length()) ! mud here is removed and then will be added to iloc=2 in Ann in %%1 section
- if ( data%State%MudSystem%Ann_MudDischarged_Volume%Array(1) > ((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline) ) then! 1st in Ann = kick ,, we expect: ((data%State%MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline)= OpMudVolLast
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(1)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(1) - ((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline)
- data%State%MudSystem%Op_MudDischarged_Volume%Array(data%State%MudSystem%Op_Density%Length())= data%State%MudSystem%Op_MudDischarged_Volume%Array(data%State%MudSystem%Op_Density%Length())+ ((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline) ! kick
- else
- call RemoveAnnulusMudArrays(1) !kick is removed
- data%State%MudSystem%iLoc= 1
- data%State%MudSystem%Op_MudDischarged_Volume%Array(data%State%MudSystem%Op_Density%Length())= data%State%MudSystem%Op_MudDischarged_Volume%Array(data%State%MudSystem%Op_Density%Length())+ ((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline)
- write(*,*) 'little expand'
- ! including a little expand
- endif
- endif
-
- if (data%State%MudSystem%Op_Saved_MudDischarged_Volume> 0.0) then !1st Mode
- data%State%MudSystem%NewDensity= data%State%MudSystem%Op_MudSaved_Density
- !write(*,*) 'iloc,...' , iloc,((data%State%MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline),Op_Saved_MudDischarged_Volume
- if (data%State%MudSystem%iLoc==1) then
- !write(*,*) 'checkpoint 1'
- data%State%MudSystem%NewVolume= data%State%MudSystem%Op_Saved_MudDischarged_Volume
- elseif (real(((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline)) - real(data%State%MudSystem%Op_Saved_MudDischarged_Volume) > 0.d0 ) then ! for avoid kick separation
- !write(*,*) 'checkpoint 2'
- data%State%MudSystem%NewVolume= ((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline) !- Op_Saved_MudDischarged_Volume
- call RemoveOpMudArrays(data%State%MudSystem%Op_Density%Length()) ! mud here is removed and then will be added to iloc=2 in Ann
- if ( data%State%MudSystem%Ann_MudDischarged_Volume%Array(1) > (((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline) - data%State%MudSystem%Op_Saved_MudDischarged_Volume) ) then! 1st in Ann = kick
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(1)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(1) - (((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline) - data%State%MudSystem%Op_Saved_MudDischarged_Volume)
- data%State%MudSystem%Op_MudDischarged_Volume%Array(data%State%MudSystem%Op_Density%Length())= data%State%MudSystem%Op_MudDischarged_Volume%Array(data%State%MudSystem%Op_Density%Length())+ (((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline) - data%State%MudSystem%Op_Saved_MudDischarged_Volume) !kick
- else
- call RemoveAnnulusMudArrays(1) !kick is removed
- data%State%MudSystem%iLoc =1
- data%State%MudSystem%Op_MudDischarged_Volume%Array(data%State%MudSystem%Op_Density%Length())= data%State%MudSystem%Op_MudDischarged_Volume%Array(data%State%MudSystem%Op_Density%Length())+ (((data%State%MudSystem%AnnulusFlowRate/60.d0)*data%State%MudSystem%DeltaT_Mudline) - data%State%MudSystem%Op_Saved_MudDischarged_Volume)
- write(*,*) 'little expand'
-
- ! including a little expand
- endif
-
-
- else ! iloc==2 , ((data%State%MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline) == Op_Saved_MudDischarged_Volume
- !write(*,*) 'checkpoint 3'
- data%State%MudSystem%NewVolume= data%State%MudSystem%Op_Saved_MudDischarged_Volume ! it is normal mode
- endif
-
-
- endif
-
- !write(*,*) 'NewVolume=' ,NewVolume
-
-
- if( data%State%MudSystem%Ann_Density%Length() == 1 .and. data%State%MudSystem%iLoc ==2 ) then
-
- write(*,*) '***errorb****=='
-
- write(*,*) 'iloc_edited=' , iloc_edited
- write(*,*) 'iloc_changedTo2=' , iloc_changedTo2
-
- write(*,*) 'Op_Capacity===' , sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts))
-
- WRITE (*,*) 'Op_Saved_MudDischarged_Volume, Op_Kick_Saved_Volume',data%State%MudSystem%Op_Saved_MudDischarged_Volume, data%State%MudSystem%Op_Kick_Saved_Volume
-
- do imud=1, data%State%MudSystem%Op_MudDischarged_Volume%Length()
- write(*,*) 'Op:', imud, data%State%MudSystem%Op_MudDischarged_Volume%Array(imud), data%State%MudSystem%Op_Density%Array(imud) ,data%State%MudSystem%Op_MudOrKick%Array(imud)
- enddo
-
- do imud=1, data%State%MudSystem%Ann_MudDischarged_Volume%Length()
- write(*,*) 'Ann:', imud, data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud), data%State%MudSystem%Ann_Density%Array(imud) ,data%State%MudSystem%Ann_MudOrKick%Array(imud)
- enddo
-
-
-
- write(*,*) '==***errorb****'
- endif
-
-
-
-
-
- if ((data%State%ROP_Bit%RateOfPenetration==0 .and. abs(data%State%MudSystem%Ann_Density%Array(data%State%MudSystem%iLoc)-data%State%MudSystem%NewDensity)< data%State%MudSystem%DensityMixTol) & !%%1 section
- .or. (data%State%ROP_Bit%RateOfPenetration>0. .and. data%State%MudSystem%Ann_CuttingMud%Array(data%State%MudSystem%iLoc)==1 .and. abs(data%State%MudSystem%Ann_Density%Array(data%State%MudSystem%iLoc)-data%State%MudSystem%NewDensity)< data%State%MudSystem%CuttingDensityMixTol) &
- .or. (data%State%ROP_Bit%RateOfPenetration>0. .and. data%State%MudSystem%Ann_CuttingMud%Array(data%State%MudSystem%iLoc)==0 .and. data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc) < 42.) ) then ! 1-Pockets are Merged
- !write(*,*) '%%1 section a)'
- data%State%MudSystem%Ann_Density%Array(data%State%MudSystem%iLoc)= (data%State%MudSystem%Ann_Density%Array(data%State%MudSystem%iLoc)*data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc)+data%State%MudSystem%NewDensity*data%State%MudSystem%NewVolume)/(data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc)+data%State%MudSystem%NewVolume)
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc)+data%State%MudSystem%NewVolume
- data%State%MudSystem%Ann_Mud_Forehead_X%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%BackheadX
- data%State%MudSystem%Ann_Mud_Forehead_section%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%MudSection
- data%State%MudSystem%Ann_Mud_Backhead_X%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%BackheadX
- data%State%MudSystem%Ann_Mud_Backhead_section%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%MudSection
- data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(data%State%MudSystem%iLoc)= (0.0d0)
- data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(data%State%MudSystem%iLoc)= (0.0d0)
- else ! 2-Merging conditions are not meeted, so new pocket
- !write(*,*) '%%1 section b)'
-
- call data%State%MudSystem%Ann_Density%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%NewDensity)
- call data%State%MudSystem%Ann_MudDischarged_Volume%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%NewVolume)
- call data%State%MudSystem%Ann_Mud_Forehead_X%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%BackheadX)
- call data%State%MudSystem%Ann_Mud_Forehead_section%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%MudSection)
- call data%State%MudSystem%Ann_Mud_Backhead_X%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%BackheadX)
- call data%State%MudSystem%Ann_Mud_Backhead_section%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%MudSection)
- call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (data%State%MudSystem%iLoc,0.0d0)
- call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (data%State%MudSystem%iLoc,0.0d0)
- call data%State%MudSystem%Ann_MudOrKick%AddTo (data%State%MudSystem%iLoc,0)
- call data%State%MudSystem%Ann_CuttingMud%AddTo (data%State%MudSystem%iLoc,0)
- !write(*,*) 'd) annLength=' , Ann_Density%Length()
-
- endif
-
-
-
-
- !========================Same to Tripping In - End====================
-
- !write(*,*) 'b)Ann_Mud sum=' , sum(Ann_MudDischarged_Volume%Array(:))
-
- !write(*,*) 'no======2'
- !
- ! do imud=1, Op_MudDischarged_Volume%Length()
- ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
- ! enddo
- !
- ! do imud=1, Ann_MudDischarged_Volume%Length()
- ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
- ! enddo
- !
- !
- ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
- !
- !
- !write(*,*) '2======no'
-
- !=============== save Ann Mud data to transfer to the ChokeLine enterance
- data%State%MudSystem%AnnMudVolumeSum= 0.d0
- !Ann_MudSaved_Density= 0.d0
- !Ann_KickSaved_Density= 0.d0
- data%State%MudSystem%Ann_Saved_MudDischarged_Volume= 0.d0
- data%State%MudSystem%Ann_Kick_Saved_Volume= 0.d0
- data%State%MudSystem%Saved_Ann_MudOrKick= 0
- data%State%MudSystem%Ann_to_Choke_2mud= .false.
-
-
-
-
- do imud=1, data%State%MudSystem%Ann_MudDischarged_Volume%Length()
-
- data%State%MudSystem%AnnMudVolumeSum= data%State%MudSystem%AnnMudVolumeSum + data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)
-
- if ( data%State%MudSystem%AnnMudVolumeSum > sum(data%State%MudSystem%PipeSection_VolumeCapacity(data%State%F_Counts%StringIntervalCounts+1:data%State%MudSystem%NoPipeSections)) ) then
-
- IF (data%State%MudSystem%Ann_MudOrKick%Array(imud) == 0) THEN
- data%State%MudSystem%Ann_MudSaved_Density = data%State%MudSystem%Ann_Density%Array(imud)
- data%State%MudSystem%Ann_Saved_MudDischarged_Volume = data%State%MudSystem%AnnMudVolumeSum - sum(data%State%MudSystem%PipeSection_VolumeCapacity(data%State%F_Counts%StringIntervalCounts+1:data%State%MudSystem%NoPipeSections))
- ELSEIF (data%State%MudSystem%Ann_MudOrKick%Array(imud) > 0 .AND. data%State%MudSystem%Ann_MudOrKick%Array(imud) <100) THEN ! 104= AIR
- data%State%MudSystem%Ann_Kick_Saved_Volume = data%State%MudSystem%AnnMudVolumeSum - sum(data%State%MudSystem%PipeSection_VolumeCapacity(data%State%F_Counts%StringIntervalCounts+1:data%State%MudSystem%NoPipeSections))
- data%State%MudSystem%Saved_Ann_MudOrKick= data%State%MudSystem%Ann_MudOrKick%Array (imud)
- data%State%MudSystem%Ann_KickSaved_Density= data%State%MudSystem%Ann_Density%Array(imud)
- END IF
-
- do ii= imud + 1, data%State%MudSystem%Ann_MudDischarged_Volume%Length()
- IF (data%State%MudSystem%Ann_MudOrKick%Array(ii) == 0) THEN
- data%State%MudSystem%Ann_MudSaved_Density = ((data%State%MudSystem%Ann_MudSaved_Density * data%State%MudSystem%Ann_Saved_MudDischarged_Volume) + (data%State%MudSystem%Ann_Density%Array(ii) * data%State%MudSystem%Ann_MudDischarged_Volume%Array(ii))) / (data%State%MudSystem%Ann_Saved_MudDischarged_Volume + data%State%MudSystem%Ann_MudDischarged_Volume%Array(ii))
- data%State%MudSystem%Ann_Saved_MudDischarged_Volume = data%State%MudSystem%Ann_Saved_MudDischarged_Volume + data%State%MudSystem%Ann_MudDischarged_Volume%Array(ii)
- data%State%MudSystem%Ann_to_Choke_2mud= .true.
- ELSEIF (data%State%MudSystem%Ann_MudOrKick%Array(ii) > 0 .AND. data%State%MudSystem%Ann_MudOrKick%Array(ii) <100) THEN ! 104= AIR
- data%State%MudSystem%Ann_Kick_Saved_Volume = data%State%MudSystem%Ann_Kick_Saved_Volume + data%State%MudSystem%Ann_MudDischarged_Volume%Array(ii)
- data%State%MudSystem%Saved_Ann_MudOrKick= data%State%MudSystem%Ann_MudOrKick%Array (ii)
- data%State%MudSystem%Ann_KickSaved_Density= data%State%MudSystem%Ann_Density%Array(ii)
- END IF
- enddo
-
- exit ! exits do
-
- endif
-
- enddo
-
- data%State%MudSystem%Ann_Saved_MudDischarged_Volume_Final= data%State%MudSystem%Ann_Saved_MudDischarged_Volume
- data%State%MudSystem%Ann_Kick_Saved_Volume_Final= data%State%MudSystem%Ann_Kick_Saved_Volume
- !write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(data%State%F_Counts%StringIntervalCounts+1:NoPipeSections))
- !write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
-
- IF (data%State%MudSystem%WellHeadIsOpen) data%State%MudSystem%MudVolume_InjectedFromAnn = data%State%MudSystem%Ann_Saved_MudDischarged_Volume_Final-((data%State%MudSystem%Qlost/60.0d0)*data%State%MudSystem%DeltaT_Mudline)
- !NoGasPocket
- !write(*,*) 'Ann_Saved_Mud_Vol,Ann_Kick_Saved_Vol=' , Ann_Saved_MudDischarged_Volume,Ann_Kick_Saved_Volume
-
- !======================================================================
-
-
- !write(*,*) 'Ann_Saved_Mud=' , Ann_Saved_MudDischarged_Volume
- !======================== Annulus ====================
-
- !MudIsChanged= .false.
-
- imud= 0
-
- do while (imud < data%State%MudSystem%Ann_Mud_Forehead_X%Length())
- imud = imud + 1
-
- if (imud> 1) then
- data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud)= data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud-1)
- data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud)= data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud-1)
- endif
-
- ! write(*,*) 'imud==' , imud
- !write(*,*) '***)Ann_Mud_Backhead_section(imud)= ' , Ann_Mud_Backhead_section%Array(imud), Ann_density%Array(imud)
-
-
- data%State%MudSystem%DirectionCoef= (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud))-data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud))) &
- / ABS(data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud))-data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud)))
- ! +1 for string , -1 for annulus
-
-
- data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%DirectionCoef* (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud))- data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud))* &
- data%State%MudSystem%Area_PipeSectionFt(data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud)) !(ft^3)
- data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
-
-
- if ( data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud) <= data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then
- data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)= data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud)
- data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud)= data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud)+ data%State%MudSystem%DirectionCoef*(data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)/7.48051948d0)/data%State%MudSystem%Area_PipeSectionFt(data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud))
- ! 7.48 is for gal to ft^3
-
- else
-
- data%State%MudSystem%isection= data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud)+1
- data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)- data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)
-
- do
- if (data%State%MudSystem%isection > data%State%MudSystem%NoPipeSections) then ! last pipe section(well exit)
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)- data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)
- data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud)= data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%NoPipeSections)
- data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)= data%State%MudSystem%NoPipeSections
-
- if (data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
- call RemoveAnnulusMudArrays(imud)
- endif
-
- exit
- endif
-
- data%State%MudSystem%xx= data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ data%State%MudSystem%PipeSection_VolumeCapacity(data%State%MudSystem%isection) !(gal)
-
- if (data%State%MudSystem%xx<= 1.0) then
- data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)= data%State%MudSystem%isection
- data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud)= (data%State%MudSystem%xx * (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%isection)- data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%isection)))+ data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%isection)
- exit
- else
- data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- data%State%MudSystem%PipeSection_VolumeCapacity(data%State%MudSystem%isection)
- data%State%MudSystem%isection= data%State%MudSystem%isection+ 1
-
- endif
-
- enddo
-
- endif
-
- enddo
-
- if (data%State%MudSystem%Ann_Mud_Forehead_X%Last() < data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%NoPipeSections)) then
- data%State%MudSystem%Ann_Mud_Forehead_X%Array(data%State%MudSystem%Ann_Mud_Forehead_X%Length()) = data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%NoPipeSections) ! for error preventing
- endif
-
- !========================ANNULUS END=================
-
-
-
- !*************************************************************************************************************************
-
- !========================Tripping Out- 2nd Mode====================
-
-
- elseif ( data%State%MudSystem%Op_NeededVolume_ToFill > ABS(data%State%MudSystem%DeltaVolumeAnnulusCapacity) ) then !pump is off or Pump flow is less than trip out so fluid Level in Annulus decreases
- !write(*,*) 'trip out 2nd mode'
-
-
- SavedDensityForOp= data%State%MudSystem%Ann_Density%Array(1)
- !========================ANNULUS ENTRANCE====================
-
- ! <<< SIMILAR TO UTUBE 2 >>>
- if ( data%State%MudSystem%Ann_Density%Last() /= 0.0 ) then ! new mud is pumped
- call data%State%MudSystem%Ann_Density%Add (0.0d0)
- call data%State%MudSystem%Ann_MudDischarged_Volume%Add (0.0d0)
- call data%State%MudSystem%Ann_Mud_Forehead_X%Add (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%NoPipeSections))
- call data%State%MudSystem%Ann_Mud_Forehead_section%Add (data%State%MudSystem%NoPipeSections)
- call data%State%MudSystem%Ann_Mud_Backhead_X%Add (data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%NoPipeSections))
- call data%State%MudSystem%Ann_Mud_Backhead_section%Add (data%State%MudSystem%NoPipeSections)
- call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Add (0.0d0)
- call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Add (0.0d0)
- call data%State%MudSystem%Ann_MudOrKick%Add (104)
- call data%State%MudSystem%Ann_CuttingMud%Add (0)
-
- !AnnulusSuctionDensity_Old= Hz_Density%Last()
- endif
-
- data%State%MudSystem%Ann_Mud_Forehead_section%Array(data%State%MudSystem%Ann_Mud_Forehead_section%Length())= data%State%MudSystem%NoPipeSections !it is needed to be updated for (a condition that one pipe is removed from Annulus due to trip out)- (and add pipe)
- data%State%MudSystem%Ann_Mud_Forehead_X%Array(data%State%MudSystem%Ann_Mud_Forehead_X%Length())= data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%NoPipeSections)
-
-
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%Ann_MudDischarged_Volume%Length())= data%State%MudSystem%Ann_MudDischarged_Volume%Last()+ (data%State%MudSystem%Op_NeededVolume_ToFill - ABS(data%State%MudSystem%DeltaVolumeAnnulusCapacity)) ! Op_NeededVolume_ToFill !ABS(DeltaVolumePipe) - ((data%State%MudSystem%AnnulusFlowRate/60.)*DeltaT_Mudline) !(gal)
-
- !===================================================================
-
-
-
- if ( (data%State%MudSystem%iLoc==2 .or. iloc_edited==1) .and. data%State%MudSystem%Op_MudOrKick%Last()==0 ) then ! for avoid kick separation
- !write(*,*) 'here mud should be removed from Op last'
-
- if (abs(data%State%MudSystem%Ann_Density%Array(data%State%MudSystem%iLoc)-data%State%MudSystem%Op_Density%Last())< data%State%MudSystem%DensityMixTol) then
-
- data%State%MudSystem%Ann_Density%Array(data%State%MudSystem%iLoc)= (data%State%MudSystem%Ann_Density%Array(data%State%MudSystem%iLoc)*data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc)+data%State%MudSystem%Op_Density%Last()*data%State%MudSystem%Op_MudDischarged_Volume%Last())/(data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc)+data%State%MudSystem%Op_MudDischarged_Volume%Last())
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%iLoc)+data%State%MudSystem%Op_MudDischarged_Volume%Last() ! OP_Last is data%State%MUD(effect of pump added mud)
- data%State%MudSystem%Ann_Mud_Forehead_X%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%BackheadX
- data%State%MudSystem%Ann_Mud_Forehead_section%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%MudSection
- data%State%MudSystem%Ann_Mud_Backhead_X%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%BackheadX
- data%State%MudSystem%Ann_Mud_Backhead_section%Array(data%State%MudSystem%iLoc)= data%State%MudSystem%MudSection
- data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(data%State%MudSystem%iLoc)= (0.0d0)
- data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(data%State%MudSystem%iLoc)= (0.0d0)
- !write(*,*) 'merge' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
-
- else ! 2-Merging conditions are not meeted, so new pocket
- call data%State%MudSystem%Ann_Density%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%Op_Density%Last())
- call data%State%MudSystem%Ann_MudDischarged_Volume%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%Op_MudDischarged_Volume%Last())
- call data%State%MudSystem%Ann_Mud_Forehead_X%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%BackheadX)
- call data%State%MudSystem%Ann_Mud_Forehead_section%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%MudSection)
- call data%State%MudSystem%Ann_Mud_Backhead_X%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%BackheadX)
- call data%State%MudSystem%Ann_Mud_Backhead_section%AddTo (data%State%MudSystem%iLoc,data%State%MudSystem%MudSection)
- call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (data%State%MudSystem%iLoc,0.0d0)
- call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (data%State%MudSystem%iLoc,0.0d0)
- call data%State%MudSystem%Ann_MudOrKick%AddTo (data%State%MudSystem%iLoc,0)
- call data%State%MudSystem%Ann_CuttingMud%AddTo (data%State%MudSystem%iLoc,0)
- endif
-
- data%State%MudSystem%Op_NeededVolume_ToFill= data%State%MudSystem%Op_NeededVolume_ToFill + data%State%MudSystem%Op_MudDischarged_Volume%Last() ! OP_Last is data%State%MUD(effect of pump added mud)
-
- call RemoveOpMudArrays(data%State%MudSystem%Op_MudOrKick%Length())
-
-
- endif
- !===================================================================
-
-
- !=============== save Ann Mud data to transfer to the ChokeLine enterance
- !AnnMudVolumeSum= 0.d0
- !!Ann_MudSaved_Density= 0.d0
- !!Ann_KickSaved_Density= 0.d0
- data%State%MudSystem%Ann_Saved_MudDischarged_Volume= 0.d0
- data%State%MudSystem%Ann_Kick_Saved_Volume= 0.d0
- !Saved_Ann_MudOrKick= 0
- !Ann_to_Choke_2mud= .false.
-
-
-
-
- !do imud=1, Ann_MudDischarged_Volume%Length()
- !
- ! AnnMudVolumeSum= AnnMudVolumeSum + Ann_MudDischarged_Volume%Array(imud)
- !
- ! if ( AnnMudVolumeSum > sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) ) then
- !
- ! IF (Ann_MudOrKick%Array(imud) == 0) THEN
- ! Ann_MudSaved_Density = Ann_Density%Array(imud)
- ! Ann_Saved_MudDischarged_Volume = AnnMudVolumeSum - sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- ! ELSEIF (Ann_MudOrKick%Array(imud) > 0 .AND. Ann_MudOrKick%Array(imud) <100) THEN ! 104= AIR
- ! Ann_Kick_Saved_Volume = AnnMudVolumeSum - sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- ! Saved_Ann_MudOrKick= Ann_MudOrKick%Array (imud)
- ! Ann_KickSaved_Density= Ann_Density%Array(imud)
- ! END IF
- !
- ! do ii= imud + 1, Ann_MudDischarged_Volume%Length()
- ! IF (Ann_MudOrKick%Array(ii) == 0) THEN
- ! Ann_MudSaved_Density = ((Ann_MudSaved_Density * Ann_Saved_MudDischarged_Volume) + (Ann_Density%Array(ii) * Ann_MudDischarged_Volume%Array(ii))) / (Ann_Saved_MudDischarged_Volume + Ann_MudDischarged_Volume%Array(ii))
- ! Ann_Saved_MudDischarged_Volume = Ann_Saved_MudDischarged_Volume + Ann_MudDischarged_Volume%Array(ii)
- ! Ann_to_Choke_2mud= .true.
- ! ELSEIF (Ann_MudOrKick%Array(ii) > 0 .AND. Ann_MudOrKick%Array(ii) <100) THEN ! 104= AIR
- ! Ann_Kick_Saved_Volume = Ann_Kick_Saved_Volume + Ann_MudDischarged_Volume%Array(ii)
- ! Saved_Ann_MudOrKick= Ann_MudOrKick%Array (ii)
- ! Ann_KickSaved_Density= Ann_Density%Array(ii)
- ! END IF
- ! enddo
- !
- ! exit ! exits do
- !
- ! endif
- !
- !enddo
-
-
- ! write(*,*) 'check point 2=='
- !
- !
- !
- ! do imud=1, Ann_MudDischarged_Volume%Length()
- ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
- ! enddo
- !
- ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
- !
- !
- !write(*,*) '==check point 2'
-
-
-
-
-
- data%State%MudSystem%Ann_Saved_MudDischarged_Volume_Final= data%State%MudSystem%Ann_Saved_MudDischarged_Volume
- data%State%MudSystem%Ann_Kick_Saved_Volume_Final= data%State%MudSystem%Ann_Kick_Saved_Volume
- !write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- !write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
-
- !write(*,*) 'Ann_Saved_MudDischarged_Volume_Final=' , Ann_Saved_MudDischarged_Volume_Final
-
-
-
- IF (data%State%MudSystem%WellHeadIsOpen) data%State%MudSystem%MudVolume_InjectedFromAnn = data%State%MudSystem%Ann_Saved_MudDischarged_Volume_Final-((data%State%MudSystem%Qlost/60.0d0)*data%State%MudSystem%DeltaT_Mudline)
- !! NoGasPocket > 0 .AND.
-
- !write(*,*) 'Ann_Saved_Mud_Vol,Ann_Kick_Saved_Vol=' , Ann_Saved_MudDischarged_Volume,Ann_Kick_Saved_Volume
-
-
- !======================================================================
-
- !========================ANNULUS====================
- ! <<< SIMILAR TO UTUBE 2 >>>
-
- !write(*,*) Ann_MudOrKick%Last(), 'DeltaVolumePipe , after volume=' ,ABS(DeltaVolumePipe), Ann_MudDischarged_Volume%Last()
- imud= data%State%MudSystem%Ann_Mud_Forehead_X%Length() + 1
-
- do while (imud > 1)
- imud = imud - 1
-
- if (imud< data%State%MudSystem%Ann_Mud_Forehead_X%Length()) then
- data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud)= data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud+1)
- data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)= data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud+1)
- endif
-
-
- ! <<< Fracture Shoe Lost
- IF ( data%State%MudSystem%ShoeLost .and. data%Configuration%Shoe%ShoeDepth < data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud) .and. data%Configuration%Shoe%ShoeDepth >= data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud) ) then
- !write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline)
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)-((data%State%MudSystem%Qlost/60.0d0)*data%State%MudSystem%DeltaT_Mudline) !(gal)
- if (data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud) < 0.0) then
- !write(*,*) 'mud is removed by shoe lost, imud=' , imud
- call RemoveAnnulusMudArrays(imud)
- imud= imud-1
- cycle
- endif
- data%State%MudSystem%LostInTripOutIsDone= .true.
- ENDIF
- ! Fracture Shoe Lost >>>
-
-
-
-
-
-
-
-
- !write(*,*) 'a)imud,Ann_Mud_Forehead_section=',imud,Ann_Mud_Forehead_section%Array(imud)
-
- data%State%MudSystem%DirectionCoef= (data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud))-data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud))) &
- / ABS(data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud))-data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)))
- ! +1 for string , -1 for annulus
-
- !write(*,*) 'b)imud,Forehead_X,Xstart_PipeSection=',imud,Ann_Mud_Forehead_X%Array(imud),Xstart_PipeSection(Ann_Mud_Forehead_section%Array(imud))
-
- data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%DirectionCoef* (data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud)- data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)))* &
- data%State%MudSystem%Area_PipeSectionFt(data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)) !(ft^3)
- data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
-
- if ( data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud) <= data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then
- data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud)= data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)
- data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud)= data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud)- data%State%MudSystem%DirectionCoef*(data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)/7.48051948d0)/data%State%MudSystem%Area_PipeSectionFt(data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud))
- ! 7.48051948 is for gal to ft^3
- else
- data%State%MudSystem%isection= data%State%MudSystem%Ann_Mud_Forehead_section%Array(imud)-1
- data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)- data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)
-
- do
- if (data%State%MudSystem%isection < data%State%F_Counts%StringIntervalCounts+1) then ! last pipe section(well exit) data%State%F_Counts%StringIntervalCounts+1 is the first section in Annulus
- data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)- data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)
- data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud)= data%State%MudSystem%Xstart_PipeSection(data%State%F_Counts%StringIntervalCounts+1)
- data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud)= data%State%F_Counts%StringIntervalCounts+1
-
- if (data%State%MudSystem%Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
- call RemoveAnnulusMudArrays(imud)
- endif
-
- exit
- endif
-
- data%State%MudSystem%xx= data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ data%State%MudSystem%PipeSection_VolumeCapacity(data%State%MudSystem%isection) !(gal)
-
- if (data%State%MudSystem%xx<= 1.0) then
- data%State%MudSystem%Ann_Mud_Backhead_section%Array(imud)= data%State%MudSystem%isection
- data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud)= (data%State%MudSystem%xx * (data%State%MudSystem%Xstart_PipeSection(data%State%MudSystem%isection)- data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%isection)))+ data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%isection)
- exit
- else
- data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- data%State%MudSystem%PipeSection_VolumeCapacity(data%State%MudSystem%isection)
- data%State%MudSystem%isection= data%State%MudSystem%isection- 1
-
-
- endif
-
- enddo
-
- endif
-
- enddo
- !========================ANNULUS END=================
-
- endif ! end of 1st &3rd & 2nd Mode
-
-
- !*************************************************************************************************************************
-
-
-
-
-
-
- !======================== Bottom Hole Entrance ==========================
- !if (iloc == 1) then
- if ( data%State%MudSystem%Op_NeededVolume_ToFill > 0.0 ) then ! it is needed for 2nd & 3rd mode
- !write(*,*) 'op add for 2nd & 3rd mode done'
-
-
-
- if ( ABS(data%State%MudSystem%Op_Density%Last() - SavedDensityForOp ) >= data%State%MudSystem%DensityMixTol) then ! .OR. (Op_MudDischarged_Volume%Last()>42.) ) then ! 1-Merging conditions are not meeted, so new pocket
-
- call data%State%MudSystem%Op_Density%Add (SavedDensityForOp)
- call data%State%MudSystem%Op_MudDischarged_Volume%Add (data%State%MudSystem%Op_NeededVolume_ToFill)
- call data%State%MudSystem%Op_Mud_Forehead_X%Add (0.0d0)
- call data%State%MudSystem%Op_Mud_Forehead_section%Add (1)
- call data%State%MudSystem%Op_Mud_Backhead_X%Add (0.0d0)
- call data%State%MudSystem%Op_Mud_Backhead_section%Add (1)
- call data%State%MudSystem%Op_RemainedVolume_in_LastSection%Add (0.0d0)
- call data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%Add (0.0d0)
- call data%State%MudSystem%Op_MudOrKick%Add (data%State%MudSystem%Ann_MudOrKick%Array(1))
- else ! 2-Pockets are Merged
-
- data%State%MudSystem%Op_Density%Array (data%State%MudSystem%Op_Density%Length())= (SavedDensityForOp*data%State%MudSystem%Op_NeededVolume_ToFill+data%State%MudSystem%Op_Density%Last()*data%State%MudSystem%Op_MudDischarged_Volume%Last())/(data%State%MudSystem%Op_MudDischarged_Volume%Last()+data%State%MudSystem%Op_NeededVolume_ToFill)
- data%State%MudSystem%Op_MudDischarged_Volume%Array (data%State%MudSystem%Op_Density%Length())= data%State%MudSystem%Op_MudDischarged_Volume%Array (data%State%MudSystem%Op_Density%Length()) + data%State%MudSystem%Op_NeededVolume_ToFill
- data%State%MudSystem%Op_RemainedVolume_in_LastSection%Array (data%State%MudSystem%Op_Density%Length())= 0.0
- data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%Array (data%State%MudSystem%Op_Density%Length())= 0.0
-
- endif
-
- endif
-
-
-
-
- !============================= Bottom Hole ==============================
-
- imud=0
- do while (imud < data%State%MudSystem%Op_Mud_Forehead_X%Length())
- imud = imud + 1
-
- if (imud> 1) then
- data%State%MudSystem%Op_Mud_Backhead_X%Array(imud)= data%State%MudSystem%Op_Mud_Forehead_X%Array(imud-1)
- data%State%MudSystem%Op_Mud_Backhead_section%Array(imud)= data%State%MudSystem%Op_Mud_Forehead_section%Array(imud-1)
- endif
-
- data%State%MudSystem%DirectionCoef= (data%State%MudSystem%Xend_OpSection(data%State%MudSystem%Op_Mud_Backhead_section%Array(imud))-data%State%MudSystem%Xstart_OpSection(data%State%MudSystem%Op_Mud_Backhead_section%Array(imud))) &
- / ABS(data%State%MudSystem%Xend_OpSection(data%State%MudSystem%Op_Mud_Backhead_section%Array(imud))-data%State%MudSystem%Xstart_OpSection(data%State%MudSystem%Op_Mud_Backhead_section%Array(imud)))
- ! +1 for string , -1 for annulus
-
-
-
- data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%DirectionCoef* (data%State%MudSystem%Xend_OpSection(data%State%MudSystem%Op_Mud_Backhead_section%Array(imud))- data%State%MudSystem%Op_Mud_Backhead_X%Array(imud))* &
- data%State%MudSystem%Area_OpSectionFt(data%State%MudSystem%Op_Mud_Backhead_section%Array(imud)) !(ft^3)
- data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
-
-
- if ( data%State%MudSystem%Op_MudDischarged_Volume%Array(imud) <= data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)) then
- data%State%MudSystem%Op_Mud_Forehead_section%Array(imud)= data%State%MudSystem%Op_Mud_Backhead_section%Array(imud)
- data%State%MudSystem%Op_Mud_Forehead_X%Array(imud)= data%State%MudSystem%Op_Mud_Backhead_X%Array(imud)+ data%State%MudSystem%DirectionCoef*(data%State%MudSystem%Op_MudDischarged_Volume%Array(imud)/7.48051948d0)/data%State%MudSystem%Area_OpSectionFt(data%State%MudSystem%Op_Mud_Backhead_section%Array(imud))
- ! 7.48051948 is for gal to ft^3
-
- else
-
- data%State%MudSystem%isection= data%State%MudSystem%Op_Mud_Backhead_section%Array(imud)+1
- data%State%MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%Op_MudDischarged_Volume%Array(imud)- data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)
-
- do
- if (data%State%MudSystem%isection > data%State%F_Counts%BottomHoleIntervalCounts) then ! last pipe section(well exit)
- !if( imud==1) KickDeltaVinAnnulus= Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space
- data%State%MudSystem%Op_MudDischarged_Volume%Array(imud)= data%State%MudSystem%Op_MudDischarged_Volume%Array(imud)- data%State%MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)
- data%State%MudSystem%Op_Mud_Forehead_X%Array(imud)= data%State%MudSystem%Xend_OpSection(data%State%F_Counts%BottomHoleIntervalCounts)
- data%State%MudSystem%Op_Mud_Forehead_section%Array(imud)= data%State%F_Counts%BottomHoleIntervalCounts
-
- if (data%State%MudSystem%Op_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
- call data%State%MudSystem%Op_MudDischarged_Volume%Remove (imud)
- call data%State%MudSystem%Op_Mud_Backhead_X%Remove (imud)
- call data%State%MudSystem%Op_Mud_Backhead_section%Remove (imud)
- call data%State%MudSystem%Op_Mud_Forehead_X%Remove (imud)
- call data%State%MudSystem%Op_Mud_Forehead_section%Remove (imud)
- call data%State%MudSystem%Op_Density%Remove (imud)
- call data%State%MudSystem%Op_RemainedVolume_in_LastSection%Remove (imud)
- call data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%Remove (imud)
- call data%State%MudSystem%Op_MudOrKick%Remove (imud)
-
- endif
-
- exit
- endif
-
- data%State%MudSystem%xx= data%State%MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)/ data%State%MudSystem%OpSection_VolumeCapacity(data%State%MudSystem%isection) !(gal)
-
- if (data%State%MudSystem%xx<= 1.0) then
- data%State%MudSystem%Op_Mud_Forehead_section%Array(imud)= data%State%MudSystem%isection
- data%State%MudSystem%Op_Mud_Forehead_X%Array(imud)= (data%State%MudSystem%xx * (data%State%MudSystem%Xend_OpSection(data%State%MudSystem%isection)- data%State%MudSystem%Xstart_OpSection(data%State%MudSystem%isection)))+ data%State%MudSystem%Xstart_OpSection(data%State%MudSystem%isection)
- exit
- else
- data%State%MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= data%State%MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)- data%State%MudSystem%OpSection_VolumeCapacity(data%State%MudSystem%isection)
- data%State%MudSystem%isection= data%State%MudSystem%isection+ 1
-
- endif
-
- enddo
-
- endif
-
- enddo
-
-
-
- !========================Bottom Hole END=================
- ! write(*,*) 'after sorting=='
- !!!
- ! do imud=1, Op_MudDischarged_Volume%Length()
- ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
- ! enddo
- !
- ! do imud=1, Ann_MudDischarged_Volume%Length()
- ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
- ! enddo
- !!!
- !! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
- !! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
- !!!
- !!!
- !write(*,*) '==after sorting'
-
- !=========================================================
-
-
- data%State%MudSystem%total_injected = data%State%MudSystem%total_injected + data%State%MudSystem%MudVolume_InjectedFromAnn
-
- if (data%Equipments%ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
- data%State%MudSystem%total_injected= 0.
- endif
- !write(*,*) ' data%State%MudSystem%MudVolume_InjectedFromAnn =' , data%State%MudSystem%MudVolume_InjectedFromAnn
-
- !write(*,*) ' total injected-tripout =' , total_injected
- !write(*,*) ' injected-tripout =' , data%State%MudSystem%MudVolume_InjectedFromAnn
-
-
-
-
-
-
-
- end subroutine TripOut_and_Pump
-
-
-
|