|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406 |
- subroutine PlotFinalMudElements ! is called in subroutine CirculationCodeSelect
-
- Use GeoElements_FluidModule
- USE CMudPropertiesVariables
- USE MudSystemVARIABLES
- use SimulationVariables
- Use TD_StringConnectionData
- USE CHOKEVARIABLES
- !use CTanks
- !@use ConfigurationVariables, TripTankVolume2 => data%Equipments%DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
- USE sROP_Other_Variables
- USE sROP_Variables
- use KickVARIABLESModule
- use OperationScenariosModule
- use UTUBEVARSModule
- use DownHoleModule
- use CLog1
- Use CError
- Use , intrinsic :: IEEE_Arithmetic
-
- implicit none
-
- integer jelement, jmud, jsection,ielement,i
- integer jopelement,jopmud,jopsection
- character(len=120) :: temp1, temp2
-
-
-
-
- if (data%Equipments%ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
- write(*,*) 'well cap=' , sum(data%State%MudSystem%PipeSection_VolumeCapacity(data%State%F_Counts%StringIntervalCounts+1:data%State%MudSystem%NoPipeSections)) + sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts))
- data%State%MudSystem%DeltaWellCap= sum(data%State%MudSystem%PipeSection_VolumeCapacity(data%State%F_Counts%StringIntervalCounts+1:data%State%MudSystem%NoPipeSections)) + sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts)) - data%State%MudSystem%WellCapOld
- data%State%MudSystem%WellCapOld= sum(data%State%MudSystem%PipeSection_VolumeCapacity(data%State%F_Counts%StringIntervalCounts+1:data%State%MudSystem%NoPipeSections)) + sum(data%State%MudSystem%OpSection_VolumeCapacity(1:data%State%F_Counts%BottomHoleIntervalCounts))
- write(*,*) 'cap_reset,DeltaWellCap=' , data%State%MudSystem%DeltaWellCap
- endif
-
-
-
-
- !========================ANNULUS END=================
- if ((data%State%MudSystem%Ann_Mud_Forehead_X%Last() - data%Configuration%BopStack%AboveAnnularHeight) > 0.8 .or. data%State%MudSystem%Ann_Density%Last()==0.0) then ! for Line (BellNippleToWell-NonFullWell)
- data%State%MudSystem%WellisNOTFull= .true.
- else
- data%State%MudSystem%WellisNOTFull= .false.
- endif
-
- !WRITE(*,*) 'Ann_Mud_Forehead_X%Last() , KillHeight', Ann_Mud_Forehead_X%Last() , KillHeight
- if ((data%State%MudSystem%Ann_Mud_Forehead_X%Last() - data%Configuration%BopStack%KillHeight)>0.8 .or. data%State%MudSystem%Ann_Density%Last()==0.0) then ! for Line j4 , WellToChokeManifold(Through 26)
- data%State%MudSystem%ChokeLineNOTFull= .true.
- else
- data%State%MudSystem%ChokeLineNOTFull= .false.
- endif
-
- !=========================================================
-
- jmud= 1
- jsection= 1
- jelement= 0 ! number of final mud elements
-
-
-
- call data%State%MudSystem%Xend_MudElement%Empty()
- call data%State%MudSystem%TVDend_MudElement%Empty()
- call data%State%MudSystem%Density_MudElement%Empty()
- call data%State%MudSystem%MudGeoType%Empty()
- call data%State%MudSystem%PipeID_MudElement%Empty()
- call data%State%MudSystem%PipeOD_MudElement%Empty()
- !call Angle_MudElement%Empty()
- call data%State%MudSystem%MudType_MudElement%Empty()
-
-
-
- DO WHILE(jmud <= data%State%MudSystem%Hz_Mud_Forehead_X%Length() .and. jsection<=1)
-
- jelement= jelement+1
- data%State%MudSystem%TrueMinValue= min(data%State%MudSystem%Hz_Mud_Forehead_X%Array(jmud), data%State%MudSystem%Xend_PipeSection(jsection))
-
- call data%State%MudSystem%Xend_MudElement%Add(data%State%MudSystem%TrueMinValue)
- call TVD_Calculator(data%State%MudSystem%TrueMinValue,data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%TVDend_MudElement%Add(data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%Density_MudElement%Add(data%State%MudSystem%Hz_Density%Array(jmud))
- call data%State%MudSystem%PipeID_MudElement%Add(data%State%MudSystem%ID_PipeSectionInch(jsection))
- call data%State%MudSystem%PipeOD_MudElement%Add(data%State%MudSystem%OD_PipeSectionInch(jsection))
- !call Angle_MudElement%Add(Angle_PipeSection(jsection))
- call data%State%MudSystem%MudType_MudElement%Add(data%State%MudSystem%Hz_MudOrKick%Array(jmud))
-
-
- if (data%State%MudSystem%Xend_MudElement%Array(jelement)== data%State%MudSystem%Hz_Mud_Forehead_X%Array(jmud)) then
- jmud= jmud+1
- else
- jsection= jsection+1
- endif
-
- ENDDO
-
- data%State%MudSystem%NoHorizontalMudElements= jelement
-
-
-
-
- jmud= 1
- jsection= 2
-
- DO WHILE(jmud <= data%State%MudSystem%St_Mud_Forehead_X%Length() .and. jsection<=data%State%F_Counts%StringIntervalCounts)
-
- jelement= jelement+1
- data%State%MudSystem%TrueMinValue= min(data%State%MudSystem%St_Mud_Forehead_X%Array(jmud), data%State%MudSystem%Xend_PipeSection(jsection))
-
- call data%State%MudSystem%Xend_MudElement%Add(data%State%MudSystem%TrueMinValue)
- call TVD_Calculator(data%State%MudSystem%TrueMinValue,data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%TVDend_MudElement%Add(data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%Density_MudElement%Add(data%State%MudSystem%St_Density%Array(jmud))
- call data%State%MudSystem%PipeID_MudElement%Add(data%State%MudSystem%ID_PipeSectionInch(jsection))
- call data%State%MudSystem%PipeOD_MudElement%Add(data%State%MudSystem%OD_PipeSectionInch(jsection))
- !call Angle_MudElement%Add(Angle_PipeSection(jsection))
- call data%State%MudSystem%MudType_MudElement%Add(data%State%MudSystem%St_MudOrKick%Array(jmud))
-
-
- if (data%State%MudSystem%Xend_MudElement%Array(jelement)== data%State%MudSystem%St_Mud_Forehead_X%Array(jmud)) then
- jmud= jmud+1
- else
- jsection= jsection+1
- endif
-
- ENDDO
-
- data%State%MudSystem%NoStringMudElements= jelement- data%State%MudSystem%NoHorizontalMudElements
-
-
-
-
-
- jmud= 1
- jsection= data%State%F_Counts%StringIntervalCounts+1
- DO WHILE(jmud<= data%State%MudSystem%Ann_Mud_Forehead_X%Length() .and. jsection<=data%State%MudSystem%NoPipeSections)
-
- jelement= jelement+1
- data%State%MudSystem%TrueMinValue= max(data%State%MudSystem%Ann_Mud_Forehead_X%Array(jmud), data%State%MudSystem%Xend_PipeSection(jsection))
-
- call data%State%MudSystem%Xend_MudElement%Add(data%State%MudSystem%TrueMinValue)
- call TVD_Calculator(data%State%MudSystem%TrueMinValue,data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%TVDend_MudElement%Add(data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%Density_MudElement%Add(data%State%MudSystem%Ann_Density%Array(jmud))
- call data%State%MudSystem%PipeID_MudElement%Add(data%State%MudSystem%ID_PipeSectionInch(jsection))
- call data%State%MudSystem%PipeOD_MudElement%Add(data%State%MudSystem%OD_PipeSectionInch(jsection))
- !call Angle_MudElement%Add(Angle_PipeSection(jsection))
- call data%State%MudSystem%MudType_MudElement%Add(data%State%MudSystem%Ann_MudOrKick%Array(jmud))
-
-
- if (data%State%MudSystem%Xend_MudElement%Array(jelement)== data%State%MudSystem%Ann_Mud_Forehead_X%Array(jmud)) then
- jmud= jmud+1
- else
- jsection= jsection+1
- endif
-
- ENDDO
-
- do i= 2, data%State%MudSystem%Xend_MudElement%Length()
- if ( i== data%State%MudSystem%NoHorizontalMudElements+data%State%MudSystem%NoStringMudElements+1) then
- call data%State%MudSystem%Xstart_MudElement%Add (data%State%MudSystem%Ann_Mud_Backhead_X%Array(1)) ! start of annulus
- call TVD_Calculator(data%State%MudSystem%Ann_Mud_Backhead_X%Array(1),data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%TVDstart_MudElement%Add(data%State%MudSystem%MudCircVerticalDepth)
- elseif ( i== data%State%MudSystem%NoHorizontalMudElements+1 ) then
- call data%State%MudSystem%Xstart_MudElement%Add (data%State%MudSystem%St_Mud_Backhead_X%Array(1)) ! start of stirng
- call TVD_Calculator(data%State%MudSystem%St_Mud_Backhead_X%Array(1),data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%TVDstart_MudElement%Add(data%State%MudSystem%MudCircVerticalDepth)
- else
- call data%State%MudSystem%Xstart_MudElement%Add(data%State%MudSystem%Xend_MudElement%Array(i-1)) ! normal calculation
- call data%State%MudSystem%TVDstart_MudElement%Add(data%State%MudSystem%TVDend_MudElement%Array(i-1)) ! normal calculation
- endif
-
- enddo
-
- data%State%MudSystem%NoCasingMudElements = jelement- data%State%MudSystem%NoStringMudElements- data%State%MudSystem%NoHorizontalMudElements
-
-
- !=========================For Torque and Drag========================
- if (allocated(data%State%MudSystem%TDXstart_MudElementArray)) deallocate(data%State%MudSystem%TDXstart_MudElementArray)
- allocate(data%State%MudSystem%TDXstart_MudElementArray(data%State%MudSystem%NoHorizontalMudElements+data%State%MudSystem%NoStringMudElements+data%State%MudSystem%NoCasingMudElements))
- if (allocated(data%State%MudSystem%TDXend_MudElementArray)) deallocate(data%State%MudSystem%TDXend_MudElementArray)
- allocate(data%State%MudSystem%TDXend_MudElementArray(data%State%MudSystem%NoHorizontalMudElements+data%State%MudSystem%NoStringMudElements+data%State%MudSystem%NoCasingMudElements))
- if (allocated(data%State%MudSystem%TDDensity_MudElementArray)) deallocate(data%State%MudSystem%TDDensity_MudElementArray)
- allocate(data%State%MudSystem%TDDensity_MudElementArray(data%State%MudSystem%NoHorizontalMudElements+data%State%MudSystem%NoStringMudElements+data%State%MudSystem%NoCasingMudElements))
-
- data%State%MudSystem%TDNoHorizontalMudElements= data%State%MudSystem%NoHorizontalMudElements
- data%State%MudSystem%TDNoStringMudElements= data%State%MudSystem%NoStringMudElements
- data%State%MudSystem%TDNoCasingMudElements= data%State%MudSystem%NoCasingMudElements
-
-
- data%State%MudSystem%TDXstart_MudElementArray(:) = data%State%MudSystem%Xstart_MudElement%Array(:)
- data%State%MudSystem%TDXend_MudElementArray(:) = data%State%MudSystem%Xend_MudElement%Array(:)
- data%State%MudSystem%TDDensity_MudElementArray(:) = data%State%MudSystem%Density_MudElement%Array(:)
- !=====================================================================
-
-
- !do i=NoHorizontalMudElements+1, NoHorizontalMudElements+NoStringMudElements ! 2-string elements
- ! write(*,333) 'STRING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
- !enddo
-
-
-
- !================================================================
-
- ! Open Hole Mud Elements
- jopmud= 1
- jopsection= 1
- jopelement= 0 ! number of final mud elements
-
-
- call data%State%MudSystem%Xend_OpMudElement%Empty()
- call data%State%MudSystem%TVDend_OpMudElement%Empty()
- call data%State%MudSystem%Density_OpMudElement%Empty()
- call data%State%MudSystem%PipeID_OpMudElement%Empty()
- call data%State%MudSystem%PipeOD_OpMudElement%Empty()
- !call Angle_OpMudElement%Empty()
- call data%State%MudSystem%MudTypeOp_MudElement%Empty()
-
-
-
- DO WHILE(jopmud<= data%State%MudSystem%Op_Mud_Forehead_X%Length() .and. jopsection<=data%State%F_Counts%BottomHoleIntervalCounts)
-
- jopelement= jopelement+1
- data%State%MudSystem%TrueMinValue= max(data%State%MudSystem%Op_Mud_Forehead_X%Array(jopmud), data%State%MudSystem%Xend_OpSection(jopsection))
- call data%State%MudSystem%Xend_OpMudElement%Add(data%State%MudSystem%TrueMinValue)
- call TVD_Calculator(data%State%MudSystem%TrueMinValue,data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%TVDend_OpMudElement%Add(data%State%MudSystem%MudCircVerticalDepth)
- call data%State%MudSystem%Density_OpMudElement%Add(data%State%MudSystem%Op_Density%Array(jopmud))
- call data%State%MudSystem%PipeID_OpMudElement%Add(data%State%MudSystem%ID_OpSectionInch(jopsection))
- call data%State%MudSystem%PipeOD_OpMudElement%Add(data%State%MudSystem%OD_OpSectionInch(jopsection))
- !call Angle_MudElement%Add(Angle_PipeSection(jopsection))
- call data%State%MudSystem%MudTypeOp_MudElement%Add(data%State%MudSystem%Op_MudOrKick%Array(jopmud))
-
-
- if (data%State%MudSystem%Xend_OpMudElement%Array(jopelement)== data%State%MudSystem%Op_Mud_Forehead_X%Array(jopmud)) then
- jopmud= jopmud+1
- else
- jopsection= jopsection+1
- endif
-
- ENDDO
-
- do i= 2, data%State%MudSystem%Xend_OpMudElement%Length()
- call data%State%MudSystem%Xstart_OpMudElement%Add(data%State%MudSystem%Xend_OpMudElement%Array(i-1))
- call data%State%MudSystem%TVDstart_OpMudElement%Add(data%State%MudSystem%TVDend_OpMudElement%Array(i-1))
- enddo
-
- data%State%MudSystem%NoBottomHoleMudElements = jopelement
-
-
- !================================================================
-
-
-
- if(allocated(data%State%MudSystem%StringMudElement)) deallocate(data%State%MudSystem%StringMudElement)
- allocate(data%State%MudSystem%StringMudElement(data%State%MudSystem%NoStringMudElements))
-
- if(allocated(data%State%MudSystem%CasingMudElement)) deallocate(data%State%MudSystem%CasingMudElement)
- allocate(data%State%MudSystem%CasingMudElement(data%State%MudSystem%NoCasingMudElements+data%State%MudSystem%NoBottomHoleMudElements))
-
- data%State%MudSystem%istring=0
- data%State%MudSystem%icasing=0
-
- data%State%MudSystem%BitMudDensity= data%State%MudSystem%Density_MudElement%Array(data%State%MudSystem%NoHorizontalMudElements+data%State%MudSystem%NoStringMudElements) ! (for ROP module)
- !================================================================
- !============================ UTUBE =============================
-
- !IF (UtubePossibility== .true. .and. Get_KellyConnection() /= KELLY_CONNECTION_STRING .and. WellHeadIsOpen) THEN
- IF (data%State%MudSystem%UtubePossibility== .true. .and. data%State%TD_StConn%FluidStringConnectionMode==0 .and. data%State%MudSystem%WellHeadIsOpen .AND. NoGasPocket == 0) THEN
- CALL WellPressureDataTransfer
- !WRITE (*,*) ' U-Tube Done 1'
- CALL Utube
- !WRITE (*,*) ' U-Tube Done 2'
- if (UTUBEVARS%QUtubeInput> 0.0) call Utube1_and_TripIn
- if (UTUBEVARS%QUtubeOutput> 0.0) call Utube2_and_TripIn
- END IF
-
- !========================== UTUBE- end =========================
-
- ! do imud=1, st_MudDischarged_Volume%Length()
- ! write(*,*) 'st-plot:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud)
- !enddo
- !==================== Display ========================
- !do i=1, St_MudOrKick%Length()
- ! write(*,555) i,'St_Volume(i), type=' ,St_MudDischarged_Volume%Array(i),St_MudOrKick%Array(i)
- !
- ! IF (IEEE_Is_NaN(St_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in St Volume-Plot')
- ! IF (St_MudDischarged_Volume%Array(i)<0.) call ErrorStop('St Volume <0' , St_MudDischarged_Volume%Array(i))
- !enddo
-
-
- IF (ANY(IEEE_Is_NaN(data%State%MudSystem%Op_MudDischarged_Volume%Array(:))) .OR. ANY(data%State%MudSystem%Op_MudDischarged_Volume%Array(:) <= 0.0)) THEN
- do i = 1 , data%State%MudSystem%Op_MudOrKick%Length()
- write(*,555) i,'Op_Volume(i), type=' ,data%State%MudSystem%Op_MudDischarged_Volume%Array(i) , data%State%MudSystem%Op_MudOrKick%Array(i) , data%State%MudSystem%Op_Density%Array(i)
- end do
- call ErrorStop('NaN in Op Volume-Plot or Op Volume <=0')
- END IF
-
-
- IF (ANY(IEEE_Is_NaN(data%State%MudSystem%Ann_MudDischarged_Volume%Array(:))) .OR. ANY(data%State%MudSystem%Ann_MudDischarged_Volume%Array(:) <= 0.0)) THEN
- do i = 1 , data%State%MudSystem%Ann_MudOrKick%Length()
- write(*,555) i,'Ann_Volume(i), type=' ,data%State%MudSystem%Ann_MudDischarged_Volume%Array(i) , data%State%MudSystem%Ann_MudOrKick%Array(i) , data%State%MudSystem%Ann_Density%Array(i)
- end do
- call ErrorStop('NaN in Ann Volume-Plot or Ann Volume <=0')
- END IF
-
- !do i=1, Ann_MudOrKick%Length()
- ! !write(*,555) i,'Ann_Volume(i), type=' ,Ann_MudDischarged_Volume%Array(i),Ann_MudOrKick%Array(i),Ann_Density%Array(i)
- !
- ! IF (IEEE_Is_NaN(Ann_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in Ann Volume-Plot')
- ! IF (Ann_MudDischarged_Volume%Array(i)<=0.) call ErrorStop('Ann Volume <=0' , Ann_MudDischarged_Volume%Array(i))
- !enddo
-
- 555 FORMAT(I3,5X,A42,(f12.5),5X,I3,5X,(f12.5))
-
- data%State%MudSystem%NoStringMudElementsForPlot= data%State%MudSystem%NoStringMudElements
-
- ! 1-Horizontal Mud Elements are not shown
- !write(*,333) 'Horiz:', 1,'Xstart\=', Xstart_MudElement%Array(1), 'Xend=' , Xend_MudElement%Array(1), 'Density=' , Density_MudElement%Array(1), 'MudType=' , MudType_MudElement%Array(1)
-
- do i=data%State%MudSystem%NoHorizontalMudElements+1, data%State%MudSystem%NoHorizontalMudElements+data%State%MudSystem%NoStringMudElements ! 2-string elements
- if (data%State%MudSystem%Xend_MudElement%Array(i) <= 0.0) then
- data%State%MudSystem%NoStringMudElementsForPlot= data%State%MudSystem%NoStringMudElementsForPlot-1
- cycle
- endif
- data%State%MudSystem%istring= data%State%MudSystem%istring+1
- data%State%MudSystem%StringMudElement(data%State%MudSystem%istring)%StartMd = data%State%MudSystem%Xstart_MudElement%Array(i)
- data%State%MudSystem%StringMudElement(data%State%MudSystem%istring)%EndMd = data%State%MudSystem%Xend_MudElement%Array(i)
- !StringMudElement(istring)%Id = PipeID_MudElement%Array(i)
- !StringMudElement(istring)%Od = PipeOD_MudElement%Array(i)
- data%State%MudSystem%StringMudElement(data%State%MudSystem%istring)%Density = data%State%MudSystem%Density_MudElement%Array(i)
-
- if (data%State%MudSystem%MudType_MudElement%Array(i) == 104) then
- data%State%MudSystem%MudType_MudElement%Array(i)= 4 ! air
- elseif (data%State%MudSystem%MudType_MudElement%Array(i) > 0 .and. data%State%MudSystem%MudType_MudElement%Array(i) < 100) then ! all kicks
- data%State%MudSystem%MudType_MudElement%Array(i)= 1 ! gas kick
- endif
-
- data%State%MudSystem%StringMudElement(data%State%MudSystem%istring)%MudType = data%State%MudSystem%MudType_MudElement%Array(i)
- !write(*,333) 'STRING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
- enddo
-
-
-
- do i=data%State%MudSystem%Xend_MudElement%Length(), data%State%MudSystem%NoHorizontalMudElements+data%State%MudSystem%NoStringMudElements+1 , -1 ! 3-casing elements
- data%State%MudSystem%icasing= data%State%MudSystem%icasing+1
- data%State%MudSystem%CasingMudElement(data%State%MudSystem%icasing)%StartMd = data%State%MudSystem%Xend_MudElement%Array(i)
- data%State%MudSystem%CasingMudElement(data%State%MudSystem%icasing)%EndMd = data%State%MudSystem%Xstart_MudElement%Array(i)
- !CasingMudElement(icasing)%Id = PipeID_MudElement%Array(i)
- !CasingMudElement(icasing)%Od = PipeOD_MudElement%Array(i)
- !write(*,333) 'CASING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
- !call Log_1(temp1)
- !write(*,444) 'CASING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'PipeID_MudElement%Array(i)=' , PipeID_MudElement%Array(i), 'PipeOD_MudElement%Array(i)=' , PipeOD_MudElement%Array(i)
- data%State%MudSystem%CasingMudElement(data%State%MudSystem%icasing)%Density = data%State%MudSystem%Density_MudElement%Array(i)
-
- if (data%State%MudSystem%MudType_MudElement%Array(i) == 104) then
- data%State%MudSystem%MudType_MudElement%Array(i)= 4 ! air
- elseif (data%State%MudSystem%MudType_MudElement%Array(i) > 0 .and. data%State%MudSystem%MudType_MudElement%Array(i) < 100) then
- data%State%MudSystem%MudType_MudElement%Array(i)= 1 ! gas kick
- endif
-
- data%State%MudSystem%CasingMudElement(data%State%MudSystem%icasing)%MudType = data%State%MudSystem%MudType_MudElement%Array(i)
-
- enddo
-
- do i= data%State%MudSystem%NoBottomHoleMudElements, 1 , -1 ! 4-open hole elements
- data%State%MudSystem%icasing= data%State%MudSystem%icasing+1
- data%State%MudSystem%CasingMudElement(data%State%MudSystem%icasing)%StartMd = data%State%MudSystem%Xend_OpMudElement%Array(i)
- data%State%MudSystem%CasingMudElement(data%State%MudSystem%icasing)%EndMd = data%State%MudSystem%Xstart_OpMudElement%Array(i)
- !CasingMudElement(icasing)%Id = PipeID_OpMudElement%Array(i)
- !CasingMudElement(icasing)%Od = PipeOD_OpMudElement%Array(i)
- !write(*,333) 'OpenHole:',i,'Xstart\=', Xstart_OpMudElement%Array(i), 'Xend=' , Xend_OpMudElement%Array(i), 'Density=' , Density_OpMudElement%Array(i), 'MudType=' , MudTypeOp_MudElement%Array(i)
- !call Log_1(temp2)
- !write(*,444) 'OpenHole:',i,'Xstart\=', Xstart_OpMudElement%Array(i), 'Xend=' , Xend_OpMudElement%Array(i), 'PipeID_MudElement%Array(i)=' , PipeID_MudElement%Array(i), 'PipeOD_MudElement%Array(i)=' , PipeOD_MudElement%Array(i)
- data%State%MudSystem%CasingMudElement(data%State%MudSystem%icasing)%Density = data%State%MudSystem%Density_OpMudElement%Array(i)
-
- if (data%State%MudSystem%MudTypeOp_MudElement%Array(i) == 104) then
- data%State%MudSystem%MudTypeOp_MudElement%Array(i)= 4 ! air
- elseif (data%State%MudSystem%MudTypeOp_MudElement%Array(i) > 0 .and. data%State%MudSystem%MudTypeOp_MudElement%Array(i) < 100) then
- data%State%MudSystem%MudTypeOp_MudElement%Array(i)= 1 ! gas kick
- endif
-
- data%State%MudSystem%CasingMudElement(data%State%MudSystem%icasing)%MudType = data%State%MudSystem%MudTypeOp_MudElement%Array(i)
- enddo
-
-
-
- 333 FORMAT(A10,I3,5X,A8,(f12.5),5X,A8,(f12.5),5X,A8,(f12.5),5X,A8,I3)
- 444 FORMAT(A10,I2,5X,A8,(f12.3),5X,A8,(f12.3),5X,A8,(f12.3),5X,A8,(f12.3))
-
-
-
- ! shomare gozari be tartib HZ mud, ST mud, Casing
- ! shomare gzari OpenHole jodagane ast az 1
-
- call SetStringFluids(data%State%MudSystem%NoStringMudElementsForPlot, data%State%MudSystem%StringMudElement) !for data display in string
- call SetAnnalusFluids(data%State%MudSystem%NoCasingMudElements+data%State%MudSystem%NoBottomHoleMudElements, data%State%MudSystem%CasingMudElement) !for data display in casing
-
-
- !===========================================================================================================================
- !===========================================================================================================================
-
-
- end subroutine PlotFinalMudElements
-
-
-
|