|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180 |
- MODULE BopVariables
- use DynamicDoubleArray, only:DynamicDoubleArrayType
- IMPLICIT NONE
-
-
-
-
- !===========================================================================
- ! INPUT VARIABLES
- !===========================================================================
- type :: BopStackInputType
- REAL,ALLOCATABLE:: MINORS1(:,:),PIPINGS_RAMLINE(:,:),MINORS_ANNULAR(:,:),PIPINGS_ANNULAR(:,:),PIPINGS_AIRPUMP(:,:),MINORS_AIRPUMP(:,:)
- integer AnnularOpenLedMine,AnnularCloseLedMine,UpperRamsCloseLEDMine,UpperRamsOpenLEDMine,LowerRamsOpenLEDMine,LowerRamsCloseLEDMine
- integer MiddleRamsOpenLEDMine,MiddleRamsCloseLEDMine,KillLineOpenLedMine,KillLineCloseLedMine,ChokeLineOpenLEDMine,ChokeLineCloseLEDMine
- integer BOP_timeCounter
- end type BopStackInputType
- !===========================================================================
- ! ACC. VARIABLES
- !===========================================================================
- REAL,PARAMETER :: PressureDifferenceSteps = 20. ,BaseDifferenceP= 200. ! psi
- type::BopStackAccType
- REAL FVR_TOT,BOTTLE_CAPACITY,PRAMS_REGSET,acc_ChargedPressure,acc_MinPressure,ACC_PRECHARGE,ByPassOld
- REAL pram_reg,test1,test2,test3,test4,test5,test6,test7,test8,test9,ax,bx
- integer NOBOTTLES,AccPupmsFailMalf,AirSupplyPressureGaugeMalf,ManifoldPressureGaugeMalf,AccumulatorPressureGaugeMalf,RigAirMalf
- real Cumulative_AirVolume, PressureDifference
- integer SoundKoomeyAirPump
- end type BopStackAccType
- !===========================================================================
-
- ! RAM LINE COMPUTATIONAL VARIABLES
- !===========================================================================
- type:: RamLineType
- logical ShearRamIsClosing,ShearRamIsOpening
- REAL ShearRamsLeverOld,NoActiveRmas
- !REAL checkp,p_acccheck
- REAL P_ACC,FVR,DeltaT_BOP
- REAL diffp_air,losses_air,Qup,kinetic_air,pipe_loss1air,minor_loss1air,static_loss1air!,pipe_loss1_before,minor_loss1,static_loss1,kinetic_loss1,pipe_loss1
- !REAL loss_before,pipe_loss2,minor_loss2,deltah,static_loss2,kinetic_loss2,loss_after
- integer AIRP_SWITCH,ELECP_SWITCH,ShearBop_closed,FINISHED_shear,EOF,NO_MINORSRAMLINE,NO_PIPINGSRAMLINE,NO_PIPINGS_AIRPLINE,NO_MINORS_AIRPLINE
- integer counter,iteration,ShearBop_Situation_forTD
- real BA1,BA2,BA3,BA4,BBA1,BBA2,BBA3,BBA4
- REAL B1,B2,B3,B4
- REAL,ALLOCATABLE:: Re_air(:),DIAM_AIR_MM(:),DIAM_AIR_INCH(:),AREA_AIR(:),REL_ROUGHAIR(:),LENGT_AIR(:),LF_AIR(:),CV_AIR(:),NOTE_AIR(:)
- REAL,ALLOCATABLE:: fric_air(:),fricloss_air(:),minlosspa_air(:),minloss_air(:)
- REAL,ALLOCATABLE:: MINORDIAM_AIR_INCH(:),MINORAREA_AIR(:)
- REAL,ALLOCATABLE:: DIAM_RAMLINE_INCH(:),DIAM_RAMLINE_MM(:),AREA_RAMLINE(:),ROUGHNESS_AIRPLINE(:),ROUGHNESS_RAMLINE(:),RELROUGH_RAMLINE(:),LENGT_RAMLINE(:),LF_RAMLINE(:),CV_RAMLINE(:),NOTE_RAMLINE(:),AREAMINOR_RAMLINE(:)
- !REAL,ALLOCATABLE:: Re_ramline(:),fric(:),fricloss(:)
- REAL,ALLOCATABLE:: MINORDIAMETER_RAMLINE(:)
- INTEGER,ALLOCATABLE:: ITEM(:),ITEM_PIPING(:),ITEM_PIPINGAIR(:),ITEM_MINORAIR(:)
- CHARACTER,ALLOCATABLE:: DECRIPTION(:),DECRIPTION2(:),DECRIPTION_RAM(:),DESCRIPTION_AIR1(:),DESCRIPTION_AIR2(:)
- real:: counter_airp,pacc_before
- integer Annular_active,ShearBop_active,PipeRam1_active,PipeRam2_active,ChokeLine_active,KillLine_active
- end type RamLineType
-
- !===========================================================================
- ! ANNULAR PREVENTER COMPUTATIONAL VARIABLES
- !===========================================================================
- type::AnnularComputationalType
- integer PannularTimeStepDelay
- type(DynamicDoubleArrayType) :: Pannular_regDelay
- logical AnnPressureRise
- integer NO_MinorsAnnularLine,NO_PipingsAnnularLine,RamsFirstSet
- REAL pa_annular,p_annular
- REAL,ALLOCATABLE:: MINORDIAMETER_ANNULARLINE(:),AREAMINOR_ANNULARLINE(:)
- !REAL,ALLOCATABLE:: REAL_PregAnnular(:),real_IDAnnular(:),real_pAnnular(:)
- REAL REAL_PregAnnular,real_IDAnnular,real_pAnnular
- REAL,ALLOCATABLE:: LF_ANNULARLINE(:),CV_ANNULARLINE(:),NOTE_ANNULARLINE(:),minlosspa_ANNULAR(:),minloss_ANNULAR(:)
- REAL,ALLOCATABLE:: DIAM_ANNULARLINE_INCH(:),DIAM_ANNULARLINE_MM(:),AREA_ANNULARLINE(:)
- REAL,ALLOCATABLE:: LENGT_ANNULARLINE(:),ROUGHNESS_ANNULARLINE(:),RELROUGH_ANNULARLINE(:),Re_ANNULARline(:),fricANNULAR(:),friclossANNULAR(:)
- INTEGER,ALLOCATABLE:: ITEMANNULAR(:),ITEM_PIPINGANNULAR(:)
- CHARACTER,ALLOCATABLE:: DECRIPTIONANNULAR(:),DECRIPTION2ANNULAR(:),DECRIPTION_ANNULAR(:)
- REAL WellBorePressure,acoef,Bcoef,const,AnnularSealingPressure,AnnularMovingPressure
- end type AnnularComputationalType
- !===========================================================================
- ! ANNULAR PREVENTER VARIABLES
- !===========================================================================
- type :: AnnularType
- REAL (8) Pannular_reg
- real Pannular_regset
- logical AnnularIsClosing,AnnularIsOpening
- REAL tolAnnular,tolzeroAnnular
- integer Annular_closed,finished_Annular,FirstSet,AnnularFailureMalf,AnnularLeakMalf,AnnularPressureGaugeMalf,Annular_Situation_forTD
- REAL AnnularLeverOld,H_AnnularBop,IDAnnular,AbopAnnular,ODDrillpipe_inAnnular,IDAnnularBase,ODDrillpipe_inAnnularBase
- REAL NeededVolumeAnnular
- end type AnnularType
- !===========================================================================
- ! PIPE RAMS 1 VARIABLES
- !===========================================================================
- type::PipeRams1Type
- logical IsClosing,IsOpening
- REAL PipeRams1DotLeverOld,H
- REAL NeededVolume,A,IDBase,ID,ODDrillpipe_in,ODDrillpipe_inBase
- integer closed,finished,UpperRamsFailureMalf,UpperRamsLeakMalf,Situation_forTD
- ! REAL real_ID
- end type PipeRams1Type
- !============================================================================
- ! SHEAR RAM BOP VARIABLES
- !============================================================================
- type:: ShearRamType
- REAL PA,PB,P_SHEAR,VA,VB,RAM_COURSE,H_REGRAM,H_ShearRamBop
- REAL,ALLOCATABLE:: ALPHA_QRAM(:),ALPHA_VDISRAM(:),ALPHA_PACC(:),ALPHA_PREGRAM(:),ALPHA_PBOP(:)
- !REAL,ALLOCATABLE:: REAL_TIME(:),REAL_QRAM(:),REAL_VDISRAM(:),REAL_PACC(:),REAL_PREGRAM(:),REAL_PBOP(:),real_IDshearBop(:)
- REAL REAL_TIME,REAL_QRAM,REAL_VDISRAM,REAL_PACC,REAL_PREGRAM,REAL_PBOP,real_IDshearBop
- REAL IDshearBopBase,IDshearBop,ODDrillpipe_inShearRam,AbopShearRam,NeededVolumeShearRams,ODDrillpipe_inShearRamBase
- Real IDshearBopFinal,IDPipeRam1Final,IDPipeRam2Final,IDAnnularFinal,OpenArea_shearBop,OpenArea_PipeRam1,OpenArea_PipeRam2,OpenArea_Annular
- Real MinimumOpenArea_InBOP
- integer MiddleRamsFailureMalf,MiddleRamsLeakMalf,ShearIsNotAllowed
- end type ShearRamType
- !===========================================================================
- ! PIPE RAMS 2 VARIABLES
- !===========================================================================
- type::PipeRam2Type
- logical IsClosing,IsOpening
- REAL LeverOld,H_Bop
- REAL NeededVolume,ID,ODDrillpipe_in,ODDrillpipe_inBase
- integer closed,finished,LowerRamsFailureMalf,LowerRamsLeakMalf,Situation_forTD
- !REAL,ALLOCATABLE:: real_IDPipeRam2(:)
- REAL real_ID
- end type PipeRam2Type
- !===========================================================================
- ! CHOKE LINE VARIABLES
- !===========================================================================
- type::ChokeLineType
- logical IsClosing,IsOpening
- REAL LeverOld,H_Bop
- REAL NeededVolume,Abop,ID,ODDrillpipe_in,IDBase,ODDrillpipe_inBase
- integer closed,finished
- !REAL,ALLOCATABLE:: real_IDPipeRam1(:)
- REAL real_ID
- end type ChokeLineType
- !===========================================================================
- ! KILL LINE VARIABLES
- !===========================================================================
- type::KillLineType
- logical IsClosing,IsOpening
- REAL LeverOld,H_Bop
- REAL NeededVolume,Abop,ID,ODDrillpipe_in,IDBase,ODDrillpipe_inBase
- integer closed,finished
- !REAL,ALLOCATABLE:: real_IDPipeRam1(:)
- REAL real_ID
- end type KillLineType
- !============================================================================
- ! OIL & ENVIRONMENT VARIABLES
- !============================================================================
- ! REAL:: SG=1.12,WDENS=1000,GRAVITY=9.81,RE_CR=2000
- !specific gravity of liquid
- !water density(kg/m^3)
- !============================================================================
- ! PUMP VARIABLES
- !============================================================================
- type::PumpsType
- REAL P_AIRP,DELTAV_AIR,TOL_AIR,DELTAV_ELECP,Qiter
- REAL ELECTRIC_ON,ELECTRIC_OFF,AIR_ON,AIR_OFF,QAIR,QELECTRIC
- !REAL,ALLOCATABLE:: alpha_Qair(:),alpha_timeair(:),alpha_paccair(:),alpha_pairp(:),alpha_diffpair(:),alpha_lossesair(:),alpha_fvrair(:)
- REAL alpha_Qair,alpha_timeair,alpha_paccair,alpha_pairp,alpha_diffpair,alpha_lossesair,alpha_fvrair
- logical SoundKoomeyElectric
- end type PumpsType
-
- !=================================================================================
-
- TYPE, PUBLIC :: BOP_TypeVars
- REAL vdis_tot,vdis_bottles,deltav_bottles,fvr_air,vdis_elecp,Qzero,Q,flow,tol,TIME,timecounter_ram,clock
- integer bop_type, SuccessionCounter, SuccessionCounterOld,First_CloseTimecheck,First_OpenTimecheck,FourwayValve ! FourwayValve 1: Open , 0: Close
- REAL loss_before,pipe_loss2,minor_loss2,deltah,static_loss2,kinetic_loss2,loss_after,TOLZERO,diffp_ram
- REAL checkp,p_acccheck,P_BOP,minor_loss1,static_loss1,kinetic_loss1,pipe_loss1
- Logical Bottles_Charged_MalfActive
- END TYPE BOP_TypeVars
-
- ! 1 : Annular (RNUMBER)
- ! 2 : PipeRam1 (RNUMBER)
- ! 3 : PipeRam2 (RNUMBER)
- ! 4 : ShearRam (RNUMBER)
- ! 5 : ChokeLine (RNUMBER)
- ! 6 : KillLine (RNUMBER)
-
- TYPE, PUBLIC :: BOP_TypeVars2D
- REAL, ALLOCATABLE:: minlosspa(:,:),minloss(:,:)
- REAL,ALLOCATABLE:: Re_ramline(:,:),fric(:,:),fricloss(:,:)
- END TYPE BOP_TypeVars2D
- END MODULE
|