|
- module Simulator
- 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
- use :: json_module, rk => json_rk
-
- implicit none
- real :: t0, dt, tf, mu
- real(kind=rk), allocatable :: x0(:)
- type(json_file) :: json
- logical :: is_found
-
- contains
- subroutine Simulate
- integer :: t
- !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
- t=0
- call init_modules()
- do while (t<10)
- !!read variable from shared file
- call read_variables()
-
- !! Tarmigh, Now merged with TorqueDrag (FluidFlow)
- ! call Rop_Step()
-
- !! Rafiee, nothing changed
- call BopStack_Step()
-
- !! Tarmigh, now is rewritten
- call Pump1_Step()
- !call Pump2_Step()
-
- !! Rafiee
- call ChokeControl_Step()
-
- !! Location ./Equipment/Rotarytable
- !! Variables:
- !! Does not have step function
- !! Call RTable_StartUp in the start
- !! Again has a loop in each step
- !! Tarmigh, now is rewritten
- call RotaryTable_Step()
-
- !! Location ./Equipment/Drawworks
- !! Variables:
- !! Does not have step function
- !! Call ..._StartUp in the start
- !! Again has a loop in each step
- !! Tarmigh, now is rewritten
- call Drawworks_Step()
-
- !! Empty nothing called
- !! Merged in FluidFlow
- ! call TorqueDrag_Step()
-
- !! Location: ./Equipment/MudSystem
- !! Variables: MudSystem_variables.f90 and MudSystem.f90
- !! Step function simply calls LineupAndPath in MudSystem.f90
- !! had not startUp
- !! Rafiee
- call MudSystem_Step()
-
- !! Location ./Equipment/BopStack
- !! Variables: VARIABLES,CBopStackVariables,CBopControlPanelVariables,CEquipmentsConstants
- !! Step function added, only call PIPE_RAMS1 and 2 function
- !! BOP_StartUp commented
- !! Rafiee
- call PipeRams1_Step()
- call PipeRams2_Step()
-
-
- !! Location ./Equipment/BopStack
- !! Variables: VARIABLES,CBopStackVariables,CBopControlPanelVariables,CEquipmentsConstants,CAccumulatorVariables,CSimulationVariables
- !! Step function added, only call PIPE_RAMS1 and PIPE_RAMS2 function
- !! BOP_StartUp commented
- !! Rafiee
- call KillLine_Step()
-
- !! Probably like other bopstack equipments
- !! Rafiee
- call ChokeLine_Step()
- call BlindRams_Step()
- call Annular_Step()
-
- !!Tarmigh. Step must rewrittem
- call TopDrive_Step()
-
- !!Empty
- ! call Geo_Step()
-
- !! Sheikh
- !call FluidFlow_Step()
-
- !! Ahmadi
- call OperationScenarios_Step()
-
- !!Ahmadi
- call PathFinding_Step()
-
- !! Write variables to shared files
- call write_variables()
-
- print *,"t=",t
- t = t + 1
- end do
- end subroutine Simulate
-
- subroutine write_variables
- !implicit none
- end subroutine
-
- subroutine read_variables
- call json%initialize()
-
- ! Load the file.
- call json%load_file('config.json'); if (json%failed()) stop
-
- call json%get('t0', t0, is_found); if (.not. is_found) return
- call json%get('dt', dt, is_found); if (.not. is_found) return
- call json%get('tf', tf, is_found); if (.not. is_found) return
- call json%get('mu', mu, is_found); if (.not. is_found) return
- call json%get('x0', x0, is_found); if (.not. is_found) return
-
- ! Output values.
- if (is_found) then
- print *, t0, dt, tf, mu
- print *, x0
- end if
-
- ! Clean up.
- call json%destroy()
- end subroutine
- subroutine init_modules
- !Tarmigh
- call Pump1_Init()
- !call Pump2_Step()
- call RotaryTable_Init()
- call Drawworks_Init()
- call TopDrive_Init()
- !Nothing in init (and step)
- ! call Rop_Init()
- ! call TorqueDrag_Init()
- ! call Geo_Step()
-
- !! Rafiee
- call BopStack_Init()
- call ChokeControl_Init()
- call MudSystem_Init()
- !Again calls Bop_Startup
- ! 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()
- ! Calls OSInitialization and that sub only subscribes some notif
- ! call OperationScenarios_Init()
- end subroutine init_modules
- end module Simulator
|