|
- module CBopProblemsVariables
- use CProblemDifinition
- implicit none
- public
-
- ! Input vars
- type::BopProblemsType
- type(CProblem) :: AnnularWash
- type(CProblem) :: AnnularFail
- type(CProblem) :: AnnularLeak
- type(CProblem) :: UpperRamWash
- type(CProblem) :: UpperRamFail
- type(CProblem) :: UpperRamLeak
- type(CProblem) :: MiddleRamWash
- type(CProblem) :: MiddleRamFail
- type(CProblem) :: MiddleRamLeak
- type(CProblem) :: LowerRamWash
- type(CProblem) :: LowerRamFail
- type(CProblem) :: LowerRamLeak
- type(CProblem) :: AccumulatorPumpFail
- type(CProblem) :: AccumulatorPumpLeak
- type(CProblem) :: AccumulatorSystemFail
- type(CProblem) :: AccumulatorSystemLeak
- end type BopProblemsType
- type(BopProblemsType)::BopProblems
-
- ! procedure (ActionInteger), pointer :: AnnularWashPtr
- ! procedure (ActionInteger), pointer :: AnnularFailPtr
- ! procedure (ActionInteger), pointer :: AnnularLeakPtr
- ! procedure (ActionInteger), pointer :: UpperRamWashPtr
- ! procedure (ActionInteger), pointer :: UpperRamFailPtr
- ! procedure (ActionInteger), pointer :: UpperRamLeakPtr
- ! procedure (ActionInteger), pointer :: MiddleRamWashPtr
- ! procedure (ActionInteger), pointer :: MiddleRamFailPtr
- ! procedure (ActionInteger), pointer :: MiddleRamLeakPtr
- ! procedure (ActionInteger), pointer :: LowerRamWashPtr
- ! procedure (ActionInteger), pointer :: LowerRamFailPtr
- ! procedure (ActionInteger), pointer :: LowerRamLeakPtr
- ! procedure (ActionInteger), pointer :: AccumulatorPumpFailPtr
- ! procedure (ActionInteger), pointer :: AccumulatorPumpLeakPtr
- ! procedure (ActionInteger), pointer :: AccumulatorSystemFailPtr
- ! procedure (ActionInteger), pointer :: AccumulatorSystemLeakPtr
-
- contains
-
- subroutine ProcessBopProblemsDueTime(time)
- implicit none
- integer :: time
- if(BopProblems%AnnularWash%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%AnnularWash, ChangeAnnularWash, time)
- if(BopProblems%AnnularFail%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%AnnularFail, ChangeAnnularFail, time)
- if(BopProblems%AnnularLeak%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%AnnularLeak, ChangeAnnularLeak, time)
- if(BopProblems%UpperRamWash%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%UpperRamWash, ChangeUpperRamWash, time)
- if(BopProblems%UpperRamFail%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%UpperRamFail, ChangeUpperRamFail, time)
- if(BopProblems%UpperRamLeak%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%UpperRamLeak, ChangeUpperRamLeak, time)
- if(BopProblems%MiddleRamWash%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%MiddleRamWash, ChangeMiddleRamWash, time)
- if(BopProblems%MiddleRamFail%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%MiddleRamFail, ChangeMiddleRamFail, time)
- if(BopProblems%MiddleRamLeak%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%MiddleRamLeak, ChangeMiddleRamLeak, time)
- if(BopProblems%LowerRamWash%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%LowerRamWash, ChangeLowerRamWash, time)
- if(BopProblems%LowerRamFail%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%LowerRamFail, ChangeLowerRamFail, time)
- if(BopProblems%LowerRamLeak%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%LowerRamLeak, ChangeLowerRamLeak, time)
- if(BopProblems%AccumulatorPumpFail%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%AccumulatorPumpFail, ChangeAccumulatorPumpFail, time)
- if(BopProblems%AccumulatorPumpLeak%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%AccumulatorPumpLeak, ChangeAccumulatorPumpLeak, time)
- if(BopProblems%AccumulatorSystemFail%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%AccumulatorSystemFail, ChangeAccumulatorSystemFail, time)
- if(BopProblems%AccumulatorSystemLeak%ProblemType == Time_ProblemType) call ProcessDueTime(BopProblems%AccumulatorSystemLeak, ChangeAccumulatorSystemLeak, time)
- end subroutine
-
- subroutine ProcessBopProblemsDuePumpStrokes(strokes)
- implicit none
- integer :: strokes
- if(BopProblems%AnnularWash%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%AnnularWash, ChangeAnnularWash, strokes)
- if(BopProblems%AnnularFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%AnnularFail, ChangeAnnularFail, strokes)
- if(BopProblems%AnnularLeak%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%AnnularLeak, ChangeAnnularLeak, strokes)
- if(BopProblems%UpperRamWash%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%UpperRamWash, ChangeUpperRamWash, strokes)
- if(BopProblems%UpperRamFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%UpperRamFail, ChangeUpperRamFail, strokes)
- if(BopProblems%UpperRamLeak%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%UpperRamLeak, ChangeUpperRamLeak, strokes)
- if(BopProblems%MiddleRamWash%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%MiddleRamWash, ChangeMiddleRamWash, strokes)
- if(BopProblems%MiddleRamFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%MiddleRamFail, ChangeMiddleRamFail, strokes)
- if(BopProblems%MiddleRamLeak%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%MiddleRamLeak, ChangeMiddleRamLeak, strokes)
- if(BopProblems%LowerRamWash%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%LowerRamWash, ChangeLowerRamWash, strokes)
- if(BopProblems%LowerRamFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%LowerRamFail, ChangeLowerRamFail, strokes)
- if(BopProblems%LowerRamLeak%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%LowerRamLeak, ChangeLowerRamLeak, strokes)
- if(BopProblems%AccumulatorPumpFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%AccumulatorPumpFail, ChangeAccumulatorPumpFail, strokes)
- if(BopProblems%AccumulatorPumpLeak%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%AccumulatorPumpLeak, ChangeAccumulatorPumpLeak, strokes)
- if(BopProblems%AccumulatorSystemFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%AccumulatorSystemFail, ChangeAccumulatorSystemFail, strokes)
- if(BopProblems%AccumulatorSystemLeak%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BopProblems%AccumulatorSystemLeak, ChangeAccumulatorSystemLeak, strokes)
- end subroutine
-
- subroutine ProcessBopProblemsDueVolumePumped(volume)
- implicit none
- real(8) :: volume
- if(BopProblems%AnnularWash%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%AnnularWash, ChangeAnnularWash, volume)
- if(BopProblems%AnnularFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%AnnularFail, ChangeAnnularFail, volume)
- if(BopProblems%AnnularLeak%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%AnnularLeak, ChangeAnnularLeak, volume)
- if(BopProblems%UpperRamWash%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%UpperRamWash, ChangeUpperRamWash, volume)
- if(BopProblems%UpperRamFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%UpperRamFail, ChangeUpperRamFail, volume)
- if(BopProblems%UpperRamLeak%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%UpperRamLeak, ChangeUpperRamLeak, volume)
- if(BopProblems%MiddleRamWash%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%MiddleRamWash, ChangeMiddleRamWash, volume)
- if(BopProblems%MiddleRamFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%MiddleRamFail, ChangeMiddleRamFail, volume)
- if(BopProblems%MiddleRamLeak%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%MiddleRamLeak, ChangeMiddleRamLeak, volume)
- if(BopProblems%LowerRamWash%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%LowerRamWash, ChangeLowerRamWash, volume)
- if(BopProblems%LowerRamFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%LowerRamFail, ChangeLowerRamFail, volume)
- if(BopProblems%LowerRamLeak%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%LowerRamLeak, ChangeLowerRamLeak, volume)
- if(BopProblems%AccumulatorPumpFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%AccumulatorPumpFail, ChangeAccumulatorPumpFail, volume)
- if(BopProblems%AccumulatorPumpLeak%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%AccumulatorPumpLeak, ChangeAccumulatorPumpLeak, volume)
- if(BopProblems%AccumulatorSystemFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%AccumulatorSystemFail, ChangeAccumulatorSystemFail,volume)
- if(BopProblems%AccumulatorSystemLeak%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BopProblems%AccumulatorSystemLeak, ChangeAccumulatorSystemLeak, volume)
- end subroutine
-
- subroutine ProcessBopProblemsDueDistanceDrilled(distance)
- implicit none
- real(8) :: distance
- if(BopProblems%AnnularWash%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%AnnularWash, ChangeAnnularWash, distance)
- if(BopProblems%AnnularFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%AnnularFail, ChangeAnnularFail, distance)
- if(BopProblems%AnnularLeak%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%AnnularLeak, ChangeAnnularLeak, distance)
- if(BopProblems%UpperRamWash%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%UpperRamWash, ChangeUpperRamWash, distance)
- if(BopProblems%UpperRamFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%UpperRamFail, ChangeUpperRamFail, distance)
- if(BopProblems%UpperRamLeak%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%UpperRamLeak, ChangeUpperRamLeak, distance)
- if(BopProblems%MiddleRamWash%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%MiddleRamWash, ChangeMiddleRamWash, distance)
- if(BopProblems%MiddleRamFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%MiddleRamFail, ChangeMiddleRamFail, distance)
- if(BopProblems%MiddleRamLeak%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%MiddleRamLeak, ChangeMiddleRamLeak, distance)
- if(BopProblems%LowerRamWash%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%LowerRamWash, ChangeLowerRamWash, distance)
- if(BopProblems%LowerRamFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%LowerRamFail, ChangeLowerRamFail, distance)
- if(BopProblems%LowerRamLeak%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%LowerRamLeak, ChangeLowerRamLeak, distance)
- if(BopProblems%AccumulatorPumpFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%AccumulatorPumpFail, ChangeAccumulatorPumpFail, distance)
- if(BopProblems%AccumulatorPumpLeak%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%AccumulatorPumpLeak, ChangeAccumulatorPumpLeak, distance)
- if(BopProblems%AccumulatorSystemFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%AccumulatorSystemFail, ChangeAccumulatorSystemFail, distance)
- if(BopProblems%AccumulatorSystemLeak%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BopProblems%AccumulatorSystemLeak, ChangeAccumulatorSystemLeak, distance)
- end subroutine
-
-
- subroutine ChangeAnnularWash(status)
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(AnnularWashPtr)) call AnnularWashPtr(status)
- !if(status == Clear_StatusType) print*,'On_AnnularWash_Clear'
- !if(status == Executed_StatusType) print*,'On_AnnularWash_Execute'
- endsubroutine
-
- subroutine ChangeAnnularFail(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(AnnularFailPtr)) call AnnularFailPtr(status)
- if(status == Clear_StatusType) Annular%AnnularFailureMalf = 0
- if(status == Executed_StatusType) Annular%AnnularFailureMalf = 1
- endsubroutine
-
- subroutine ChangeAnnularLeak(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(AnnularLeakPtr)) call AnnularLeakPtr(status)
- if(status == Clear_StatusType) Annular%AnnularLeakMalf = 0
- if(status == Executed_StatusType) Annular%AnnularLeakMalf = 1
- endsubroutine
-
-
-
- subroutine ChangeUpperRamWash(status)
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(UpperRamWashPtr)) call UpperRamWashPtr(status)
- !if(status == Clear_StatusType) print*,'On_UpperRamWash_Clear'
- !if(status == Executed_StatusType) print*,'On_UpperRamWash_Execute'
- endsubroutine
-
- subroutine ChangeUpperRamFail(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(UpperRamFailPtr)) call UpperRamFailPtr(status)
- if(status == Clear_StatusType) PipeRam1%UpperRamsFailureMalf = 0
- if(status == Executed_StatusType) PipeRam1%UpperRamsFailureMalf = 1
- endsubroutine
-
- subroutine ChangeUpperRamLeak(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(UpperRamLeakPtr)) call UpperRamLeakPtr(status)
- if(status == Clear_StatusType) PipeRam1%UpperRamsLeakMalf = 0
- if(status == Executed_StatusType) PipeRam1%UpperRamsLeakMalf = 1
- endsubroutine
-
-
- subroutine ChangeMiddleRamWash(status)
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(MiddleRamWashPtr)) call MiddleRamWashPtr(status)
- !if(status == Clear_StatusType) print*,'On_MiddleRamWash_Clear'
- !if(status == Executed_StatusType) print*,'On_MiddleRamWash_Execute'
- endsubroutine
-
- subroutine ChangeMiddleRamFail(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! if(associated(MiddleRamFailPtr)) call MiddleRamFailPtr(status)
- if(status == Clear_StatusType) ShearRam%MiddleRamsFailureMalf = 0
- if(status == Executed_StatusType) ShearRam%MiddleRamsFailureMalf = 1
- endsubroutine
-
- subroutine ChangeMiddleRamLeak(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(MiddleRamLeakPtr)) call MiddleRamLeakPtr(status)
- if(status == Clear_StatusType) ShearRam%MiddleRamsLeakMalf = 0
- if(status == Executed_StatusType) ShearRam%MiddleRamsLeakMalf = 1
- endsubroutine
-
-
-
- subroutine ChangeLowerRamWash(status)
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(LowerRamWashPtr)) call LowerRamWashPtr(status)
- !if(status == Clear_StatusType) print*,'On_LowerRamWash_Clear'
- !if(status == Executed_StatusType) print*,'On_LowerRamWash_Execute'
- endsubroutine
-
- subroutine ChangeLowerRamFail(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! ! if(associated(LowerRamFailPtr)) call LowerRamFailPtr(status)
- if(status == Clear_StatusType) PipeRam2%LowerRamsFailureMalf = 0
- if(status == Executed_StatusType) PipeRam2%LowerRamsFailureMalf = 1
- endsubroutine
-
- subroutine ChangeLowerRamLeak(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! if(associated(LowerRamLeakPtr)) call LowerRamLeakPtr(status)
- if(status == Clear_StatusType) PipeRam2%LowerRamsLeakMalf = 0
- if(status == Executed_StatusType) PipeRam2%LowerRamsLeakMalf = 1
- endsubroutine
-
- subroutine ChangeAccumulatorPumpFail(status)
- USE VARIABLES
- implicit none
- integer, intent (in) :: status
- ! if(associated(AccumulatorPumpFailPtr)) call AccumulatorPumpFailPtr(status)
- if(status == Clear_StatusType) BopStackAcc%AccPupmsFailMalf = 0
- if(status == Executed_StatusType) BopStackAcc%AccPupmsFailMalf = 1
- endsubroutine
-
- subroutine ChangeAccumulatorPumpLeak(status)
- implicit none
- integer, intent (in) :: status
- ! if(associated(AccumulatorPumpLeakPtr)) call AccumulatorPumpLeakPtr(status)
- !if(status == Clear_StatusType) print*,'On_AccumulatorPumpLeak_Clear'
- !if(status == Executed_StatusType) print*,'On_AccumulatorPumpLeak_Execute'
- endsubroutine
-
- subroutine ChangeAccumulatorSystemFail(status)
- implicit none
- integer, intent (in) :: status
- ! if(associated(AccumulatorSystemFailPtr)) call AccumulatorSystemFailPtr(status)
- !if(status == Clear_StatusType) print*,'On_AccumulatorSystemFail_Clear'
- !if(status == Executed_StatusType) print*,'On_AccumulatorSystemFail_Execute'
- endsubroutine
-
- subroutine ChangeAccumulatorSystemLeak(status)
- implicit none
- integer, intent (in) :: status
- ! if(associated(AccumulatorSystemLeakPtr)) call AccumulatorSystemLeakPtr(status)
- !if(status == Clear_StatusType) print*,'On_AccumulatorSystemLeak_Clear'
- !if(status == Executed_StatusType) print*,'On_AccumulatorSystemLeak_Execute'
- endsubroutine
-
-
-
-
-
-
-
-
-
-
-
-
- ! subroutine SubscribeAnnularWash(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAnnularWash
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeAnnularWash' :: SubscribeAnnularWash
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! AnnularWashPtr => v
- ! end subroutine
-
- ! subroutine SubscribeAnnularFail(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAnnularFail
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeAnnularFail' :: SubscribeAnnularFail
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! AnnularFailPtr => v
- ! end subroutine
-
- ! subroutine SubscribeAnnularLeak(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAnnularLeak
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeAnnularLeak' :: SubscribeAnnularLeak
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! AnnularLeakPtr => v
- ! end subroutine
-
-
- ! subroutine SubscribeUpperRamWash(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeUpperRamWash
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeUpperRamWash' :: SubscribeUpperRamWash
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! UpperRamWashPtr => v
- ! end subroutine
-
- ! subroutine SubscribeUpperRamFail(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeUpperRamFail
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeUpperRamFail' :: SubscribeUpperRamFail
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! UpperRamFailPtr => v
- ! end subroutine
-
- ! subroutine SubscribeUpperRamLeak(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeUpperRamLeak
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeUpperRamLeak' :: SubscribeUpperRamLeak
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! UpperRamLeakPtr => v
- ! end subroutine
-
-
- ! subroutine SubscribeMiddleRamWash(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMiddleRamWash
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeMiddleRamWash' :: SubscribeMiddleRamWash
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! MiddleRamWashPtr => v
- ! end subroutine
-
- ! subroutine SubscribeMiddleRamFail(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMiddleRamFail
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeMiddleRamFail' :: SubscribeMiddleRamFail
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! MiddleRamFailPtr => v
- ! end subroutine
-
- ! subroutine SubscribeMiddleRamLeak(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMiddleRamLeak
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeMiddleRamLeak' :: SubscribeMiddleRamLeak
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! MiddleRamLeakPtr => v
- ! end subroutine
-
-
- ! subroutine SubscribeLowerRamWash(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLowerRamWash
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeLowerRamWash' :: SubscribeLowerRamWash
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! LowerRamWashPtr => v
- ! end subroutine
-
- ! subroutine SubscribeLowerRamFail(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLowerRamFail
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeLowerRamFail' :: SubscribeLowerRamFail
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! LowerRamFailPtr => v
- ! end subroutine
-
- ! subroutine SubscribeLowerRamLeak(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLowerRamLeak
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeLowerRamLeak' :: SubscribeLowerRamLeak
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! LowerRamLeakPtr => v
- ! end subroutine
-
- ! subroutine SubscribeAccumulatorPumpFail(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAccumulatorPumpFail
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeAccumulatorPumpFail' :: SubscribeAccumulatorPumpFail
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! AccumulatorPumpFailPtr => v
- ! end subroutine
-
- ! subroutine SubscribeAccumulatorPumpLeak(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAccumulatorPumpLeak
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeAccumulatorPumpLeak' :: SubscribeAccumulatorPumpLeak
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! AccumulatorPumpLeakPtr => v
- ! end subroutine
-
- ! subroutine SubscribeAccumulatorSystemFail(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAccumulatorSystemFail
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeAccumulatorSystemFail' :: SubscribeAccumulatorSystemFail
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! AccumulatorSystemFailPtr => v
- ! end subroutine
-
- ! subroutine SubscribeAccumulatorSystemLeak(v)
- ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAccumulatorSystemLeak
- ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeAccumulatorSystemLeak' :: SubscribeAccumulatorSystemLeak
- ! implicit none
- ! procedure (ActionInteger) :: v
- ! AccumulatorSystemLeakPtr => v
- ! end subroutine
-
-
-
-
-
- end module CBopProblemsVariables
|