|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140 |
- module CMudPropertiesVariables
- use CIActionReference
- use CDoubleEventHandlerCollection
- implicit none
- public
-
- !pointers
- procedure (ActionDouble), pointer :: ActiveMudVolumePtr
- procedure (ActionDouble), pointer :: ActiveDensityPtr
- procedure (ActionDouble), pointer :: ReserveMudVolumePtr
- procedure (ActionDouble), pointer :: ReserveDensityPtr
-
- type(DoubleEventHandlerCollection) :: OnActiveMudVolumeChange
- type(DoubleEventHandlerCollection) :: OnActiveDensityChange
- type(DoubleEventHandlerCollection) :: OnReserveMudVolumeChange
- type(DoubleEventHandlerCollection) :: OnReserveDensityChange
-
- !constants
- integer, parameter :: WaterBase_MudType = 0
- integer, parameter :: OilBase_MudType = 1
- integer, parameter :: PowerLaw_RheologyModel = 0
- integer, parameter :: Bingham_RheologyModel = 1
- integer, parameter :: Newtonian_RheologyModel = 2
- INTEGER, PARAMETER :: Herschel_Bulkley_RheologyModel = 3
-
- ! variables
- integer :: ActiveMudType
- integer :: ActiveRheologyModel
- real(8) :: ActiveMudVolume
- real(8) :: ActiveMudVolumeGal
- real(8) :: ActiveDensity
- real(8) :: ActivePlasticViscosity
- real(8) :: ActiveYieldPoint
- real(8) :: ActiveThetaThreeHundred
- real(8) :: ActiveThetaSixHundred
-
- integer :: ReserveMudType
- real(8) :: ReserveMudVolume
- real(8) :: ReserveMudVolumeGal
- real(8) :: ReserveDensity
- real(8) :: ReservePlasticViscosity
- real(8) :: ReserveYieldPoint
- real(8) :: ReserveThetaThreeHundred
- real(8) :: ReserveThetaSixHundred
-
- real(8) :: ActiveTotalTankCapacity
- real(8) :: ActiveTotalTankCapacityGal
- real(8) :: ActiveSettledContents
- real(8) :: ActiveSettledContentsGal
- real(8) :: ActiveTotalContents
- real(8) :: ActiveTotalContentsGal
- logical :: ActiveAutoDensity
- !real(8) :: ReserveTotalTankCapacity
- !real(8) :: ReserveTotalTankCapacityGal
- !real(8) :: ReserveSettledContents
- !real(8) :: ReserveSettledContentsGal
- !real(8) :: ReserveTotalContents
- !real(8) :: ReserveTotalContentsGal
- real(8) :: InitialTripTankMudVolume
- real(8) :: InitialTripTankMudVolumeGal
- real(8) :: PedalFlowMeter
-
- contains
-
-
- subroutine Set_ActiveMudVolume_StudentStation(v)
- implicit none
- real*8, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(ActiveMudVolume == v) return
- #endif
- ActiveMudVolume = v
- if(associated(ActiveMudVolumePtr)) call ActiveMudVolumePtr(ActiveMudVolume)
- end subroutine
-
- subroutine Set_ActiveDensity_StudentStation(v)
- implicit none
- real*8, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(ActiveDensity == v) return
- #endif
- ActiveDensity = v
- if(associated(ActiveDensityPtr)) call ActiveDensityPtr(ActiveDensity)
- end subroutine
-
- subroutine Set_ReserveMudVolume_StudentStation(v)
- implicit none
- real*8, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(ReserveMudVolume == v) return
- #endif
- ReserveMudVolume = v
- if(associated(ReserveMudVolumePtr)) call ReserveMudVolumePtr(ReserveMudVolume)
- end subroutine
-
- subroutine Set_ReserveDensity_StudentStation(v)
- implicit none
- real*8, intent(in) :: v
- #ifdef ExcludeExtraChanges
- if(ReserveDensity == v) return
- #endif
- ReserveDensity = v
- if(associated(ReserveDensityPtr)) call ReserveDensityPtr(ReserveDensity)
- end subroutine
-
-
-
- subroutine SubscribeActiveMudVolume(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeActiveMudVolume
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeActiveMudVolume' :: SubscribeActiveMudVolume
- implicit none
- procedure (ActionDouble) :: a
- ActiveMudVolumePtr => a
- end subroutine
-
- subroutine SubscribeActiveDensity(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeActiveDensity
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeActiveDensity' :: SubscribeActiveDensity
- implicit none
- procedure (ActionDouble) :: a
- ActiveDensityPtr => a
- end subroutine
-
- subroutine SubscribeReserveMudVolume(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeReserveMudVolume
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeReserveMudVolume' :: SubscribeReserveMudVolume
- implicit none
- procedure (ActionDouble) :: a
- ReserveMudVolumePtr => a
- end subroutine
-
- subroutine SubscribeReserveDensity(a)
- !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeReserveDensity
- !DEC$ ATTRIBUTES ALIAS: 'SubscribeReserveDensity' :: SubscribeReserveDensity
- implicit none
- procedure (ActionDouble) :: a
- ReserveDensityPtr => a
- end subroutine
-
- end module CMudPropertiesVariables
|