|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906 |
- module Simulator
- use IFPORT
- use RedisInterface
- use Bop
- use PumpsMain
- use RopMain
- use RotaryTableMain
- use DrawworksMain
- use FluidFlowMain
- use TorqueDragMain
- use MudSystemMain
- use PipeRams1Main
- use PipeRams2Main
- use KillLineMain
- use ChokeLineMain
- use BlindRamsMain
- use AnnularMain
- use TopDriveMain
- use CManifolds
- use GeoMain
- use ChokeControlMain
- use COperationScenariosMain
-
- ! For Json read and write
- use CStringConfiguration
- use CFormation
- use CReservoir
- use CShoe
- use CAccumulator
- use CBopStack
- use CHoisting
- use CPower
- use CPumpsVariables
- use CRigSize
- use CCasingLinerChoke
- use CPathGeneration
- use CWellSurveyData
- use MudPropertiesModule
-
- use CBitProblems
- use CBopProblems
- use CChokeProblems
- use CDrillStemProblems
- use CGaugesProblems
- use CHoistingProblems
- use CKickProblems
- use CLostProblems
- use CMudTreatmentProblems
- use COtherProblems
- use CPumpProblems
- use CRotaryProblems
- use OperationScenariosModule
- use PermissionsModule
- use UnitySignalsModule
- use CBopControlPanel
- use CChokeControlPanel
- use CChokeManifold
- use CDataDisplayConsole
- use CDrillingConsole
- use CHook
- use CStandPipeManifold
- use CTopDrivePanel
- use DrillingWatchModule
- use CTanks
- use UnityModule
- use COperationScenariosSettings
- use DownHoleModule
-
- use iso_c_binding, only: c_char,c_ptr,c_loc
-
- implicit none
- type(json_core):: jsoncore
- integer :: simulationStatus,simulationSpeed,msPerStep,simulationEnd,simulationStep
- logical::Kelly_ConnectionNothing_in_progress=.false.
- character(len=:),allocatable::redisInput,operationScenarioEvent,stateStr
- character(kind=c_char,len=:),allocatable,target::redisOutput
- type(c_ptr) :: c_string_ptr
-
- character(len=100)::simulationId
-
- enum, bind(c)
- enumerator :: PLAY = 1
- enumerator :: PAUSE = 2
- enumerator :: STOP = 3
- enumerator :: PLAY_TO_DETERMINED_TIME = 4
- enumerator :: LOAD_STATE = 5
- end enum
-
- contains
- FUNCTION time_ms()
- INTEGER(8) :: time_ms
- integer,dimension(8)::timearray
- call date_and_time(values=timearray)
- time_ms = timearray(8)+timearray(7)*1000 + timearray(6)*60000 + timearray(5)*60000*600000 +timearray(4)*24*60000*60000
- RETURN
- END FUNCTION
-
- subroutine Simulate(redis_host,redis_port,redis_password, sim_id,stepTime,print_freq)
- character(len=*) :: redis_host,redis_password, sim_id
- integer::t0,t1,t2,t3,t_read=0,t_write=0,t_exec=0,i,status,redis_port,stepTime,print_freq
- integer(8),dimension(12)::t,t_modules
- !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
- simulationId = sim_id
- do i=1,size(t_modules)
- t_modules(i)=0
- end do
- ! call initSimulation(configFilename)
- call initConnection(redis_host,redis_port,redis_password, sim_id,status)
- allocate(character(len=30000) :: redisOutput)
- if (status<0) then
- print *,"Can not init connection to redis."
- stop
- endif
-
- call read_configuration()
- if(simulationStatus==LOAD_STATE) then
- call readState()
- endif
- ! call read_variables()
- print *,"connection initialized"
- call init_modules()
- print *,"modules initialized"
- ! call cpu_time(T1)
- simulationStep = 1
- !$omp parallel sections
-
- !$omp section
- call listenToChannel()
-
- !$omp section
- do while (.true.)
- if(mod(simulationStep,print_freq)==0) then
- print_log=.true.
- else
- print_log=.false.
- endif
- if(mod(simulationStep,10)==0) call publishMessageToChannel("ack")
- ! if(simulationStep>100) exit
- t0 = time_ms()
- if(print_log) print *,"simulationStep = ",simulationStep
- call read_variables()
- if(simulationStatus==PLAY_TO_DETERMINED_TIME .and. simulationStep>simulationEnd) exit
- if(simulationStatus==STOP) exit
- if(simulationStatus==PAUSE) then
- if(print_log) print *, "Paused"
- call sleepqq(stepTime)
- go to 211
- endif
- t1 = time_ms()
- t_read = t_read+t1-t0
- ! call logg(4,"read completed")
-
- !! Rafiee, nothing changed
- call BopStack_Step()
- t(1) = time_ms()
- t_modules(1) = t_modules(1)+t(1)-t1
-
- !! Tarmigh, now is rewritten
- call Pumps_MainSolver()
- t(2) = time_ms()
- t_modules(2) = t_modules(2)+t(2)-t(1)
- !call Pump2_Step()
- !! Rafiee
- call ChokeControl_Step()
- t(3) = time_ms()
- t_modules(3) = t_modules(3)+t(3)-t(2)
-
- !! Tarmigh, now is rewritten
- call RotaryTable_Step()
- t(4) = time_ms()
- t_modules(4) = t_modules(4)+t(4)-t(3)
-
- !! Tarmigh, now is rewritten
- call Drawworks_Step()
- t(5) = time_ms()
- t_modules(5) = t_modules(5)+t(5)-t(4)
-
- !! Rafiee
- call MudSystem_Step()
-
- !! Rafiee
- call PipeRams1_Step()
- call PipeRams2_Step()
-
- !! Rafiee
- call KillLine_Step()
- t(6) = time_ms()
- t_modules(6) = t_modules(6)+t(6)-t(5)
-
- !! Rafiee
- call ChokeLine_Step()
- t(7) = time_ms()
- t_modules(7) = t_modules(7)+t(7)-t(6)
-
- call BlindRams_Step()
- t(8) = time_ms()
- t_modules(8) = t_modules(8)+t(8)-t(7)
-
- call Annular_Step()
- t(9) = time_ms()
- t_modules(9) = t_modules(9)+t(9)-t(8)
-
- !!Tarmigh. Step must rewrittem
- call TopDrive_Step()
- t(10) = time_ms()
- t_modules(10) = t_modules(10)+t(10)-t(9)
-
- ! call Geo_Step()
- !!Ahmadi
- call PathFinding_Step()
- t(11) = time_ms()
- t_modules(11) = t_modules(11)+t(11)-t(10)
-
- !! Ahmadi
- call OperationScenarios_Step()
- !! Sheikh
- call FluidFlow_Step()
- !! Write variables to shared files
- t2 = time_ms()
- ! stepTime = t2-t1
- t_modules(12) = t_modules(12)+t2-t(11)
-
- t_exec = t_exec+t2-t1
- ! call date_and_time(values=timearray)
- ! t0 = time_ms()
- call write_variables()
- t3 = time_ms()
- if(t3-t0 < stepTime) then
- call sleepqq(stepTime-t3+t0)
- else
- print *,"Simulation step can not be complete in 100 ms. step time=",t3-t0
- endif
- t_write = t_write+t3-t2
- ! print *,"write completed"
- ! print *,"t=",t
- simulationStep = simulationStep + 1
- 211 end do
- !$omp end parallel sections
-
- ! call write_variables()
- ! call json%print(jsonroot,'test.json')
- ! call json%destroy(jsonroot)
- do i=1,size(t)
- print *,"t_modules(",i,")=",t_modules(i)
- end do
- print *,"Number of steps =",simulationStep-1
- print *,"Read Time (from redis) =",t_read
- print *,"Write Time (to redis)=",t_write
- print *,"Simulation Time =",t_exec
- print *,"Total Time =",t_read+t_write+t_exec
- end subroutine Simulate
-
-
- subroutine write_variables()
- use json_module
- implicit none
- type(json_value),pointer :: jsonroot
- character(len=10)::str
- type(json_value),pointer :: p
-
- call jsoncore%initialize()
- call jsoncore%create_object(jsonroot,'')
- call jsoncore%add(jsonroot,'step',simulationStep)
- call WarningsToJson(jsonroot)
- ! call ProblemsToJson(jsonroot)
- call EquipmentsToJson(jsonroot)
- ! call StateToJson(jsonroot)
-
- ! some data from state
- call jsoncore%create_object(p,'State')
- call ManifoldToJson(p)
- call notificationsToJson(p)
- call UnitySignalsToJson(p)
- call jsoncore%add(jsonroot,p)
-
- call jsoncore%print_to_string(jsonroot,redisInput)
- if(log_level>4) then
- write(str, '(I0)') len(redisInput)
- print *,"Writing to redis:"//trim(str)
- endif
-
- call setData(redisInput)
- ! nullify(redisContent)
- ! deallocate(redisContent)
- ! call json%destroy(pval)
- call jsoncore%destroy(jsonroot)
- ! print *,"write ends"
- end subroutine
-
- subroutine readState()
- ! type(json_value),pointer :: jsonroot,pval
- type(json_file) :: jsonfile
- type(json_core)::json
- integer::len
- ! logical::is_found
-
- c_string_ptr = c_loc(redisOutput)
- call getData2_C(c_string_ptr,len)
-
- call jsonfile%initialize()
- call jsonfile%get_core(json)
- call jsonfile%deserialize(redisOutput(1:len))
-
-
- ! ! call OperationScenarioFromJson(jsonfile)
- ! call notificationsFromJson(jsonfile)
- ! call permissionsFromJson(jsonfile)
- ! call unitySignalsFromJson(jsonfile)
- ! call StudentStationFromJson(jsonfile)
- ! call BopStackInputFromJson(jsonfile)
- ! call BopStackAccFromJson(jsonfile)
- ! call RamLineFromJson(jsonfile)
- ! call AnnularComputationalFromJson(jsonfile)
- ! call AnnularFromJson(jsonfile)
- ! call PipeRam1FromJson(jsonfile)
- ! call ShearRamFromJson(jsonfile)
- ! call PipeRam2FromJson(jsonfile)
- ! call ChokeLineFromJson(jsonfile)
- ! call KillLineFromJson(jsonfile)
- ! call PumpsFromJson(jsonfile)
- ! call RAMFromJson(jsonfile)
- ! call RAMSFromJson(jsonfile)
- ! call ChokeFromJson(jsonfile)
- ! call AirDrivenPumpFromJson(jsonfile)
- ! call AirPumpLineFromJson(jsonfile)
- ! call CHOOKEFromJson(jsonfile)
- ! call DrawworksFromJson(jsonfile)
- ! call MudSystemFromJson(jsonfile)
- ! call MUDFromJson(jsonfile)
- ! call MPumpsFromJson(jsonfile)
- ! call PUMPFromJson(jsonfile)
- ! call RTableFromJson(jsonfile)
- ! call TDSFromJson(jsonfile)
- ! call GasType(3)FromJson(jsonfile)
- ! call PressureDisplayFromJson(jsonfile)
- ! call FricPressDropFromJson(jsonfile)
- ! call ROP_SpecFromJson(jsonfile)
- ! call ROP_BitFromJson(jsonfile)
- ! call TDGeoFromJson(jsonfile)
- ! call F_String(:)FromJson(jsonfile)
- ! call F_CountsFromJson(jsonfile)
- ! call F_Interval(:)FromJson(jsonfile)
- ! call OD_Annulus(4)FromJson(jsonfile)
- ! call TD_DrillStemFromJson(jsonfile)
- ! call TD_DrillStemsFromJson(jsonfile)
- ! call TD_StringFromJson(jsonfile)
- ! call TD_CountFromJson(jsonfile)
- ! call G_StringElementFromJson(jsonfile)
- ! call TD_VolFromJson(jsonfile)
- ! call TD_GeneralFromJson(jsonfile)
- ! call TD_BOPFromJson(jsonfile)
- ! call TD_BOPElement(4)FromJson(jsonfile)
- ! call TD_StConnFromJson(jsonfile)
- ! call TD_LoadFromJson(jsonfile)
- ! call TD_WellElFromJson(jsonfile)
- ! call TD_CasingFromJson(jsonfile)
- ! call TD_LinerFromJson(jsonfile)
- ! call TD_OpenHoleFromJson(jsonfile)
- ! call TD_ROPHoleFromJson(jsonfile)
- ! call TD_WellGeneralFromJson(jsonfile)
- ! call TD_WellGeo(:)FromJson(jsonfile)
-
- call jsonfile%destroy()
- end subroutine
-
- subroutine read_configuration()
- type(json_value),pointer :: jsonroot,pval
- type(json_file) :: jsonfile
- type(json_core)::json
- integer::len
- ! character(len=:),allocatable::redisOutput
- ! call getData3(simulationId,redisOutput)
- c_string_ptr = c_loc(redisOutput)
- call getData2_C(c_string_ptr,len)
- ! print *,len(redisOutput)," bytes read from redis"
- ! open(1,file="redisContent.json",status="REPLACE")
- ! write(1,"(A)") redisOutput
- ! close(1)
-
- call jsonfile%initialize()
- call jsonfile%get_core(json)
- call jsonfile%deserialize(redisOutput(1:len))
- call jsonfile%json_file_get_root(jsonroot)
- ! call json%info(jsonvalue, n_children=n_children)
- ! print *,"n_children =",n_children
- call json%get(jsonroot,'status',pval)
- call json%get(pval,simulationStatus)
- call json%get(jsonroot,'speed',pval)
- call json%get(pval,simulationSpeed)
- if(simulationSpeed==0) simulationSpeed = 1
- msPerStep = 100/simulationSpeed
- call json%get(jsonroot,'endstep',pval)
- call json%get(pval,simulationEnd)
- call ConfigurationFromJson(jsonfile)
- call jsonfile%destroy()
- end subroutine
-
- subroutine read_variables()
- type(json_value),pointer :: jsonroot,pval
- type(json_file) :: jsonfile
- type(json_core)::json
- integer::stat,leng
- logical::found
-
- c_string_ptr = c_loc(redisOutput)
- call getData2_C(c_string_ptr,leng)
- ! open(1,file="redisContent.json",status="REPLACE")
- ! write(1,"(A)") redisOutput
- ! close(1)
- call jsonfile%initialize()
- call jsonfile%get_core(json)
- call jsonfile%deserialize(redisOutput(1:leng))
- call jsonfile%json_file_get_root(jsonroot)
- call jsonfile%get('status',stat,found)
- if (stat==0) then
- if(print_log) print *,"Status is oddly zero"
- return
- endif
- simulationStatus = stat
-
- ! call jsonfile%get('OperationScenarioEvent',operationScenarioEvent,found)
- ! if ( .not. found .and. print_log) print *,"Not found: operationScenarioEvent"
-
- call json%get(jsonroot,'speed',pval)
- call json%get(pval,simulationSpeed)
- if(simulationSpeed==0) simulationSpeed = 1
- msPerStep = 100/simulationSpeed
- call json%get(jsonroot,'endstep',pval)
- call json%get(pval,simulationEnd)
- ! call ProblemsFromJson(jsonfile)
- call EquipmentsFromJson(jsonfile)
- ! call UnitySignalsFromJson(jsonfile)
- call jsonfile%destroy()
- end subroutine
-
- subroutine init_modules
- print *,"initializing modules"
- !Tarmigh
- call Pumps_StartUp()
- print *,"pump1 initialized"
- !call Pump2_Init()
- call RotaryTable_Init()
- print *,"RT initialized"
- call Drawworks_Init()
- call TopDrive_Init()
- print *,"TD initialized"
-
- !Nothing in init (and step)
- ! call Rop_Init()
- ! call TorqueDrag_Init()
- ! call Geo_Step()
-
- !! Rafiee
- call BopStack_Init()
- call ChokeControl_Init()
- call MudSystem_Init()
- ! call PipeRams1_Init()
- ! call PipeRams2_Step()
- ! call KillLine_Step()
- ! call ChokeLine_Step()
- ! call BlindRams_Step()
- ! call Annular_Step()
-
- !! Sheikh
- call FluidFlow_Init()
-
- !! Ahmadi
- call PathFinding_Init()
- call OperationScenarios_Init()
- print *,"Modules are initialized"
- ! Calls OSInitialization and that sub only subscribes some notif
- end subroutine init_modules
-
- subroutine EquipmentsFromJson(jsonfile)
- type(json_value),pointer :: p
- type(json_file)::jsonfile
- logical::is_found
-
- ! 1. get related root
- ! call jsonfile%json_file_get_root(parent)
- ! call jsoncore%get(parent,"Equipments",p)
- call jsonfile%get("Equipments",p,is_found)
-
- ! call jsoncore%info(p, n_children=n_children)
- ! print *,"number of Equipments =",n_children
-
- ! 2. add member of data type to new node
- call BopControlPanelFromJson(p)
- call ChokeControlPanelFromJson(jsonfile)
- call ChokeManifoldFromJson(p)
- call DataDisplayConsoleFromJson(p)
- call DrillingConsoleFromJson(jsonfile)
- call StandPipeManifoldFromJson(p)
- call TopDrivePanelFromJson(p)
- ! call DrillingWatchFromJson(p)
- call TankFromJson(p)
- ! call UnityInputsFromJson(jsonfile)
-
- call jsonfile%get('Equipments.HookHeight',data%State%Drawworks%Hook_Height_final,is_found)
- if ( .not. is_found ) call logg(4,"Not found: Equipments.HookHeight")
- ! if(print_log) print *,"HookHeight=",data%State%Drawworks%Hook_Height_final
-
- ! call jsonfile%get('Equipments.TdsStemIn',data%Equipments%UnityInputs%TdsStemIn,is_found)
- ! if ( .not. is_found ) call logg(4,"Not found: Equipments.TdsStemIn")
- if (print_log .AND. data%Equipments%UnityInputs%TdsStemIn) print *,"TdsStemIn"
- end subroutine
-
- subroutine EquipmentsToJson(parent)
-
- type(json_value),pointer :: parent
-
- type(json_value),pointer :: p
-
- ! 1. create new node
- call jsoncore%create_object(p,'Equipments')
-
- ! 2. add member of data type to new node
- call BopControlPanelToJson(p)
- call ChokeControlPanelToJson(p)
- call ChokeManifoldToJson(p)
- call DataDisplayConsoleToJson(p)
- call DrillingConsoleToJson(p)
- call StandPipeManifoldToJson(p)
- call TopDrivePanelToJson(p)
- call DrillingWatchToJson(p)
- call DownHoleToJson(p)
-
- call jsoncore%add(p,"HookVelocity",data%State%Drawworks%HookLinearVelocity_final)
- call jsoncore%add(p,"TotalSPM",data%Equipments%MPumps%Total_Pump_SPM)
-
-
- ! 3. add new node to parent
- call jsoncore%add(parent,p)
- end subroutine
-
- subroutine WarningsToJson(parent)
- type(json_value),pointer :: parent
- type(json_value),pointer :: p
-
- ! 1. create new node
- call jsoncore%create_object(p,'Warnings')
-
- ! 2. add member of data type to new node
- call jsoncore%add(p,"PumpWithKellyDisconnected",data%Warnings%PumpWithKellyDisconnected)
- call jsoncore%add(p,"PumpWithTopdriveDisconnected",data%Warnings%PumpWithTopdriveDisconnected)
- call jsoncore%add(p,"Pump1PopOffValveBlown",data%Warnings%Pump1PopOffValveBlown)
- call jsoncore%add(p,"Pump1Failure",data%Warnings%Pump1Failure)
- call jsoncore%add(p,"Pump2PopOffValveBlown",data%Warnings%Pump2PopOffValveBlown)
- call jsoncore%add(p,"Pump2Failure",data%Warnings%Pump2Failure)
- call jsoncore%add(p,"Pump3PopOffValveBlown",data%Warnings%Pump3PopOffValveBlown)
- call jsoncore%add(p,"Pump3Failure",data%Warnings%Pump3Failure)
- call jsoncore%add(p,"DrawworksGearsAbuse",data%Warnings%DrawworksGearsAbuse)
- call jsoncore%add(p,"RotaryGearsAbuse",data%Warnings%RotaryGearsAbuse)
- call jsoncore%add(p,"HoistLineBreak",data%Warnings%HoistLineBreak)
- call jsoncore%add(p,"PartedDrillString",data%Warnings%PartedDrillString)
- call jsoncore%add(p,"ActiveTankOverflow",data%Warnings%ActiveTankOverflow)
- call jsoncore%add(p,"ActiveTankUnderVolume",data%Warnings%ActiveTankUnderVolume)
- call jsoncore%add(p,"TripTankOverflow",data%Warnings%TripTankOverflow)
- call jsoncore%add(p,"DrillPipeTwistOff",data%Warnings%DrillPipeTwistOff)
- call jsoncore%add(p,"DrillPipeParted",data%Warnings%DrillPipeParted)
- call jsoncore%add(p,"TripWithSlipsSet",data%Warnings%TripWithSlipsSet)
- call jsoncore%add(p,"Blowout",data%Warnings%Blowout)
- call jsoncore%add(p,"UndergroundBlowout",data%Warnings%UndergroundBlowout)
- call jsoncore%add(p,"MaximumWellDepthExceeded",data%Warnings%MaximumWellDepthExceeded)
- call jsoncore%add(p,"CrownCollision",data%Warnings%CrownCollision)
- call jsoncore%add(p,"FloorCollision",data%Warnings%FloorCollision)
- call jsoncore%add(p,"TopdriveRotaryTableConfilict",data%Warnings%TopdriveRotaryTableConfilict)
-
- ! 3. add new node to parent
- call jsoncore%add(parent,p)
- end subroutine
-
- subroutine ProblemsToJson(parent)
- type(json_value),pointer :: parent
-
- type(json_value),pointer :: p
-
- ! 1. create new node
- call jsoncore%create_object(p,'Problems')
-
- ! 2. add member of data type to new node
- call BitProblemsToJson(p)
- call BopProblemsToJson(p)
- call ChokeProblemsToJson(p)
- call DrillStemProblemsToJson(p)
- call GaugesProblemsToJson(p)
- call HoistingProblemsToJson(p)
- call KickProblemsToJson(p)
- call LostProblemsToJson(p)
- call MudTreatmentProblemsToJson(p)
- call OtherProblemsToJson(p)
- call PumpProblemsToJson(p)
- call RotaryProblemsToJson(p)
-
- ! 3. add new node to parent
- call jsoncore%add(parent,p)
- end subroutine
-
- subroutine writeState() bind(C,name="writeState")
- use json_module
- implicit none
- type(json_value),pointer :: p
- type(json_value),pointer :: jsonroot
- character(len=10)::str
-
- call jsoncore%initialize()
- call jsoncore%create_object(p,'')
- call ManifoldToJson(p)
- call notificationsToJson(p)
- call UnitySignalsToJson(p)
- call OperationScenariosToJson(p)
- ! call permissionsToJson(p)
- ! call StudentStationToJson(p)
- ! call BopStackInputToJson(p)
- ! call BopStackAccToJson(p)
- ! call RamLineToJson(p)
- ! call AnnularComputationalToJson(p)
- ! call AnnularToJson(p)
- ! call PipeRam1ToJson(p)
- ! call ShearRamToJson(p)
- ! call PipeRam2ToJson(p)
- ! call ChokeLineToJson(p)
- ! call KillLineToJson(p)
- ! call PumpsToJson(p)
- ! call RAMToJson(p)
- ! call RAMSToJson(p)
- ! call ChokeToJson(p)
- ! call AirDrivenPumpToJson(p)
- ! call AirPumpLineToJson(p)
- ! call CHOOKEToJson(p)
- ! call DrawworksToJson(p)
- ! call MudSystemToJson(p)
- ! call MUDToJson(p)
- ! call MPumpsToJson(p)
- ! call PUMPToJson(p)
- ! call RTableToJson(p)
- ! call TDSToJson(p)
- ! call GasType(3)ToJson(p)
- ! call PressureDisplayToJson(p)
- ! call FricPressDropToJson(p)
- ! call ROP_SpecToJson(p)
- ! call ROP_BitToJson(p)
- ! call TDGeoToJson(p)
- ! call F_String(:)ToJson(p)
- ! call F_CountsToJson(p)
- ! call F_Interval(:)ToJson(p)
- ! call OD_Annulus(4)ToJson(p)
- ! call TD_DrillStemToJson(p)
- ! call TD_DrillStemsToJson(p)
- ! call TD_StringToJson(p)
- ! call TD_CountToJson(p)
- ! call G_StringElementToJson(p)
- ! call TD_VolToJson(p)
- ! call TD_GeneralToJson(p)
- ! call TD_BOPToJson(p)
- ! call TD_BOPElement(4)ToJson(p)
- ! call TD_StConnToJson(p)
- ! call TD_LoadToJson(p)
- ! call TD_WellElToJson(p)
- ! call TD_CasingToJson(p)
- ! call TD_LinerToJson(p)
- ! call TD_OpenHoleToJson(p)
- ! call TD_ROPHoleToJson(p)
- ! call TD_WellGeneralToJson(p)
- ! call TD_WellGeo(:)ToJson(p)
-
- call jsoncore%print_to_string(p,stateStr)
- if(log_level>4) then
- write(str, '(I0)') len(stateStr)
- print *,"Writing to redis:"//trim(stateStr)
- endif
-
- call setState(stateStr)
- call jsoncore%destroy(jsonroot)
- end subroutine
-
- !use this as a template
- subroutine notificationsToJson(parent)
- type(json_value),pointer :: parent
- type(json_value),pointer :: p
- ! 1. create new node
- call jsoncore%create_object(p,'Notifications')
- ! 2. add member of data type to new node
- ! 3. add new node to parent
- call jsoncore%add(parent,p)
- end subroutine
-
- subroutine ConfigurationFromJson(jsonfile)
- type(json_file)::jsonfile
- type(json_value),pointer :: parent
- type(json_value),pointer :: p
-
- ! 1. get related root
- call jsonfile%json_file_get_root(parent)
- call jsoncore%get(parent,"Configuration",p)
-
- call StringConfigurationFromJson(p)
- call FormationFromJson(p)
- call ReservoirFromJson(p)
- call ShoeFromJson(p)
- call AccumulatorFromJson(p)
- call BopStackFromJson(p)
- call HoistingFromJson(p)
- call PowerFromJson(p)
- call PumpsFromJson(p)
- call RigSizeFromJson(p)
- call CasingLinerChokeFromJson(p)
- call PathGenerationFromJson(p)
- call MudPropertiesFromJson(p)
- ! 3. add new node to parent
- ! nullify(parent)
- end subroutine
-
- subroutine WarningsFromJson(parent)
- type(json_value),pointer :: parent
- type(json_value),pointer :: p
- type(json_value),pointer :: pval
-
- ! 1. get node
- call jsoncore%get(parent,'Warnings',p)
-
- ! ! 2. add member of data type to new node
- call jsoncore%get(p,'PumpWithKellyDisconnected',pval)
- call jsoncore%get(pval,data%Warnings%PumpWithKellyDisconnected)
- call jsoncore%get(p,'PumpWithTopdriveDisconnected',pval)
- call jsoncore%get(pval,data%Warnings%PumpWithTopdriveDisconnected)
- call jsoncore%get(p,'Pump1PopOffValveBlown',pval)
- call jsoncore%get(pval,data%Warnings%Pump1PopOffValveBlown)
- call jsoncore%get(p,'Pump1Failure',pval)
- call jsoncore%get(pval,data%Warnings%Pump1Failure)
- call jsoncore%get(p,'Pump2PopOffValveBlown',pval)
- call jsoncore%get(pval,data%Warnings%Pump2PopOffValveBlown)
- call jsoncore%get(p,'Pump2Failure',pval)
- call jsoncore%get(pval,data%Warnings%Pump2Failure)
- call jsoncore%get(p,'Pump3PopOffValveBlown',pval)
- call jsoncore%get(pval,data%Warnings%Pump3PopOffValveBlown)
- call jsoncore%get(p,'Pump3Failure',pval)
- call jsoncore%get(pval,data%Warnings%Pump3Failure)
- call jsoncore%get(p,'DrawworksGearsAbuse',pval)
- call jsoncore%get(pval,data%Warnings%DrawworksGearsAbuse)
- call jsoncore%get(p,'RotaryGearsAbuse',pval)
- call jsoncore%get(pval,data%Warnings%RotaryGearsAbuse)
- call jsoncore%get(p,'HoistLineBreak',pval)
- call jsoncore%get(pval,data%Warnings%HoistLineBreak)
- call jsoncore%get(p,'PartedDrillString',pval)
- call jsoncore%get(pval,data%Warnings%PartedDrillString)
- call jsoncore%get(p,'ActiveTankOverflow',pval)
- call jsoncore%get(pval,data%Warnings%ActiveTankOverflow)
- call jsoncore%get(p,'ActiveTankUnderVolume',pval)
- call jsoncore%get(pval,data%Warnings%ActiveTankUnderVolume)
- call jsoncore%get(p,'TripTankOverflow',pval)
- call jsoncore%get(pval,data%Warnings%TripTankOverflow)
- call jsoncore%get(p,'DrillPipeTwistOff',pval)
- call jsoncore%get(pval,data%Warnings%DrillPipeTwistOff)
- call jsoncore%get(p,'DrillPipeParted',pval)
- call jsoncore%get(pval,data%Warnings%DrillPipeParted)
- call jsoncore%get(p,'TripWithSlipsSet',pval)
- call jsoncore%get(pval,data%Warnings%TripWithSlipsSet)
- call jsoncore%get(p,'Blowout',pval)
- call jsoncore%get(pval,data%Warnings%Blowout)
- call jsoncore%get(p,'UndergroundBlowout',pval)
- call jsoncore%get(pval,data%Warnings%UndergroundBlowout)
- call jsoncore%get(p,'MaximumWellDepthExceeded',pval)
- call jsoncore%get(pval,data%Warnings%MaximumWellDepthExceeded)
- call jsoncore%get(p,'CrownCollision',pval)
- call jsoncore%get(pval,data%Warnings%CrownCollision)
- call jsoncore%get(p,'FloorCollision',pval)
- call jsoncore%get(pval,data%Warnings%FloorCollision)
- call jsoncore%get(p,'TopdriveRotaryTableConfilict',pval)
- call jsoncore%get(pval,data%Warnings%TopdriveRotaryTableConfilict)
- end subroutine
-
- subroutine ProblemsFromJson(jsonfile)
- type(json_value),pointer :: parent
- type(json_value),pointer :: p
- type(json_file)::jsonfile
-
- call jsonfile%json_file_get_root(parent)
- call jsoncore%get(parent,'Warnings',p)
-
- call BitProblemsToJson(p)
- call BopProblemsFromJson(p)
- call ChokeProblemsFromJson(p)
- call DrillStemProblemsFromJson(p)
- call GaugesProblemsFromJson(p)
- call HoistingProblemsFromJson(p)
- call KickProblemsFromJson(p)
- call LostProblemsFromJson(p)
- call MudTreatmentProblemsFromJson(p)
- call OtherProblemsFromJson(p)
- call PumpProblemsFromJson(p)
- call RotaryProblemsFromJson(p)
- end subroutine
-
- subroutine StateFromJson(jsonfile)
- type(json_value),pointer :: p
- type(json_file)::jsonfile
- logical::is_found
-
- ! 1. get related root
- ! call jsonfile%json_file_get_root(parent)
- ! call jsoncore%get(parent,"Equipments",p)
- call jsonfile%get("Equipments",p,is_found)
-
- ! call jsoncore%info(p, n_children=n_children)
- ! print *,"number of Equipments =",n_children
-
- ! 2. add member of data type to new node
- call BopControlPanelFromJson(p)
- call ChokeControlPanelFromJson(jsonfile)
-
- ! 1. create new node
- ! call json%create_object(p,'State')
-
- ! ! call OperationScenarioFromJson(p)
- ! call notificationsFromJson(p)
- ! call permissionsFromJson(p)
- ! call unitySignalsFromJson(p)
- ! call StudentStationFromJson(p)
- ! call BopStackInputFromJson(p)
- ! call BopStackAccFromJson(p)
- ! call RamLineFromJson(p)
- ! call AnnularComputationalFromJson(p)
- ! call AnnularFromJson(p)
- ! call PipeRam1FromJson(p)
- ! call ShearRamFromJson(p)
- ! call PipeRam2FromJson(p)
- ! call ChokeLineFromJson(p)
- ! call KillLineFromJson(p)
- ! call PumpsFromJson(p)
- ! call RAMFromJson(p)
- ! call RAMSFromJson(p)
- ! call ChokeFromJson(p)
- ! call AirDrivenPumpFromJson(p)
- ! call AirPumpLineFromJson(p)
- ! call CHOOKEFromJson(p)
- ! call DrawworksFromJson(p)
- ! call MudSystemFromJson(p)
- ! call MUDFromJson(p)
- ! call MPumpsFromJson(p)
- ! call PUMPFromJson(p)
- ! call RTableFromJson(p)
- ! call TDSFromJson(p)
- ! call GasType(3)FromJson(p)
- ! call PressureDisplayFromJson(p)
- ! call FricPressDropFromJson(p)
- ! call ROP_SpecFromJson(p)
- ! call ROP_BitFromJson(p)
- ! call TDGeoFromJson(p)
- ! call F_String(:)FromJson(p)
- ! call F_CountsFromJson(p)
- ! call F_Interval(:)FromJson(p)
- ! call OD_Annulus(4)FromJson(p)
- ! call TD_DrillStemFromJson(p)
- ! call TD_DrillStemsFromJson(p)
- ! call TD_StringFromJson(p)
- ! call TD_CountFromJson(p)
- ! call G_StringElementFromJson(p)
- ! call TD_VolFromJson(p)
- ! call TD_GeneralFromJson(p)
- ! call TD_BOPFromJson(p)
- ! call TD_BOPElement(4)FromJson(p)
- ! call TD_StConnFromJson(p)
- ! call TD_LoadFromJson(p)
- ! call TD_WellElFromJson(p)
- ! call TD_CasingFromJson(p)
- ! call TD_LinerFromJson(p)
- ! call TD_OpenHoleFromJson(p)
- ! call TD_ROPHoleFromJson(p)
- ! call TD_WellGeneralFromJson(p)
- ! call TD_WellGeo(:)FromJson(p)
-
- ! 2. add member of data type to new node
-
- ! 3. add new node to parent
- ! call jsoncore%add(parent,p)
- end subroutine
-
- !use this as a template
- subroutine notificationsFromJson(parent)
- type(json_value),pointer :: parent
- !
- ! type(json_value),pointer :: p
-
- ! 1. create new node
- ! call json%create_object(p,'Notifications')
-
- ! ! 2. add member of data type to new node
-
- ! ! 3. add new node to parent
- ! call json%add(parent,p)
- end subroutine
-
- ! subroutine fireOperationScenarioEvent()
- ! print *,"fireOperationScenarioEvent starts"
- ! if(operationScenarioEvent=='Kelly_ConnectionNothing'.and. .not. Kelly_ConnectionNothing_in_progress) then
- ! Kelly_ConnectionNothing_in_progress = .true.
- ! print *, "Starting Kelly_ConnectionNothing"
- ! call Kelly_ConnectionNothing()
- ! print *, "Kelly_ConnectionNothing ends."
- ! Kelly_ConnectionNothing_in_progress = .false.
- ! endif
- ! end subroutine
-
-
- end module Simulator
|