module CSimulationVariables use CVoidEventHandlerCollection ! use CSimulationThreads use CIActionReference ! use ifcore ! use ifmt ! use CTimer use CError use CLog3 implicit none public integer, parameter :: SimulationState_Stopped = 0; integer, parameter :: SimulationState_Started = 1; integer, parameter :: SimulationState_Paused = 2; logical :: IsStopped = .false. logical :: IsSnapshot = .false. logical :: IsPortable = .false. integer :: IsPortableInt = 0 integer :: SimulationState_old integer :: SimulationState integer :: SimulationTime integer :: SimulationSpeed ! 1, 2, 5, 10 integer :: SleepLimit = 0 integer :: TotalPumpStrokes real(8) :: TotalVolumePumped real(8) :: DistanceDrilled type(VoidEventHandlerCollection) :: OnSimulationInitialization type(VoidEventHandlerCollection) :: OnSimulationStart type(VoidEventHandlerCollection) :: OnSimulationStop type(VoidEventHandlerCollection) :: OnSimulationPause !type(VoidEventHandlerCollection) :: OnSimulationGetOutput procedure (ActionVoid), pointer :: ForceRealTimeSpeedPtr procedure (ActionBool), pointer :: SpeedChangePossibilityPtr logical :: SpeedChangePossibilityValue procedure (ActionInteger), pointer :: TotalStrokesChangedPtr procedure (ActionInteger), pointer :: TotalStrokesPtr procedure (ActionDouble), pointer :: TotalVolumePumpedPtr procedure (ActionDouble), pointer :: DistanceDrilledPtr ! modules... !BopStack type(VoidEventHandlerCollection) :: OnBopStackStep type(VoidEventHandlerCollection) :: OnBopStackStart type(VoidEventHandlerCollection) :: OnBopStackOutput type(VoidEventHandlerCollection) :: OnBopStackPause type(VoidEventHandlerCollection) :: OnBopStackMain logical :: BopStackStarted !Pumps type(VoidEventHandlerCollection) :: OnPump1Step type(VoidEventHandlerCollection) :: OnPump1Start type(VoidEventHandlerCollection) :: OnPump1Output type(VoidEventHandlerCollection) :: OnPump1Pause type(VoidEventHandlerCollection) :: OnPump1Main logical :: Pump1Started type(VoidEventHandlerCollection) :: OnPump2Step type(VoidEventHandlerCollection) :: OnPump2Start type(VoidEventHandlerCollection) :: OnPump2Output type(VoidEventHandlerCollection) :: OnPump2Pause type(VoidEventHandlerCollection) :: OnPump2Main logical :: Pump2Started type(VoidEventHandlerCollection) :: OnPump3Step type(VoidEventHandlerCollection) :: OnPump3Start type(VoidEventHandlerCollection) :: OnPump3Output type(VoidEventHandlerCollection) :: OnPump3Pause type(VoidEventHandlerCollection) :: OnPump3Main logical :: Pump3Started !ChokeControl type(VoidEventHandlerCollection) :: OnChokeControlStep type(VoidEventHandlerCollection) :: OnChokeControlStart type(VoidEventHandlerCollection) :: OnChokeControlOutput type(VoidEventHandlerCollection) :: OnChokeControlPause type(VoidEventHandlerCollection) :: OnChokeControlMain logical :: ChokeControlStarted !ROP type(VoidEventHandlerCollection) :: OnRopStep type(VoidEventHandlerCollection) :: OnRopStart type(VoidEventHandlerCollection) :: OnRopOutput type(VoidEventHandlerCollection) :: OnRopPause type(VoidEventHandlerCollection) :: OnRopMain logical :: RopStarted !RotaryTable type(VoidEventHandlerCollection) :: OnRotaryTableStep type(VoidEventHandlerCollection) :: OnRotaryTableStart type(VoidEventHandlerCollection) :: OnRotaryTableOutput type(VoidEventHandlerCollection) :: OnRotaryTablePause type(VoidEventHandlerCollection) :: OnRotaryTableMain logical :: RotaryTableStarted !Drawworks type(VoidEventHandlerCollection) :: OnDrawworksStep type(VoidEventHandlerCollection) :: OnDrawworksStart type(VoidEventHandlerCollection) :: OnDrawworksOutput type(VoidEventHandlerCollection) :: OnDrawworksPause type(VoidEventHandlerCollection) :: OnDrawworksMain logical :: DrawworksStarted !FluidFlow type(VoidEventHandlerCollection) :: OnFluidFlowStep type(VoidEventHandlerCollection) :: OnFluidFlowStart type(VoidEventHandlerCollection) :: OnFluidFlowOutput type(VoidEventHandlerCollection) :: OnFluidFlowPause type(VoidEventHandlerCollection) :: OnFluidFlowMain logical :: FluidFlowStarted !TorqueDrag type(VoidEventHandlerCollection) :: OnTorqueDragStep type(VoidEventHandlerCollection) :: OnTorqueDragStart type(VoidEventHandlerCollection) :: OnTorqueDragOutput type(VoidEventHandlerCollection) :: OnTorqueDragPause type(VoidEventHandlerCollection) :: OnTorqueDragMain logical :: TorqueDragStarted !TopDrive type(VoidEventHandlerCollection) :: OnTopDriveStep type(VoidEventHandlerCollection) :: OnTopDriveStart type(VoidEventHandlerCollection) :: OnTopDriveOutput type(VoidEventHandlerCollection) :: OnTopDrivePause type(VoidEventHandlerCollection) :: OnTopDriveMain logical :: TopDriveStarted !MudSystem type(VoidEventHandlerCollection) :: OnMudSystemStep type(VoidEventHandlerCollection) :: OnMudSystemStart type(VoidEventHandlerCollection) :: OnMudSystemOutput type(VoidEventHandlerCollection) :: OnMudSystemPause type(VoidEventHandlerCollection) :: OnMudSystemMain logical :: MudSystemStarted !PipeRams1 type(VoidEventHandlerCollection) :: OnPipeRams1Step type(VoidEventHandlerCollection) :: OnPipeRams1Start type(VoidEventHandlerCollection) :: OnPipeRams1Output type(VoidEventHandlerCollection) :: OnPipeRams1Pause type(VoidEventHandlerCollection) :: OnPipeRams1Main logical :: PipeRams1Started !PipeRams2 type(VoidEventHandlerCollection) :: OnPipeRams2Step type(VoidEventHandlerCollection) :: OnPipeRams2Start type(VoidEventHandlerCollection) :: OnPipeRams2Output type(VoidEventHandlerCollection) :: OnPipeRams2Pause type(VoidEventHandlerCollection) :: OnPipeRams2Main logical :: PipeRams2Started !KillLine type(VoidEventHandlerCollection) :: OnKillLineStep type(VoidEventHandlerCollection) :: OnKillLineStart type(VoidEventHandlerCollection) :: OnKillLineOutput type(VoidEventHandlerCollection) :: OnKillLinePause type(VoidEventHandlerCollection) :: OnKillLineMain logical :: KillLineStarted !ChokeLine type(VoidEventHandlerCollection) :: OnChokeLineStep type(VoidEventHandlerCollection) :: OnChokeLineStart type(VoidEventHandlerCollection) :: OnChokeLineOutput type(VoidEventHandlerCollection) :: OnChokeLinePause type(VoidEventHandlerCollection) :: OnChokeLineMain logical :: ChokeLineStarted !BlindRams type(VoidEventHandlerCollection) :: OnBlindRamsStep type(VoidEventHandlerCollection) :: OnBlindRamsStart type(VoidEventHandlerCollection) :: OnBlindRamsOutput type(VoidEventHandlerCollection) :: OnBlindRamsPause type(VoidEventHandlerCollection) :: OnBlindRamsMain logical :: BlindRamsStarted !Annular type(VoidEventHandlerCollection) :: OnAnnularStep type(VoidEventHandlerCollection) :: OnAnnularStart type(VoidEventHandlerCollection) :: OnAnnularOutput type(VoidEventHandlerCollection) :: OnAnnularPause type(VoidEventHandlerCollection) :: OnAnnularMain logical :: AnnularStarted !Geo type(VoidEventHandlerCollection) :: OnGeoStep type(VoidEventHandlerCollection) :: OnGeoStart type(VoidEventHandlerCollection) :: OnGeoOutput type(VoidEventHandlerCollection) :: OnGeoPause type(VoidEventHandlerCollection) :: OnGeoMain logical :: GeoStarted !OperationScenarios type(VoidEventHandlerCollection) :: OnOperationScenariosStep type(VoidEventHandlerCollection) :: OnOperationScenariosOutput type(VoidEventHandlerCollection) :: OnOperationScenariosPause type(VoidEventHandlerCollection) :: OnOperationScenariosMain !PathFinding type(VoidEventHandlerCollection) :: OnPathFindingStep type(VoidEventHandlerCollection) :: OnPathFindingOutput type(VoidEventHandlerCollection) :: OnPathFindingPause type(VoidEventHandlerCollection) :: OnPathFindingMain ! sample type(VoidEventHandlerCollection) :: OnSampleStep type(VoidEventHandlerCollection) :: OnSampleStart type(VoidEventHandlerCollection) :: OnSampleOutput type(VoidEventHandlerCollection) :: OnSamplePause type(VoidEventHandlerCollection) :: OnSampleMain logical :: SampleStarted !!MudFlowFillIndicator !type(VoidEventHandlerCollection) :: OnMudFlowFillIndicatorStep !type(VoidEventHandlerCollection) :: OnMudFlowFillIndicatorOutput !type(VoidEventHandlerCollection) :: OnMudFlowFillIndicatorMain contains ! subroutine Quit() ! use ifmt ! call ExitThread(0) ! end subroutine real function GetSimulationSpeedSecond() implicit none GetSimulationSpeedSecond = 1.0 / SimulationSpeed end function GetSimulationSpeedSecond integer function GetSimulationSpeedMilisecond() implicit none GetSimulationSpeedMilisecond = int(GetSimulationSpeedSecond()* 1000.0) end function GetSimulationSpeedMilisecond subroutine DrillMode_ON() implicit none call SpeedChangePossibility(.true.) end subroutine subroutine DrillMode_OFF() implicit none call ForceRealTimeSpeed() call SpeedChangePossibility(.false.) end subroutine subroutine ForceRealTimeSpeed() implicit none if(associated(ForceRealTimeSpeedPtr)) call ForceRealTimeSpeedPtr() end subroutine subroutine SpeedChangePossibility(v) implicit none logical, intent(in) :: v SpeedChangePossibilityValue = v if(associated(SpeedChangePossibilityPtr)) call SpeedChangePossibilityPtr(SpeedChangePossibilityValue) end subroutine subroutine SubscribeSpeedChangePossibility(a) !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeSpeedChangePossibility !DEC$ ATTRIBUTES ALIAS: 'SubscribeSpeedChangePossibility' :: SubscribeSpeedChangePossibility implicit none procedure (ActionBool) :: a SpeedChangePossibilityPtr => a end subroutine subroutine SubscribeForceRealTimeSpeed(a) !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeForceRealTimeSpeed !DEC$ ATTRIBUTES ALIAS: 'SubscribeForceRealTimeSpeed' :: SubscribeForceRealTimeSpeed implicit none procedure (ActionVoid) :: a ForceRealTimeSpeedPtr => a end subroutine subroutine SubscribeTotalStrokesChanged(a) !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeTotalStrokesChanged !DEC$ ATTRIBUTES ALIAS: 'SubscribeTotalStrokesChanged' :: SubscribeTotalStrokesChanged implicit none procedure (ActionInteger) :: a TotalStrokesChangedPtr => a end subroutine subroutine SetTotalStrokes(strokes) implicit none integer, intent(in) :: strokes if (TotalPumpStrokes == strokes) return TotalPumpStrokes = strokes if(associated(TotalStrokesChangedPtr)) call TotalStrokesChangedPtr(TotalPumpStrokes) if(associated(TotalStrokesPtr)) call TotalStrokesPtr(TotalPumpStrokes) end subroutine subroutine SetTotalVolumePumped(volume) implicit none real(8), intent(in) :: volume if (TotalVolumePumped == volume) return TotalVolumePumped = volume if(associated(TotalVolumePumpedPtr)) call TotalVolumePumpedPtr(TotalVolumePumped) end subroutine subroutine SetDistanceDrilled(distance) implicit none real(8), intent(in) :: distance if (DistanceDrilled == distance) return DistanceDrilled = distance if(associated(DistanceDrilledPtr)) call DistanceDrilledPtr(DistanceDrilled) end subroutine ! integer(4) function BopStackThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_bopstackthread" :: BopStackThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_BopStack ! call OnBopStackMain%RunAll() ! #endif ! #ifdef S_BopStack ! if(.not.BopStackStarted) then ! call OnBopStackStart%RunAll() ! BopStackStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnBopStackStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('BOP Stack Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnBopStackOutput%RunAll() ! end do ! call OnBopStackPause%RunAll() ! end do loop ! #endif ! BopStackThread = 0; ! call ExitThread(0) ! end function BopStackThread ! integer(4) function Pump1Thread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_pump1thread" :: Pump1Thread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_Pump1 ! call OnPump1Main%RunAll() ! #endif ! #ifdef S_Pump1 ! if(.not.Pump1Started) then ! call OnPump1Start%RunAll() ! Pump1Started = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnPump1Step%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Pump 1 Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnPump1Output%RunAll() ! end do ! call OnPump1Pause%RunAll() ! end do loop ! #endif ! Pump1Thread = 0; ! call ExitThread(0) ! end function Pump1Thread ! integer(4) function Pump2Thread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_pump2thread" :: Pump2Thread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_Pump2 ! call OnPump2Main%RunAll() ! #endif ! #ifdef S_Pump2 ! if(.not.Pump2Started) then ! call OnPump2Start%RunAll() ! Pump2Started = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnPump2Step%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Pump 2 Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnPump2Output%RunAll() ! end do ! call OnPump2Pause%RunAll() ! end do loop ! #endif ! Pump2Thread = 0; ! call ExitThread(0) ! end function Pump2Thread ! integer(4) function Pump3Thread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_pump3thread" :: Pump3Thread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_Pump3 ! call OnPump3Main%RunAll() ! #endif ! #ifdef S_Pump3 ! if(.not.Pump3Started) then ! call OnPump3Start%RunAll() ! Pump3Started = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnPump3Step%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Pump 3 Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnPump3Output%RunAll() ! end do ! call OnPump3Pause%RunAll() ! end do loop ! #endif ! Pump3Thread = 0; ! call ExitThread(0) ! end function Pump3Thread ! integer(4) function ChokeControlThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_chokecontrolthread" :: ChokeControlThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_ChokeControl ! call OnChokeControlMain%RunAll() ! #endif ! #ifdef S_ChokeControl ! if(.not.ChokeControlStarted) then ! call OnChokeControlStart%RunAll() ! ChokeControlStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnChokeControlStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Choke Control Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnChokeControlOutput%RunAll() ! end do ! call OnChokeControlPause%RunAll() ! end do loop ! #endif ! ChokeControlThread = 0; ! call ExitThread(0) ! end function ChokeControlThread ! integer(4) function RopThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_ropthread" :: RopThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_Rop ! call OnRopMain%RunAll() ! #endif ! #ifdef S_Rop ! if(.not.RopStarted) then ! call OnRopStart%RunAll() ! RopStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnRopStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('ROP Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnRopOutput%RunAll() ! end do ! call OnRopPause%RunAll() ! end do loop ! #endif ! RopThread = 0; ! call ExitThread(0) ! end function RopThread ! integer(4) function RotaryTableThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_rotarytablethread" :: RotaryTableThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_RotaryTable ! call OnRotaryTableMain%RunAll() ! #endif ! #ifdef S_RotaryTable ! if(.not.RotaryTableStarted) then ! call OnRotaryTableStart%RunAll() ! RotaryTableStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnRotaryTableStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Rotary Table Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnRotaryTableOutput%RunAll() ! end do ! call OnRotaryTablePause%RunAll() ! end do loop ! #endif ! RotaryTableThread = 0; ! call ExitThread(0) ! end function RotaryTableThread ! integer(4) function DrawworksThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_drawworksthread" :: DrawworksThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_Drawworks ! call OnDrawworksMain%RunAll() ! #endif ! #ifdef S_Drawworks ! if(.not.DrawworksStarted) then ! call OnDrawworksStart%RunAll() ! DrawworksStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnDrawworksStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Drawworks Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnDrawworksOutput%RunAll() ! end do ! call OnDrawworksPause%RunAll() ! end do loop ! #endif ! DrawworksThread = 0; ! call ExitThread(0) ! end function DrawworksThread ! integer(4) function FluidFlowThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_fluidflowthread" :: FluidFlowThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_FluidFlow ! call OnFluidFlowMain%RunAll() ! #endif ! #ifdef S_FluidFlow ! if(.not.FluidFlowStarted) then ! call OnFluidFlowStart%RunAll() ! FluidFlowStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnFluidFlowStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Fluid Flow Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnFluidFlowOutput%RunAll() ! end do ! call OnFluidFlowPause%RunAll() ! end do loop ! #endif ! FluidFlowThread = 0; ! call ExitThread(0) ! end function FluidFlowThread ! integer(4) function TorqueDragThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_torquedragthread" :: TorqueDragThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_TorqueDrag ! call OnTorqueDragMain%RunAll() ! #endif ! #ifdef S_TorqueDrag ! if(.not.TorqueDragStarted) then ! call OnTorqueDragStart%RunAll() ! TorqueDragStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnTorqueDragStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Torque Drag Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnTorqueDragOutput%RunAll() ! end do ! call OnTorqueDragPause%RunAll() ! end do loop ! #endif ! TorqueDragThread = 0; ! call ExitThread(0) ! end function TorqueDragThread ! integer(4) function TopDriveThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_topdrivethread" :: TopDriveThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_TopDrive ! call OnTopDriveMain%RunAll() ! #endif ! #ifdef S_TopDrive ! if(.not.TopDriveStarted) then ! call OnTopDriveStart%RunAll() ! TopDriveStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnTopDriveStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('TopDrive Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnTopDriveOutput%RunAll() ! end do ! call OnTopDrivePause%RunAll() ! end do loop ! #endif ! TopDriveThread = 0; ! call ExitThread(0) ! end function TopDriveThread ! integer(4) function MudSystemThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_MudSystemthread" :: MudSystemThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_MudSystem ! call OnMudSystemMain%RunAll() ! #endif ! #ifdef S_MudSystem ! if(.not.MudSystemStarted) then ! call OnMudSystemStart%RunAll() ! MudSystemStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnMudSystemStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Mud System Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnMudSystemOutput%RunAll() ! end do ! call OnMudSystemPause%RunAll() ! end do loop ! #endif ! MudSystemThread = 0; ! call ExitThread(0) ! end function MudSystemThread ! integer(4) function PipeRams1Thread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_piperams1thread" :: PipeRams1Thread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_PipeRams1 ! call OnPipeRams1Main%RunAll() ! #endif ! #ifdef S_PipeRams1 ! if(.not.PipeRams1Started) then ! call OnPipeRams1Start%RunAll() ! PipeRams1Started = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnPipeRams1Step%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Pipe Rams 1 Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnPipeRams1Output%RunAll() ! end do ! call OnPipeRams1Pause%RunAll() ! end do loop ! #endif ! PipeRams1Thread = 0; ! call ExitThread(0) ! end function PipeRams1Thread ! integer(4) function PipeRams2Thread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_piperams2thread" :: PipeRams2Thread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_PipeRams2 ! call OnPipeRams2Main%RunAll() ! #endif ! #ifdef S_PipeRams2 ! if(.not.PipeRams2Started) then ! call OnPipeRams2Start%RunAll() ! PipeRams2Started = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnPipeRams2Step%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Pipe Rams 2 Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnPipeRams2Output%RunAll() ! end do ! call OnPipeRams2Pause%RunAll() ! end do loop ! #endif ! PipeRams2Thread = 0; ! call ExitThread(0) ! end function PipeRams2Thread ! integer(4) function KillLineThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_killlinethread" :: KillLineThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_KillLine ! call OnKillLineMain%RunAll() ! #endif ! #ifdef S_KillLine ! if(.not.KillLineStarted) then ! call OnKillLineStart%RunAll() ! KillLineStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnKillLineStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Kill Line Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnKillLineOutput%RunAll() ! end do ! call OnKillLinePause%RunAll() ! end do loop ! #endif ! KillLineThread = 0; ! call ExitThread(0) ! end function KillLineThread ! integer(4) function ChokeLineThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_chokelinethread" :: ChokeLineThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_ChokeLine ! call OnChokeLineMain%RunAll() ! #endif ! #ifdef S_ChokeLine ! if(.not.ChokeLineStarted) then ! call OnChokeLineStart%RunAll() ! ChokeLineStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnChokeLineStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Choke Line Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnChokeLineOutput%RunAll() ! end do ! call OnChokeLinePause%RunAll() ! end do loop ! #endif ! ChokeLineThread = 0; ! call ExitThread(0) ! end function ChokeLineThread ! integer(4) function BlindRamsThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_blindramsthread" :: BlindRamsThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_BlindRams ! call OnBlindRamsMain%RunAll() ! #endif ! #ifdef S_BlindRams ! if(.not.BlindRamsStarted) then ! call OnBlindRamsStart%RunAll() ! BlindRamsStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnBlindRamsStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Blind Rams Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnBlindRamsOutput%RunAll() ! end do ! call OnBlindRamsPause%RunAll() ! end do loop ! #endif ! BlindRamsThread = 0; ! call ExitThread(0) ! end function BlindRamsThread ! integer(4) function AnnularThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_annularthread" :: AnnularThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_Annular ! call OnAnnularMain%RunAll() ! #endif ! #ifdef S_Annular ! if(.not.AnnularStarted) then ! call OnAnnularStart%RunAll() ! AnnularStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnAnnularStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Annular Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnAnnularOutput%RunAll() ! end do ! call OnAnnularPause%RunAll() ! end do loop ! #endif ! AnnularThread = 0; ! call ExitThread(0) ! end function AnnularThread ! integer(4) function GeoThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_geothread" :: GeoThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_Geo ! call OnGeoMain%RunAll() ! #endif ! #ifdef S_Geo ! if(.not.GeoStarted) then ! call OnGeoStart%RunAll() ! GeoStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnGeoStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Geo Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnGeoOutput%RunAll() ! end do ! call OnGeoPause%RunAll() ! end do loop ! #endif ! GeoThread = 0; ! call ExitThread(0) ! end function GeoThread ! integer(4) function OperationScenariosThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_operationscenariosthread" :: OperationScenariosThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! call OnOperationScenariosMain%RunAll() ! OperationScenariosThread = 0; ! call ExitThread(0) ! end function OperationScenariosThread ! integer(4) function PathFindingThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_pathfindingthread" :: PathFindingThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! call OnPathFindingMain%RunAll() ! PathFindingThread = 0; ! call ExitThread(0) ! end function PathFindingThread ! integer(4) function SampleThread(arg) ! !DEC$ ATTRIBUTES STDCALL, ALIAS:"_samplethread" :: SampleThread ! use ifport ! use ifmt ! implicit none ! integer(4), pointer :: arg ! integer i, j ! integer elapsed, speed, remaining ! type(Timer) t ! #ifdef M_Sample ! call OnSampleMain%RunAll() ! #endif ! #ifdef S_Sample ! if(.not.SampleStarted) then ! call OnSampleStart%RunAll() ! SampleStarted = .true. ! end if ! loop: do ! if(IsStopped) call ExitThread(0) ! do i=1, 10 ! if(IsStopped) call ExitThread(0) ! call t%Start() ! do j=1, SimulationSpeed ! if(IsStopped) call ExitThread(0) ! call OnSampleStep%RunAll() ! end do ! call t%Finish() ! elapsed = t%ElapsedTimeMs() ! remaining = 100 - elapsed ! #ifdef E_SpeedWatchdog ! if(elapsed > 100) call Error('Sample Module: exceeding more than 100ms interval, the time was ', elapsed) ! #endif ! if(remaining > 0 .and. i < 10) call sleepqq(remaining - SleepLimit) ! call OnSampleOutput%RunAll() ! end do ! call OnSamplePause%RunAll() ! end do loop ! #endif ! SampleThread = 0; ! call ExitThread(0) ! end function SampleThread end module CSimulationVariables