|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080 |
- module CSimulation
- use CSimulationVariables
- use CSimulationThreads
- use ifcore
- use ifmt
- implicit none
- public
-
-
- contains
-
- subroutine InitThreads
- implicit none
-
- #ifdef EnableSimulation
- !BopStack
- BopStackThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- BopStackThread, &
- loc(BopStackThreadParam), &
- CREATE_SUSPENDED, &
- BopStackThreadId )
-
- !Pumps
- Pump1ThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- Pump1Thread, &
- loc(Pump1ThreadParam), &
- CREATE_SUSPENDED, &
- Pump1ThreadId )
- Pump2ThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- Pump2Thread, &
- loc(Pump2ThreadParam), &
- CREATE_SUSPENDED, &
- Pump2ThreadId )
- Pump3ThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- Pump3Thread, &
- loc(Pump3ThreadParam), &
- CREATE_SUSPENDED, &
- Pump3ThreadId )
-
-
- !ChokeControl
- ChokeControlThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- ChokeControlThread, &
- loc(ChokeControlThreadParam), &
- CREATE_SUSPENDED, &
- ChokeControlThreadId )
-
- !ROP
- RopThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- RopThread, &
- loc(RopThreadParam), &
- CREATE_SUSPENDED, &
- RopThreadId )
-
- !Geo
- GeoThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- GeoThread, &
- loc(GeoThreadParam), &
- CREATE_SUSPENDED, &
- GeoThreadId )
-
- !RotaryTable
- RotaryTableThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- RotaryTableThread, &
- loc(RotaryTableThreadParam), &
- CREATE_SUSPENDED, &
- RotaryTableThreadId )
-
-
- !Drawworks
- DrawworksThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- DrawworksThread, &
- loc(DrawworksThreadParam), &
- CREATE_SUSPENDED, &
- DrawworksThreadId )
-
- !FluidFlow
- FluidFlowThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- FluidFlowThread, &
- loc(FluidFlowThreadParam), &
- CREATE_SUSPENDED, &
- FluidFlowThreadId )
-
-
- !TorqueDrag
- TorqueDragThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- TorqueDragThread, &
- loc(TorqueDragThreadParam), &
- CREATE_SUSPENDED, &
- TorqueDragThreadId )
-
- !TopDrive
- TopDriveThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- TopDriveThread, &
- loc(TopDriveThreadParam), &
- CREATE_SUSPENDED, &
- TopDriveThreadId )
-
- !MudSystem
- MudSystemThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- MudSystemThread, &
- loc(MudSystemThreadParam), &
- CREATE_SUSPENDED, &
- MudSystemThreadId )
-
- !PipeRams1
- PipeRams1ThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- PipeRams1Thread, &
- loc(PipeRams1ThreadParam), &
- CREATE_SUSPENDED, &
- PipeRams1ThreadId )
-
- !PipeRams2
- PipeRams2ThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- PipeRams2Thread, &
- loc(PipeRams2ThreadParam), &
- CREATE_SUSPENDED, &
- PipeRams2ThreadId )
-
- !KillLine
- KillLineThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- KillLineThread, &
- loc(KillLineThreadParam), &
- CREATE_SUSPENDED, &
- KillLineThreadId )
-
- !ChokeLine
- ChokeLineThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- ChokeLineThread, &
- loc(ChokeLineThreadParam), &
- CREATE_SUSPENDED, &
- ChokeLineThreadId )
-
- !BlindRams
- BlindRamsThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- BlindRamsThread, &
- loc(BlindRamsThreadParam), &
- CREATE_SUSPENDED, &
- BlindRamsThreadId )
-
- !Annular
- AnnularThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- AnnularThread, &
- loc(AnnularThreadParam), &
- CREATE_SUSPENDED, &
- AnnularThreadId )
-
-
- !OperationScenarios
- OperationScenariosThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- OperationScenariosThread, &
- loc(OperationScenariosThreadParam), &
- CREATE_SUSPENDED, &
- OperationScenariosThreadId )
-
- !PathFinding
- PathFindingThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- PathFindingThread, &
- loc(PathFindingThreadParam), &
- CREATE_SUSPENDED, &
- PathFindingThreadId )
-
-
- !Sample
- SampleThreadHandle = CreateThread( &
- ThreadSecurity, &
- ThreadStackSize, &
- SampleThread, &
- loc(SampleThreadParam), &
- CREATE_SUSPENDED, &
- SampleThreadId )
-
- #endif
-
- end subroutine InitThreads
-
- subroutine StopThreads
- implicit none
-
- #ifdef EnableSimulation
- !BopStack
- #ifdef HardStop
- ApiResult = TerminateThread(BopStackThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(BopStackThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(BopStackThreadHandle)
-
-
-
-
- !Pump 1
- #ifdef HardStop
- ApiResult = TerminateThread(Pump1ThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(Pump1ThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(Pump1ThreadHandle)
-
- !Pump 2
- #ifdef HardStop
- ApiResult = TerminateThread(Pump2ThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(Pump2ThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(Pump2ThreadHandle)
-
- !Pump 3
- #ifdef HardStop
- ApiResult = TerminateThread(Pump3ThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(Pump3ThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(Pump3ThreadHandle)
-
-
- !ChokeControl
- #ifdef HardStop
- ApiResult = TerminateThread(ChokeControlThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(ChokeControlThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(ChokeControlThreadHandle)
-
- !ROP
- #ifdef HardStop
- ApiResult = TerminateThread(RopThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(RopThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(RopThreadHandle)
-
- !Geo
- #ifdef HardStop
- ApiResult = TerminateThread(GeoThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(GeoThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(GeoThreadHandle)
-
- !RotaryTable
- #ifdef HardStop
- ApiResult = TerminateThread(RotaryTableThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(RotaryTableThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(RotaryTableThreadHandle)
-
-
- !Drawworks
- #ifdef HardStop
- ApiResult = TerminateThread(DrawworksThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(DrawworksThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(DrawworksThreadHandle)
-
- !FluidFlow
- #ifdef HardStop
- ApiResult = TerminateThread(FluidFlowThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(FluidFlowThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(FluidFlowThreadHandle)
-
-
- !TorqueDrag
- #ifdef HardStop
- ApiResult = TerminateThread(TorqueDragThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(TorqueDragThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(TorqueDragThreadHandle)
-
-
- !TopDrive
- #ifdef HardStop
- ApiResult = TerminateThread(TopDriveThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(TopDriveThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(TopDriveThreadHandle)
-
-
-
- !MudSystem
- #ifdef HardStop
- ApiResult = TerminateThread(MudSystemThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(MudSystemThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(MudSystemThreadHandle)
-
- !PipeRams1
- #ifdef HardStop
- ApiResult = TerminateThread(PipeRams1ThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(PipeRams1ThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(PipeRams1ThreadHandle)
-
- !PipeRams2
- #ifdef HardStop
- ApiResult = TerminateThread(PipeRams2ThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(PipeRams2ThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(PipeRams2ThreadHandle)
-
- !KillLine
- #ifdef HardStop
- ApiResult = TerminateThread(KillLineThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(KillLineThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(KillLineThreadHandle)
-
- !ChokeLine
- #ifdef HardStop
- ApiResult = TerminateThread(ChokeLineThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(ChokeLineThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(ChokeLineThreadHandle)
-
- !BlindRams
- #ifdef HardStop
- ApiResult = TerminateThread(BlindRamsThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(BlindRamsThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(BlindRamsThreadHandle)
-
- !Annular
- #ifdef HardStop
- ApiResult = TerminateThread(AnnularThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(AnnularThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(AnnularThreadHandle)
-
-
- !OperationScenarios
- #ifdef HardStop
- ApiResult = TerminateThread(OperationScenariosThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(OperationScenariosThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(OperationScenariosThreadHandle)
-
- !PathFinding
- #ifdef HardStop
- ApiResult = TerminateThread(PathFindingThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(PathFindingThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(PathFindingThreadHandle)
-
-
-
-
-
-
- !Sample
- #ifdef HardStop
- ApiResult = TerminateThread(SampleThreadHandle, 0)
- #else
- !ApiResult = WaitForSingleObject(SampleThreadHandle, WaitForStopMs)
- #endif
- ApiResult = CloseHandle(SampleThreadHandle)
-
- #endif
-
-
-
-
-
-
-
-
-
-
-
-
- end subroutine StopThreads
-
- subroutine Initialization(portable)
- !DEC$ ATTRIBUTES DLLEXPORT::Initialization
- !DEC$ ATTRIBUTES ALIAS: 'Initialization' :: Initialization
- use BopStackMain
- use PumpsMain
- use ChokeControlMain
- 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 GeoMain
-
- use COperationScenariosMain
- use CManifolds
- implicit none
- logical, intent(in) :: portable
- IsPortable = portable
- if(portable) then
- IsPortableInt = 1
- !print*, 'IsPortableInt=', IsPortableInt
- else
- IsPortableInt = 0
- !print*, 'IsPortableInt=', IsPortableInt
- endif
-
- call BopStack_Setup()
- call Pump1_Setup()
- call Pump2_Setup()
- call Pump3_Setup()
- call ChokeControl_Setup()
- call Rop_Setup()
- call RotaryTable_Setup()
- call Drawworks_Setup()
- call FluidFlow_Setup()
- call TorqueDrag_Setup()
- call MudSystem_Setup()
- call PipeRams1_Setup()
- call PipeRams2_Setup()
- call KillLine_Setup()
- call ChokeLine_Setup()
- call BlindRams_Setup()
- call Annular_Setup()
- call TopDrive_Setup()
- call Geo_Setup()
-
- call OperationScenarios_Setup()
- call PathFinding_Setup()
-
- call Sample_Setup()
-
- call OnSimulationInitialization%RunAll()
-
- call InitThreads()
-
-
- call OnBopStackPause%Add(BopStack_Thread)
- call OnPump1Pause%Add(Pump1_Thread)
- call OnPump2Pause%Add(Pump2_Thread)
- call OnPump3Pause%Add(Pump3_Thread)
- call OnChokeControlPause%Add(ChokeControl_Thread)
- call OnRopPause%Add(Rop_Thread)
- call OnRotaryTablePause%Add(RotaryTable_Thread)
- call OnDrawworksPause%Add(Drawworks_Thread)
- call OnFluidFlowPause%Add(FluidFlow_Thread)
- call OnTorqueDragPause%Add(TorqueDrag_Thread)
- call OnMudSystemPause%Add(MudSystem_Thread)
- call OnPipeRams1Pause%Add(PipeRams1_Thread)
- call OnPipeRams2Pause%Add(PipeRams2_Thread)
- call OnKillLinePause%Add(KillLine_Thread)
- call OnChokeLinePause%Add(ChokeLine_Thread)
- call OnBlindRamsPause%Add(BlindRams_Thread)
- call OnAnnularPause%Add(Annular_Thread)
- call OnGeoPause%Add(Geo_Thread)
-
- call OnSamplePause%Add(Sample_Thread)
-
- TotalStrokesPtr => TotalStrokesDue
- TotalVolumePumpedPtr => TotalVolumePumpedDue
- DistanceDrilledPtr => DistanceDrilledDue
-
- !TODO: CHANGE LATER
- call DrillMode_ON()
-
- end subroutine Initialization
-
- subroutine StartSimulation
- !DEC$ ATTRIBUTES DLLEXPORT::StartSimulation
- !DEC$ ATTRIBUTES ALIAS: 'StartSimulation' :: StartSimulation
- implicit none
-
- if(SimulationState_old == SimulationState_Stopped) call OnSimulationStart%RunAll()
- IsStopped = .false.
- SimulationState = SimulationState_Started
- SimulationState_old = SimulationState_Started
-
- BopStackStarted = .false.
- Pump1Started = .false.
- Pump2Started = .false.
- Pump3Started = .false.
- ChokeControlStarted = .false.
- RopStarted = .false.
- RotaryTableStarted = .false.
- DrawworksStarted = .false.
- FluidFlowStarted = .false.
- TorqueDragStarted = .false.
- MudSystemStarted = .false.
- PipeRams1Started = .false.
- PipeRams2Started = .false.
- KillLineStarted = .false.
- ChokeLineStarted = .false.
- BlindRamsStarted = .false.
- AnnularStarted = .false.
- GeoStarted = .false.
-
- SampleStarted = .false.
-
-
- #ifdef EnableSimulation
-
- #ifdef M_BopStack
- ApiResult = ResumeThread(BopStackThreadHandle)
- #endif
-
- #ifdef M_Pump1
- ApiResult = ResumeThread(Pump1ThreadHandle)
- #endif
- #ifdef M_Pump2
- ApiResult = ResumeThread(Pump2ThreadHandle)
- #endif
- #ifdef M_Pump3
- ApiResult = ResumeThread(Pump3ThreadHandle)
- #endif
-
-
- #ifdef M_ChokeControl
- ApiResult = ResumeThread(ChokeControlThreadHandle)
- #endif
- #ifdef M_Rop
- ApiResult = ResumeThread(RopThreadHandle)
- #endif
- #ifdef M_Geo
- ApiResult = ResumeThread(GeoThreadHandle)
- #endif
- #ifdef M_RotaryTable
- ApiResult = ResumeThread(RotaryTableThreadHandle)
- #endif
-
- #ifdef M_Drawworks
- ApiResult = ResumeThread(DrawworksThreadHandle)
- #endif
- #ifdef M_FluidFlow
- ApiResult = ResumeThread(FluidFlowThreadHandle)
- #endif
-
- #ifdef M_TorqueDrag
- ApiResult = ResumeThread(TorqueDragThreadHandle)
- #endif
-
- #ifdef M_TopDrive
- ApiResult = ResumeThread(TopDriveThreadHandle)
- #endif
-
- #ifdef M_MudSystem
- ApiResult = ResumeThread(MudSystemThreadHandle)
- #endif
- #ifdef M_PipeRams1
- ApiResult = ResumeThread(PipeRams1ThreadHandle)
- #endif
- #ifdef M_PipeRams2
- ApiResult = ResumeThread(PipeRams2ThreadHandle)
- #endif
- #ifdef M_KillLine
- ApiResult = ResumeThread(KillLineThreadHandle)
- #endif
- #ifdef M_ChokeLine
- ApiResult = ResumeThread(ChokeLineThreadHandle)
- #endif
- #ifdef M_BlindRams
- ApiResult = ResumeThread(BlindRamsThreadHandle)
- #endif
- #ifdef M_Annular
- ApiResult = ResumeThread(AnnularThreadHandle)
- #endif
-
- !OperationScenarios
- ApiResult = ResumeThread(OperationScenariosThreadHandle)
-
- !PathFinding
- ApiResult = ResumeThread(PathFindingThreadHandle)
-
- #ifdef M_Sample
- ApiResult = ResumeThread(SampleThreadHandle)
- #endif
-
- #endif
- end subroutine StartSimulation
-
- subroutine StopSimulation
- !DEC$ ATTRIBUTES DLLEXPORT::StopSimulation
- !DEC$ ATTRIBUTES ALIAS: 'StopSimulation' :: StopSimulation
- use CDrillingConsoleVariables, only: MP1CPSwitchI, MP2SwitchI, MP1CPSwitch, MP2Switch, MP1Throttle, MP2Throttle, MP1ThrottleUpdate, MP2ThrottleUpdate
- implicit none
- MP1CPSwitchI = 0
- MP1CPSwitch = 0
- MP2SwitchI = 0
- MP2Switch = .false.
- MP1ThrottleUpdate = .false.
- MP2ThrottleUpdate = .false.
- MP1Throttle = -1.0
- MP2Throttle = -1.0
- !MP1Throttle = 0.0
- !MP2Throttle = 0.0
-
- IsSnapshot = .false.
- IsStopped = .true.
- TotalPumpStrokes = 0
- TotalVolumePumped = 0
- DistanceDrilled = 0
- SimulationState = SimulationState_Stopped
- SimulationState_old = SimulationState_Stopped
- call OnSimulationStop%RunAll()
- call StopThreads()
- call InitThreads()
- end subroutine StopSimulation
-
- subroutine PauseSimulation
- implicit none
- if(SimulationState_old == SimulationState_Stopped) then
- SimulationState_old = SimulationState_Started
- return
- endif
- SimulationState_old = SimulationState_Paused
- #ifdef EnableSimulation
- !BopStack
- ApiResult = SuspendThread(BopStackThreadHandle)
-
- !Pumps
- ApiResult = SuspendThread(Pump1ThreadHandle)
- ApiResult = SuspendThread(Pump2ThreadHandle)
- ApiResult = SuspendThread(Pump3ThreadHandle)
-
-
- !ChokeControl
- ApiResult = SuspendThread(ChokeControlThreadHandle)
-
- !ROP
- ApiResult = SuspendThread(RopThreadHandle)
-
- !Geo
- ApiResult = SuspendThread(GeoThreadHandle)
-
- !RotaryTable
- ApiResult = SuspendThread(RotaryTableThreadHandle)
-
-
- !Drawworks
- ApiResult = SuspendThread(DrawworksThreadHandle)
-
- !FluidFlow
- ApiResult = SuspendThread(FluidFlowThreadHandle)
-
-
- !TorqueDrag
- ApiResult = SuspendThread(TorqueDragThreadHandle)
-
-
- !TopDrive
- ApiResult = SuspendThread(TopDriveThreadHandle)
-
- !MudSystem
- ApiResult = SuspendThread(MudSystemThreadHandle)
-
- !PipeRams1
- ApiResult = SuspendThread(PipeRams1ThreadHandle)
-
- !PipeRams2
- ApiResult = SuspendThread(PipeRams2ThreadHandle)
-
- !KillLine
- ApiResult = SuspendThread(KillLineThreadHandle)
-
- !ChokeLine
- ApiResult = SuspendThread(ChokeLineThreadHandle)
-
- !BlindRams
- ApiResult = SuspendThread(BlindRamsThreadHandle)
-
- !Annular
- ApiResult = SuspendThread(AnnularThreadHandle)
-
-
- !OperationScenarios
- ApiResult = SuspendThread(OperationScenariosThreadHandle)
-
- !PathFinding
- ApiResult = SuspendThread(PathFindingThreadHandle)
-
-
-
- !Sample
- ApiResult = SuspendThread(SampleThreadHandle)
- #endif
- call OnSimulationPause%RunAll()
- end subroutine PauseSimulation
-
- logical function IsRunning()
- !DEC$ ATTRIBUTES DLLEXPORT :: IsRunning
- !DEC$ ATTRIBUTES ALIAS: 'IsRunning' :: IsRunning
- implicit none
- IsRunning = .not. IsStopped
- end function
-
- subroutine OnTimerTick(time, state)
- !DEC$ ATTRIBUTES DLLEXPORT :: OnTimerTick
- !DEC$ ATTRIBUTES ALIAS: 'OnTimerTick' :: OnTimerTick
- implicit none
- integer, intent(in) :: time
- integer, intent(in) :: state
- SimulationState = state
- SimulationTime = time
- end subroutine
-
- subroutine TimerTick(s)
- !DEC$ ATTRIBUTES DLLEXPORT :: TimerTick
- !DEC$ ATTRIBUTES ALIAS: 'TimerTick' :: TimerTick
- use CBitProblemsVariables
- use CBopProblemsVariables
- use CChokeProblemsVariables
- use CDrillStemProblemsVariables
- use CGaugesProblemsVariables
- use CHoistingProblemsVariables
- use CLostProblemsVariables
- use CMudTreatmentProblemsVariables
- use COtherProblemsVariables
- use CPumpProblemsVariables
- use CRotaryProblemsVariables
- use CKickProblemsVariables
- use GeoMain
- implicit none
- integer, intent(in) :: s
- SimulationTime = s
- call ProcessBitProblemsDueTime(s)
- call ProcessBopProblemsDueTime(s)
- call ProcessChokeProblemsDueTime(s)
- call ProcessDrillStemProblemsDueTime(s)
- call ProcessGaugesProblemsDueTime(s)
- call ProcessHoistingProblemsDueTime(s)
- call ProcessLostProblemsDueTime(s)
- call ProcessMudTreatmentProblemsDueTime(s)
- call ProcessOtherProblemsDueTime(s)
- call ProcessPumpProblemsDueTime(s)
- call ProcessRotaryProblemsDueTime(s)
- call ProcessKickProblemsDueTime(s)
-
- #ifdef S_BopStack
- ApiResult = ResumeThread(BopStackThreadHandle)
- #endif
- #ifdef S_Pump1
- ApiResult = ResumeThread(Pump1ThreadHandle)
- #endif
- #ifdef S_Pump2
- ApiResult = ResumeThread(Pump2ThreadHandle)
- #endif
- #ifdef S_Pump3
- ApiResult = ResumeThread(Pump3ThreadHandle)
- #endif
- #ifdef S_ChokeControl
- ApiResult = ResumeThread(ChokeControlThreadHandle)
- #endif
- #ifdef S_Rop
- ApiResult = ResumeThread(RopThreadHandle)
- #endif
- #ifdef S_RotaryTable
- ApiResult = ResumeThread(RotaryTableThreadHandle)
- #endif
- #ifdef S_Drawworks
- ApiResult = ResumeThread(DrawworksThreadHandle)
- #endif
- #ifdef S_FluidFlow
- ApiResult = ResumeThread(FluidFlowThreadHandle)
- #endif
- #ifdef S_TorqueDrag
- ApiResult = ResumeThread(TorqueDragThreadHandle)
- #endif
- #ifdef S_TopDrive
- ApiResult = ResumeThread(TopDriveThreadHandle)
- #endif
- #ifdef S_MudSystem
- ApiResult = ResumeThread(MudSystemThreadHandle)
- #endif
- #ifdef S_PipeRams1
- ApiResult = ResumeThread(PipeRams1ThreadHandle)
- #endif
- #ifdef S_PipeRams2
- ApiResult = ResumeThread(PipeRams2ThreadHandle)
- #endif
- #ifdef S_KillLine
- ApiResult = ResumeThread(KillLineThreadHandle)
- #endif
- #ifdef S_ChokeLine
- ApiResult = ResumeThread(ChokeLineThreadHandle)
- #endif
- #ifdef S_BlindRams
- ApiResult = ResumeThread(BlindRamsThreadHandle)
- #endif
- #ifdef S_Annular ت
- ApiResult = ResumeThread(AnnularThreadHandle)
- #endif
- #ifdef S_Geo
- ApiResult = ResumeThread(GeoThreadHandle)
- #endif
-
-
-
- #ifdef S_Sample
- ApiResult = ResumeThread(SampleThreadHandle)
- #endif
-
- end subroutine
-
- subroutine StateChanged(state)
- !DEC$ ATTRIBUTES DLLEXPORT :: StateChanged
- !DEC$ ATTRIBUTES ALIAS: 'StateChanged' :: StateChanged
- implicit none
- integer, intent(in) :: state
- SimulationState = state
- if(SimulationState == SimulationState_Paused) call PauseSimulation()
- end subroutine
-
- subroutine SetSimulationSpeed(speed)
- !DEC$ ATTRIBUTES DLLEXPORT :: SetSimulationSpeed
- !DEC$ ATTRIBUTES ALIAS: 'SetSimulationSpeed' :: SetSimulationSpeed
- implicit none
- integer, intent(in) :: speed
- SimulationSpeed = speed
- end subroutine
-
-
- subroutine SetSnapshot(s)
- !DEC$ ATTRIBUTES DLLEXPORT::SetSnapshot
- !DEC$ ATTRIBUTES ALIAS: 'SetSnapshot' :: SetSnapshot
- implicit none
- logical, intent(in) :: s
- IsSnapshot = s
- !if(IsSnapshot) SimulationState_old = SimulationState_Started
- end subroutine SetSnapshot
-
-
- subroutine TotalStrokesDue(strokes)
- use CBitProblemsVariables
- use CBopProblemsVariables
- use CChokeProblemsVariables
- use CDrillStemProblemsVariables
- use CGaugesProblemsVariables
- use CHoistingProblemsVariables
- use CLostProblemsVariables
- use CMudTreatmentProblemsVariables
- use COtherProblemsVariables
- use CPumpProblemsVariables
- use CRotaryProblemsVariables
- use CKickProblemsVariables
- implicit none
- integer, intent(in) :: strokes
- call ProcessBitProblemsDuePumpStrokes(strokes)
- call ProcessBopProblemsDuePumpStrokes(strokes)
- call ProcessChokeProblemsDuePumpStrokes(strokes)
- call ProcessDrillStemProblemsDuePumpStrokes(strokes)
- call ProcessGaugesProblemsDuePumpStrokes(strokes)
- call ProcessHoistingProblemsDuePumpStrokes(strokes)
- call ProcessLostProblemsDuePumpStrokes(strokes)
- call ProcessMudTreatmentProblemsDuePumpStrokes(strokes)
- call ProcessOtherProblemsDuePumpStrokes(strokes)
- call ProcessPumpProblemsDuePumpStrokes(strokes)
- call ProcessRotaryProblemsDuePumpStrokes(strokes)
- call ProcessKickProblemsDuePumpStrokes(strokes)
-
- end subroutine
-
- subroutine TotalVolumePumpedDue(volume)
- use CBitProblemsVariables
- use CBopProblemsVariables
- use CChokeProblemsVariables
- use CDrillStemProblemsVariables
- use CGaugesProblemsVariables
- use CHoistingProblemsVariables
- use CLostProblemsVariables
- use CMudTreatmentProblemsVariables
- use COtherProblemsVariables
- use CPumpProblemsVariables
- use CRotaryProblemsVariables
- use CKickProblemsVariables
- implicit none
- real(8), intent(in) :: volume
- call ProcessBitProblemsDueVolumePumped(volume)
- call ProcessBopProblemsDueVolumePumped(volume)
- call ProcessChokeProblemsDueVolumePumped(volume)
- call ProcessDrillStemProblemsDueVolumePumped(volume)
- call ProcessGaugesProblemsDueVolumePumped(volume)
- call ProcessHoistingProblemsDueVolumePumped(volume)
- call ProcessLostProblemsDueVolumePumped(volume)
- call ProcessMudTreatmentProblemsDueVolumePumped(volume)
- call ProcessOtherProblemsDueVolumePumped(volume)
- call ProcessPumpProblemsDueVolumePumped(volume)
- call ProcessRotaryProblemsDueVolumePumped(volume)
- call ProcessKickProblemsDueVolumePumped(volume)
-
- end subroutine
-
- subroutine DistanceDrilledDue(distance)
- use CBitProblemsVariables
- use CBopProblemsVariables
- use CChokeProblemsVariables
- use CDrillStemProblemsVariables
- use CGaugesProblemsVariables
- use CHoistingProblemsVariables
- use CLostProblemsVariables
- use CMudTreatmentProblemsVariables
- use COtherProblemsVariables
- use CPumpProblemsVariables
- use CRotaryProblemsVariables
- use CKickProblemsVariables
- implicit none
- real(8), intent(in) :: distance
- call ProcessBitProblemsDueDistanceDrilled(distance)
- call ProcessBopProblemsDueDistanceDrilled(distance)
- call ProcessChokeProblemsDueDistanceDrilled(distance)
- call ProcessDrillStemProblemsDueDistanceDrilled(distance)
- call ProcessGaugesProblemsDueDistanceDrilled(distance)
- call ProcessHoistingProblemsDueDistanceDrilled(distance)
- call ProcessLostProblemsDueDistanceDrilled(distance)
- call ProcessMudTreatmentProblemsDueDistanceDrilled(distance)
- call ProcessOtherProblemsDueDistanceDrilled(distance)
- call ProcessPumpProblemsDueDistanceDrilled(distance)
- call ProcessRotaryProblemsDueDistanceDrilled(distance)
- call ProcessKickProblemsDueDistanceDrilled(distance)
- end subroutine
-
-
-
-
- subroutine BopStack_Thread
- implicit none
- ApiResult = SuspendThread(BopStackThreadHandle)
- end subroutine BopStack_Thread
-
- subroutine Pump1_Thread
- implicit none
- ApiResult = SuspendThread(Pump1ThreadHandle)
- end subroutine Pump1_Thread
-
- subroutine Pump2_Thread
- implicit none
- ApiResult = SuspendThread(Pump2ThreadHandle)
- end subroutine Pump2_Thread
-
- subroutine Pump3_Thread
- implicit none
- ApiResult = SuspendThread(Pump3ThreadHandle)
- end subroutine Pump3_Thread
-
- subroutine ChokeControl_Thread
- implicit none
- ApiResult = SuspendThread(ChokeControlThreadHandle)
- end subroutine ChokeControl_Thread
-
- subroutine Rop_Thread
- implicit none
- ApiResult = SuspendThread(RopThreadHandle)
- end subroutine Rop_Thread
-
- subroutine RotaryTable_Thread
- implicit none
- ApiResult = SuspendThread(RotaryTableThreadHandle)
- end subroutine RotaryTable_Thread
-
- subroutine Drawworks_Thread
- implicit none
- ApiResult = SuspendThread(DrawworksThreadHandle)
- end subroutine Drawworks_Thread
-
- subroutine FluidFlow_Thread
- implicit none
- ApiResult = SuspendThread(FluidFlowThreadHandle)
- end subroutine FluidFlow_Thread
-
- subroutine TorqueDrag_Thread
- implicit none
- ApiResult = SuspendThread(TorqueDragThreadHandle)
- end subroutine TorqueDrag_Thread
-
- subroutine TopDrive_Thread
- implicit none
- ApiResult = SuspendThread(TopDriveThreadHandle)
- end subroutine TopDrive_Thread
-
- subroutine MudSystem_Thread
- implicit none
- ApiResult = SuspendThread(MudSystemThreadHandle)
- end subroutine MudSystem_Thread
-
- subroutine PipeRams1_Thread
- implicit none
- ApiResult = SuspendThread(PipeRams1ThreadHandle)
- end subroutine PipeRams1_Thread
-
- subroutine PipeRams2_Thread
- implicit none
- ApiResult = SuspendThread(PipeRams2ThreadHandle)
- end subroutine PipeRams2_Thread
-
- subroutine KillLine_Thread
- implicit none
- ApiResult = SuspendThread(KillLineThreadHandle)
- end subroutine KillLine_Thread
-
- subroutine ChokeLine_Thread
- implicit none
- ApiResult = SuspendThread(ChokeLineThreadHandle)
- end subroutine ChokeLine_Thread
-
- subroutine BlindRams_Thread
- implicit none
- ApiResult = SuspendThread(BlindRamsThreadHandle)
- end subroutine BlindRams_Thread
-
- subroutine Annular_Thread
- implicit none
- ApiResult = SuspendThread(AnnularThreadHandle)
- end subroutine Annular_Thread
-
- subroutine Geo_Thread
- implicit none
- ApiResult = SuspendThread(GeoThreadHandle)
- end subroutine Geo_Thread
-
-
-
- subroutine Sample_Thread
- implicit none
- ApiResult = SuspendThread(SampleThreadHandle)
- end subroutine Sample_Thread
-
- end module CSimulation
|