@@ -0,0 +1,62 @@ | |||||
module CStringConfiguration | |||||
use CStringConfigurationVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
integer function SetStringConfigurations(count, array, bit) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::SetStringConfigurations | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStringConfigurations' :: SetStringConfigurations | |||||
use CManifolds | |||||
implicit none | |||||
integer, intent(in) :: count | |||||
integer :: i, j | |||||
type(CStringItem), intent(inout), target :: array(count) | |||||
type(CBitInfo), intent(inout) :: bit | |||||
type(CStringItem), pointer :: item | |||||
BitDefinition%BitType = bit%BitType | |||||
BitDefinition%BitSize = bit%BitSize | |||||
BitDefinition%BitCodeHundreds = bit%BitCodeHundreds | |||||
BitDefinition%BitCodeTens = bit%BitCodeTens | |||||
BitDefinition%BitCodeOnes = bit%BitCodeOnes | |||||
BitDefinition%BitNozzleSize = bit%BitNozzleSize | |||||
BitDefinition%BitLength = bit%BitLength | |||||
BitDefinition%BitWeightPerLength = bit%BitWeightPerLength | |||||
BitDefinition%BitNozzleNo = bit%BitNozzleNo | |||||
BitDefinition%FloatValve = bit%FloatValve | |||||
StringConfigurationCount = count | |||||
if(BitDefinition%FloatValve) then | |||||
call InstallFloatValve() | |||||
else | |||||
call RemoveFloatValve() | |||||
endif | |||||
if(size(StringConfigurations) > 0) then | |||||
deallocate(StringConfigurations) | |||||
end if | |||||
if(count > 0) then | |||||
allocate(StringConfigurations(count)) | |||||
!j = count | |||||
do i = 1, count | |||||
item => array(i) | |||||
StringConfigurations(i)%ComponentType = item%ComponentType | |||||
StringConfigurations(i)%NumberOfJoint = item%NumberOfJoint | |||||
StringConfigurations(i)%LengthPerJoint = item%LengthPerJoint | |||||
StringConfigurations(i)%NominalOd = item%NominalOd | |||||
StringConfigurations(i)%NominalId = item%NominalId | |||||
StringConfigurations(i)%WeightPerLength = item%WeightPerLength | |||||
StringConfigurations(i)%ComponentLength = item%ComponentLength | |||||
StringConfigurations(i)%NominalToolJointOd = item%NominalToolJointOd | |||||
StringConfigurations(i)%Grade = item%Grade | |||||
!print*, 'type=', StringConfigurations(i)%ComponentType | |||||
!print*, 'NumberOfJoint=', StringConfigurations(i)%NumberOfJoint | |||||
!print*, '-----------------------------------------------------------' | |||||
!j = j - 1 | |||||
end do | |||||
end if | |||||
SetStringConfigurations = 0 | |||||
end function SetStringConfigurations | |||||
end module CStringConfiguration |
@@ -0,0 +1,54 @@ | |||||
module CStringConfigurationVariables | |||||
implicit none | |||||
public | |||||
!constants | |||||
integer :: Bit_ComponentType = 0 | |||||
integer :: Stabilizer_ComponentType = 1 | |||||
integer :: Collar_ComponentType = 2 | |||||
integer :: DrillPipe_ComponentType = 3 | |||||
integer :: Heavyweight_ComponentType = 4 | |||||
integer :: Cone_BitType = 0 | |||||
integer :: PDC_BitType = 1 | |||||
integer :: Rock_BitType = 2 | |||||
! types | |||||
! Pipe Items in String Array | |||||
type, bind(c), public :: CStringItem | |||||
integer :: ComponentType | |||||
real(8) :: NumberOfJoint | |||||
real(8) :: LengthPerJoint | |||||
real(8) :: NominalOd | |||||
real(8) :: NominalId | |||||
real(8) :: WeightPerLength | |||||
real(8) :: ComponentLength | |||||
real(8) :: NominalToolJointOd | |||||
character(1) :: Grade | |||||
end type CStringItem | |||||
! types | |||||
! Pipe Items in String Array | |||||
type, bind(c), public :: CBitInfo | |||||
integer :: BitType | |||||
real(8) :: BitSize | |||||
integer :: BitCodeHundreds | |||||
integer :: BitCodeTens | |||||
integer :: BitCodeOnes | |||||
real(8) :: BitNozzleSize | |||||
real(8) :: BitLength | |||||
real(8) :: BitWeightPerLength | |||||
integer :: BitNozzleNo | |||||
logical :: FloatValve | |||||
end type CBitInfo | |||||
integer :: StringConfigurationCount = 0 | |||||
type(CStringItem), allocatable :: StringConfigurations(:) | |||||
type(CBitInfo) :: BitDefinition | |||||
contains | |||||
end module CStringConfigurationVariables |
@@ -0,0 +1,237 @@ | |||||
module CMudProperties | |||||
use CMudPropertiesVariables | |||||
use CLog4 | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetActiveMudType(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveMudType | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveMudType' :: SetActiveMudType | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
ActiveMudType = v | |||||
end subroutine | |||||
subroutine SetActiveRheologyModel(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveRheologyModel | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveRheologyModel' :: SetActiveRheologyModel | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
ActiveRheologyModel = v | |||||
#ifdef deb | |||||
call Log_4( '=====ActiveRheologyModel=', ActiveRheologyModel) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveMudVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveMudVolume' :: SetActiveMudVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActiveMudVolume = v | |||||
!call Log_5('ActiveDensity=', ActiveDensity) | |||||
#ifdef deb | |||||
print*, 'ActiveMudVolume=', ActiveMudVolume | |||||
#endif | |||||
ActiveMudVolumeGal = v * 42.0 | |||||
call OnActiveMudVolumeChange%RunAll(v * 42.0d0) | |||||
end subroutine | |||||
subroutine SetActiveDensity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveDensity' :: SetActiveDensity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActiveDensity = v | |||||
!call Log_5('ActiveDensity=', ActiveDensity) | |||||
#ifdef deb | |||||
print*, 'ActiveDensity=', ActiveDensity | |||||
#endif | |||||
call OnActiveDensityChange%RunAll(v) | |||||
end subroutine | |||||
subroutine SetActiveThetaThreeHundred(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveThetaThreeHundred | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveThetaThreeHundred' :: SetActiveThetaThreeHundred | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActiveThetaThreeHundred = v | |||||
end subroutine | |||||
subroutine SetActiveThetaSixHundred(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveThetaSixHundred | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveThetaSixHundred' :: SetActiveThetaSixHundred | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActiveThetaSixHundred = v | |||||
end subroutine | |||||
subroutine SetReserveMudType(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveMudType | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveMudType' :: SetReserveMudType | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
ReserveMudType = v | |||||
end subroutine | |||||
subroutine SetReserveMudVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveMudVolume' :: SetReserveMudVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ReserveMudVolume = v | |||||
!call Log_5('ReserveMudVolume=', ReserveMudVolume) | |||||
#ifdef deb | |||||
print*, 'ReserveMudVolume=', ReserveMudVolume | |||||
#endif | |||||
ReserveMudVolumeGal = v * 42.0 | |||||
call OnReserveMudVolumeChange%RunAll(v * 42.0d0) | |||||
end subroutine | |||||
subroutine SetReserveDensity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveDensity' :: SetReserveDensity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ReserveDensity = v | |||||
!call Log_5('ReserveDensity=', ReserveDensity) | |||||
#ifdef deb | |||||
print*, 'ReserveDensity=', ReserveDensity | |||||
#endif | |||||
call OnReserveDensityChange%RunAll(v) | |||||
end subroutine | |||||
subroutine SetReserveThetaThreeHundred(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveThetaThreeHundred | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveThetaThreeHundred' :: SetReserveThetaThreeHundred | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ReserveThetaThreeHundred = v | |||||
end subroutine | |||||
subroutine SetReserveThetaSixHundred(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveThetaSixHundred | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveThetaSixHundred' :: SetReserveThetaSixHundred | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ReserveThetaSixHundred = v | |||||
end subroutine | |||||
subroutine SetActiveTotalTankCapacity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveTotalTankCapacity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveTotalTankCapacity' :: SetActiveTotalTankCapacity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActiveTotalTankCapacity = v | |||||
ActiveTotalTankCapacityGal = v * 42.0 | |||||
#ifdef deb | |||||
print*, 'ActiveTotalTankCapacity=', ActiveTotalTankCapacity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveSettledContents(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveSettledContents | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveSettledContents' :: SetActiveSettledContents | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActiveSettledContents = v | |||||
ActiveSettledContentsGal = v * 42.0 | |||||
#ifdef deb | |||||
print*, 'ActiveSettledContents=', ActiveSettledContents | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveTotalContents(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveTotalContents | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveTotalContents' :: SetActiveTotalContents | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActiveTotalContents = v | |||||
ActiveTotalContentsGal = v * 42.0 | |||||
#ifdef deb | |||||
print*, 'ActiveTotalContents=', ActiveTotalContents | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActivePlasticViscosity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActivePlasticViscosity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActivePlasticViscosity' :: SetActivePlasticViscosity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActivePlasticViscosity = v | |||||
#ifdef deb | |||||
print*, 'ActivePlasticViscosity=', ActivePlasticViscosity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveYieldPoint(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveYieldPoint | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveYieldPoint' :: SetActiveYieldPoint | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ActiveYieldPoint = v | |||||
#ifdef deb | |||||
print*, 'ActiveYieldPoint=', ActiveYieldPoint | |||||
#endif | |||||
end subroutine | |||||
subroutine SetActiveAutoDensity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetActiveAutoDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetActiveAutoDensity' :: SetActiveAutoDensity | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ActiveAutoDensity = v | |||||
#ifdef deb | |||||
print*, 'ActiveAutoDensity=', ActiveAutoDensity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetReservePlasticViscosity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReservePlasticViscosity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReservePlasticViscosity' :: SetReservePlasticViscosity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ReservePlasticViscosity = v | |||||
#ifdef deb | |||||
print*, 'ReservePlasticViscosity=', ReservePlasticViscosity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetReserveYieldPoint(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReserveYieldPoint | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReserveYieldPoint' :: SetReserveYieldPoint | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ReserveYieldPoint = v | |||||
#ifdef deb | |||||
print*, 'ReserveYieldPoint=', ReserveYieldPoint | |||||
#endif | |||||
end subroutine | |||||
subroutine SetInitialTripTankMudVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetInitialTripTankMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetInitialTripTankMudVolume' :: SetInitialTripTankMudVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
InitialTripTankMudVolume = v | |||||
InitialTripTankMudVolumeGal = v * 42.0 | |||||
#ifdef deb | |||||
print*, 'InitialTripTankMudVolume=', InitialTripTankMudVolume | |||||
#endif | |||||
end subroutine | |||||
subroutine SetPedalFlowMeter(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetPedalFlowMeter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetPedalFlowMeter' :: SetPedalFlowMeter | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
PedalFlowMeter = v | |||||
#ifdef deb | |||||
print*, 'PedalFlowMeter=', PedalFlowMeter | |||||
#endif | |||||
end subroutine | |||||
end module CMudProperties |
@@ -0,0 +1,140 @@ | |||||
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 |
@@ -0,0 +1,37 @@ | |||||
module CFormation | |||||
use CFormationVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
integer function SetFormations(count, array) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::SetFormations | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetFormations' :: SetFormations | |||||
implicit none | |||||
integer, intent(in) :: count | |||||
integer :: i | |||||
type(CFormationItem), intent(inout), target :: array(count) | |||||
type(CFormationItem), pointer :: item | |||||
FormationCount = count | |||||
if(size(Formations) > 0) then | |||||
deallocate(Formations) | |||||
end if | |||||
if(count > 0) then | |||||
allocate(Formations(count)) | |||||
do i = 1, count | |||||
item => array(i) | |||||
Formations(i)%Top = item%Top | |||||
Formations(i)%Thickness = item%Thickness | |||||
Formations(i)%Drillablity = item%Drillablity | |||||
Formations(i)%Abrasiveness = item%Abrasiveness | |||||
Formations(i)%ThresholdWeight = item%ThresholdWeight | |||||
Formations(i)%PorePressureGradient = item%PorePressureGradient | |||||
!print*, "===========================" | |||||
!print*, "Formations(", i, ")%Top=", Formations(i)%Top | |||||
!print*, "Formations(",i,")%Thickness", Formations(i)%Thickness | |||||
!print*, "Formations(",i,")%Drillablity", Formations(i)%Drillablity | |||||
end do | |||||
end if | |||||
SetFormations = 0 | |||||
end function SetFormations | |||||
end module CFormation |
@@ -0,0 +1,20 @@ | |||||
module CFormationVariables | |||||
implicit none | |||||
public | |||||
! types | |||||
! Pipe Items in String Array | |||||
type, bind(c), public :: CFormationItem | |||||
real(8) :: Top | |||||
real(8) :: Thickness | |||||
real(8) :: Drillablity | |||||
real(8) :: Abrasiveness | |||||
real(8) :: ThresholdWeight | |||||
real(8) :: PorePressureGradient | |||||
end type CFormationItem | |||||
integer :: FormationCount = 0 | |||||
type(CFormationItem), allocatable :: Formations(:) | |||||
contains | |||||
end module CFormationVariables |
@@ -0,0 +1,114 @@ | |||||
module CReservoir | |||||
use CReservoirVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetReservoirFormationNo(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetReservoirFormationNo | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetReservoirFormationNo' :: SetReservoirFormationNo | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
FormationNo = v | |||||
end subroutine | |||||
subroutine SetFormationTop(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetFormationTop | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetFormationTop' :: SetFormationTop | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
FormationTop = v | |||||
end subroutine | |||||
subroutine SetPressureGradient(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetPressureGradient | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetPressureGradient' :: SetPressureGradient | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
PressureGradient = v | |||||
end subroutine | |||||
subroutine SetFormationPermeability(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetFormationPermeability | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetFormationPermeability' :: SetFormationPermeability | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
FormationPermeability = v | |||||
end subroutine | |||||
subroutine SetGeothermalGradient(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetGeothermalGradient | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetGeothermalGradient' :: SetGeothermalGradient | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
GeothermalGradient = v | |||||
end subroutine | |||||
subroutine SetFluidType(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetFluidType | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetFluidType' :: SetFluidType | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
FluidType = v | |||||
end subroutine | |||||
subroutine SetFluidGradient(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetFluidGradient | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetFluidGradient' :: SetFluidGradient | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
FluidGradient = v | |||||
end subroutine | |||||
subroutine SetFluidViscosity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetFluidViscosity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetFluidViscosity' :: SetFluidViscosity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
FluidViscosity = v | |||||
end subroutine | |||||
subroutine SetInactiveInflux(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetInactiveInflux | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetInactiveInflux' :: SetInactiveInflux | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
InactiveInflux = v | |||||
end subroutine | |||||
subroutine SetMakeKickSinglePacket(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMakeKickSinglePacket | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMakeKickSinglePacket' :: SetMakeKickSinglePacket | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MakeKickSinglePacket = v | |||||
#ifdef deb | |||||
print*, 'MakeKickSinglePacket=', MakeKickSinglePacket | |||||
#endif | |||||
end subroutine | |||||
subroutine SetIsAutoMigrationRateSelected(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetIsAutoMigrationRateSelected | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetIsAutoMigrationRateSelected' :: SetIsAutoMigrationRateSelected | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
IsAutoMigrationRateSelected = v | |||||
#ifdef deb | |||||
print*, 'IsAutoMigrationRateSelected=', IsAutoMigrationRateSelected | |||||
#endif | |||||
end subroutine | |||||
subroutine SetAutoMigrationRate(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAutoMigrationRate | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAutoMigrationRate' :: SetAutoMigrationRate | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AutoMigrationRate = v | |||||
#ifdef deb | |||||
print*, 'AutoMigrationRate=', AutoMigrationRate | |||||
#endif | |||||
end subroutine | |||||
end module CReservoir |
@@ -0,0 +1,25 @@ | |||||
module CReservoirVariables | |||||
implicit none | |||||
public | |||||
!constants | |||||
integer :: Gas_FluidType = 0 | |||||
integer :: Oil_FluidType = 1 | |||||
integer :: Water_FluidType = 2 | |||||
! variables | |||||
integer :: FormationNo | |||||
real(8) :: FormationTop | |||||
real(8) :: PressureGradient | |||||
real(8) :: FormationPermeability | |||||
real(8) :: GeothermalGradient | |||||
integer :: FluidType | |||||
real(8) :: FluidGradient | |||||
real(8) :: FluidViscosity | |||||
logical :: InactiveInflux | |||||
logical :: IsAutoMigrationRateSelected | |||||
real(8) :: AutoMigrationRate | |||||
logical :: MakeKickSinglePacket | |||||
contains | |||||
end module CReservoirVariables |
@@ -0,0 +1,55 @@ | |||||
module CShoe | |||||
use CShoeVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetShoeFormationNo(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetShoeFormationNo | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetShoeFormationNo' :: SetShoeFormationNo | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
FormationNo = v | |||||
end subroutine | |||||
subroutine SetShoeDepth(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetShoeDepth | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetShoeDepth' :: SetShoeDepth | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ShoeDepth = v | |||||
end subroutine | |||||
subroutine SetLeakOff(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLeakOff | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLeakOff' :: SetLeakOff | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LeakOff = v | |||||
end subroutine | |||||
subroutine SetBreakdown(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetBreakdown | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetBreakdown' :: SetBreakdown | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
Breakdown = v | |||||
end subroutine | |||||
subroutine SetFracturePropagation(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetFracturePropagation | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetFracturePropagation' :: SetFracturePropagation | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
FracturePropagation = v | |||||
end subroutine | |||||
subroutine SetInactiveFracture(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetInactiveFracture | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetInactiveFracture' :: SetInactiveFracture | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
InactiveFracture = v | |||||
end subroutine | |||||
end module CShoe |
@@ -0,0 +1,12 @@ | |||||
module CShoeVariables | |||||
implicit none | |||||
public | |||||
! variables | |||||
integer :: FormationNo | |||||
real(8) :: ShoeDepth | |||||
real(8) :: LeakOff | |||||
real(8) :: Breakdown | |||||
real(8) :: FracturePropagation | |||||
logical :: InactiveFracture | |||||
contains | |||||
end module CShoeVariables |
@@ -0,0 +1,95 @@ | |||||
module CAccumulator | |||||
use CAccumulatorVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetNumberOfBottels(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetNumberOfBottels | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetNumberOfBottels' :: SetNumberOfBottels | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
NumberOfBottels = v | |||||
end subroutine | |||||
subroutine SetAccumulatorSystemSize(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAccumulatorSystemSize | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAccumulatorSystemSize' :: SetAccumulatorSystemSize | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AccumulatorSystemSize = v | |||||
end subroutine | |||||
subroutine SetOilTankVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetOilTankVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetOilTankVolume' :: SetOilTankVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
OilTankVolume = v | |||||
end subroutine | |||||
subroutine SetPrechargePressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetPrechargePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetPrechargePressure' :: SetPrechargePressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
PrechargePressure = v | |||||
end subroutine | |||||
subroutine SetAccumulatorMinimumOperatingPressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAccumulatorMinimumOperatingPressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAccumulatorMinimumOperatingPressure' :: SetAccumulatorMinimumOperatingPressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AccumulatorMinimumOperatingPressure = v | |||||
end subroutine | |||||
subroutine SetElectricPumpOutput(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetElectricPumpOutput | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetElectricPumpOutput' :: SetElectricPumpOutput | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ElectricPumpOutput = v | |||||
end subroutine | |||||
subroutine SetStartPressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStartPressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStartPressure' :: SetStartPressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
StartPressure = v | |||||
end subroutine | |||||
subroutine SetStopPressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStopPressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStopPressure' :: SetStopPressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
StopPressure = v | |||||
end subroutine | |||||
subroutine SetAirPlungerPumpOutput(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAirPlungerPumpOutput | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAirPlungerPumpOutput' :: SetAirPlungerPumpOutput | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AirPlungerPumpOutput = v | |||||
end subroutine | |||||
subroutine SetStartPressure2(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStartPressure2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStartPressure2' :: SetStartPressure2 | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
StartPressure2 = v | |||||
end subroutine | |||||
subroutine SetStopPressure2(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStopPressure2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStopPressure2' :: SetStopPressure2 | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
StopPressure2 = v | |||||
end subroutine | |||||
end module CAccumulator |
@@ -0,0 +1,18 @@ | |||||
module CAccumulatorVariables | |||||
implicit none | |||||
public | |||||
integer :: NumberOfBottels | |||||
real(8) :: AccumulatorSystemSize | |||||
real(8) :: OilTankVolume | |||||
real(8) :: PrechargePressure | |||||
real(8) :: AccumulatorMinimumOperatingPressure | |||||
real(8) :: ElectricPumpOutput | |||||
real(8) :: StartPressure | |||||
real(8) :: StopPressure | |||||
real(8) :: AirPlungerPumpOutput | |||||
real(8) :: StartPressure2 | |||||
real(8) :: StopPressure2 | |||||
contains | |||||
end module CAccumulatorVariables |
@@ -0,0 +1,201 @@ | |||||
module CBopStack | |||||
use CBopStackVariables | |||||
use CLog4 | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetAboveAnnularHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAboveAnnularHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAboveAnnularHeight' :: SetAboveAnnularHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!AboveAnnularHeight = v | |||||
!call Log_4('AboveAnnularHeight=', AboveAnnularHeight) | |||||
end subroutine | |||||
subroutine SetAnnularPreventerHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAnnularPreventerHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAnnularPreventerHeight' :: SetAnnularPreventerHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!AnnularPreventerHeight = v | |||||
!call Log_4('AnnularPreventerHeight=', AnnularPreventerHeight) | |||||
end subroutine | |||||
subroutine SetUpperRamHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetUpperRamHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetUpperRamHeight' :: SetUpperRamHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!UpperRamHeight = v | |||||
!call Log_4('UpperRamHeight=', UpperRamHeight) | |||||
end subroutine | |||||
subroutine SetLowerRamHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLowerRamHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLowerRamHeight' :: SetLowerRamHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!LowerRamHeight = v | |||||
!call Log_4('LowerRamHeight=', LowerRamHeight) | |||||
end subroutine | |||||
subroutine SetBlindRamHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetBlindRamHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetBlindRamHeight' :: SetBlindRamHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!BlindRamHeight = v | |||||
!call Log_4('BlindRamHeight=', BlindRamHeight) | |||||
end subroutine | |||||
subroutine SetKillHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetKillHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetKillHeight' :: SetKillHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!KillHeight = v | |||||
!call Log_4('KillHeight=', KillHeight) | |||||
end subroutine | |||||
subroutine SetKillOpen(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetKillOpen | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetKillOpen' :: SetKillOpen | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!KillOpen = v | |||||
!call Log_4('KillOpen=', KillOpen) | |||||
end subroutine | |||||
subroutine SetKillClose(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetKillClose | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetKillClose' :: SetKillClose | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!KillClose = v | |||||
!call Log_4('KillClose=', KillClose) | |||||
end subroutine | |||||
subroutine SetGroundLevel(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetGroundLevel | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetGroundLevel' :: SetGroundLevel | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!GroundLevel = v | |||||
!call Log_4('GroundLevel=', GroundLevel) | |||||
end subroutine | |||||
subroutine SetLowerRamOpen(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLowerRamOpen | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLowerRamOpen' :: SetLowerRamOpen | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LowerRamOpen = v | |||||
end subroutine | |||||
subroutine SetLowerRamClose(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLowerRamClose | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLowerRamClose' :: SetLowerRamClose | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LowerRamClose = v | |||||
end subroutine | |||||
subroutine SetChokeOpen(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeOpen | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeOpen' :: SetChokeOpen | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ChokeOpen = v | |||||
end subroutine | |||||
subroutine SetChokeClose(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeClose | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeClose' :: SetChokeClose | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ChokeClose = v | |||||
end subroutine | |||||
subroutine SetBlindRamOpen(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetBlindRamOpen | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetBlindRamOpen' :: SetBlindRamOpen | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
BlindRamOpen = v | |||||
end subroutine | |||||
subroutine SetBlindRamClose(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetBlindRamClose | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetBlindRamClose' :: SetBlindRamClose | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
BlindRamClose = v | |||||
end subroutine | |||||
subroutine SetUpperRamOpen(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetUpperRamOpen | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetUpperRamOpen' :: SetUpperRamOpen | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
UpperRamOpen = v | |||||
end subroutine | |||||
subroutine SetUpperRamClose(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetUpperRamClose | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetUpperRamClose' :: SetUpperRamClose | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
UpperRamClose = v | |||||
end subroutine | |||||
subroutine SetAnnularPreventerOpen(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAnnularPreventerOpen | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAnnularPreventerOpen' :: SetAnnularPreventerOpen | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AnnularPreventerOpen = v | |||||
end subroutine | |||||
subroutine SetAnnularPreventerClose(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAnnularPreventerClose | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAnnularPreventerClose' :: SetAnnularPreventerClose | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AnnularPreventerClose = v | |||||
end subroutine | |||||
subroutine SetRamStringDrag(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRamStringDrag | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRamStringDrag' :: SetRamStringDrag | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
RamStringDrag = v | |||||
end subroutine | |||||
subroutine SetAnnularStringDrag(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAnnularStringDrag | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAnnularStringDrag' :: SetAnnularStringDrag | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AnnularStringDrag = v | |||||
end subroutine | |||||
subroutine SetChokeLineLength(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeLineLength | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeLineLength' :: SetChokeLineLength | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ChokeLineLength = v | |||||
end subroutine | |||||
subroutine SetChokeLineId(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeLineId | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeLineId' :: SetChokeLineId | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ChokeLineId = v | |||||
end subroutine | |||||
end module CBopStack |
@@ -0,0 +1,31 @@ | |||||
module CBopStackVariables | |||||
implicit none | |||||
public | |||||
real(8) :: AboveAnnularHeight = 10.0d0 | |||||
real(8) :: AnnularPreventerHeight = 10.2d0 | |||||
real(8) :: UpperRamHeight = 14.632d0 | |||||
real(8) :: LowerRamHeight = 21.35d0 | |||||
real(8) :: BlindRamHeight = 16.24d0 | |||||
real(8) :: KillHeight = 18.8d0 | |||||
real(8) :: KillOpen = 1.5d0 | |||||
real(8) :: KillClose = 1.5d0 | |||||
real(8) :: GroundLevel = 30.0d0 | |||||
real(8) :: LowerRamOpen | |||||
real(8) :: LowerRamClose | |||||
real(8) :: ChokeOpen | |||||
real(8) :: ChokeClose | |||||
real(8) :: BlindRamOpen | |||||
real(8) :: BlindRamClose | |||||
real(8) :: UpperRamOpen | |||||
real(8) :: UpperRamClose | |||||
real(8) :: AnnularPreventerOpen | |||||
real(8) :: AnnularPreventerClose | |||||
real(8) :: RamStringDrag | |||||
real(8) :: AnnularStringDrag | |||||
real(8) :: ChokeLineLength | |||||
real(8) :: ChokeLineId | |||||
contains | |||||
end module CBopStackVariables |
@@ -0,0 +1,76 @@ | |||||
module CHoisting | |||||
use CHoistingVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetDriveType(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDriveType | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDriveType' :: SetDriveType | |||||
use CManifolds | |||||
use CIrSafetyValveLedNotificationVariables, only: Set_IrSafetyValveLed | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
DriveType = v | |||||
#ifdef deb | |||||
print*, 'DriveType=', DriveType | |||||
#endif | |||||
if(v == TopDrive_DriveType) then ! top drive mode | |||||
call RemoveKellyCock() | |||||
call InstallTopDriveIBop() | |||||
call RemoveSafetyValve_TripMode() | |||||
call RemoveSafetyValve_KellyMode() | |||||
call Set_IrSafetyValveLed(.false.) | |||||
endif | |||||
if(v == Kelly_DriveType) then ! kelly mode | |||||
call RemoveTopDriveIBop() | |||||
call InstallKellyCock() | |||||
endif | |||||
end subroutine | |||||
subroutine SetTravelingBlockWeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTravelingBlockWeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTravelingBlockWeight' :: SetTravelingBlockWeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TravelingBlockWeight = v | |||||
end subroutine | |||||
subroutine SetTopDriveWeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveWeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDriveWeight' :: SetTopDriveWeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TopDriveWeight = v | |||||
end subroutine | |||||
subroutine SetKellyWeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetKellyWeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetKellyWeight' :: SetKellyWeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
KellyWeight = v | |||||
end subroutine | |||||
subroutine SetNumberOfLine(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetNumberOfLine | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetNumberOfLine' :: SetNumberOfLine | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
NumberOfLine = v | |||||
#ifdef deb | |||||
print*, 'NumberOfLine=', NumberOfLine | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDrillingLineBreakingLoad(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDrillingLineBreakingLoad | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDrillingLineBreakingLoad' :: SetDrillingLineBreakingLoad | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
DrillingLineBreakingLoad = v | |||||
end subroutine | |||||
end module CHoisting |
@@ -0,0 +1,16 @@ | |||||
module CHoistingVariables | |||||
implicit none | |||||
public | |||||
!constants | |||||
integer :: TopDrive_DriveType = 0 | |||||
integer :: Kelly_DriveType = 1 | |||||
! variables | |||||
integer :: DriveType | |||||
real(8) :: TravelingBlockWeight | |||||
real(8) :: TopDriveWeight | |||||
real(8) :: KellyWeight | |||||
integer :: NumberOfLine | |||||
real(8) :: DrillingLineBreakingLoad | |||||
contains | |||||
end module CHoistingVariables |
@@ -0,0 +1,71 @@ | |||||
module CPower | |||||
use CPowerVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetNumberOfgenerators(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetNumberOfgenerators | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetNumberOfgenerators' :: SetNumberOfgenerators | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
NumberOfgenerators = v | |||||
end subroutine | |||||
subroutine SetGeneratorPowerRating(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetGeneratorPowerRating | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetGeneratorPowerRating' :: SetGeneratorPowerRating | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
GeneratorPowerRating = v | |||||
end subroutine | |||||
subroutine SetMudPump1(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1' :: SetMudPump1 | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1 = v | |||||
end subroutine | |||||
subroutine SetMudPump2(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2' :: SetMudPump2 | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2 = v | |||||
end subroutine | |||||
subroutine SetCementPump(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPump | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPump' :: SetCementPump | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPump = v | |||||
end subroutine | |||||
subroutine SetRotaryTable(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRotaryTable | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRotaryTable' :: SetRotaryTable | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
RotaryTable = v | |||||
end subroutine | |||||
subroutine SetDrawworks(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDrawworks | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDrawworks' :: SetDrawworks | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
Drawworks = v | |||||
end subroutine | |||||
subroutine SetTopDrive(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTopDrive | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDrive' :: SetTopDrive | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TopDrive = v | |||||
end subroutine | |||||
end module CPower |
@@ -0,0 +1,14 @@ | |||||
module CPowerVariables | |||||
implicit none | |||||
public | |||||
! variables | |||||
integer :: NumberOfgenerators | |||||
real(8) :: GeneratorPowerRating | |||||
real(8) :: MudPump1 | |||||
real(8) :: MudPump2 | |||||
real(8) :: CementPump | |||||
real(8) :: RotaryTable | |||||
real(8) :: Drawworks | |||||
real(8) :: TopDrive | |||||
contains | |||||
end module CPowerVariables |
@@ -0,0 +1,381 @@ | |||||
module CPumps | |||||
use CPumpsVariables | |||||
use CManifolds | |||||
use CLog4 | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetMudPump1LinerDiameter(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1LinerDiameter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1LinerDiameter' :: SetMudPump1LinerDiameter | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1LinerDiameter = v | |||||
call CalcPump1OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'MudPump1LinerDiameter=', MudPump1LinerDiameter) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump1Stroke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1Stroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1Stroke' :: SetMudPump1Stroke | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1Stroke = v | |||||
!call CalcMudPump1LinerDiameter() | |||||
call CalcPump1OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'MudPump1Stroke=', v) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump1MechanicalEfficiency(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1MechanicalEfficiency | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1MechanicalEfficiency' :: SetMudPump1MechanicalEfficiency | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1MechanicalEfficiency = v | |||||
end subroutine | |||||
subroutine SetMudPump1VolumetricEfficiency(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1VolumetricEfficiency | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1VolumetricEfficiency' :: SetMudPump1VolumetricEfficiency | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1VolumetricEfficiency = v | |||||
!call CalcMudPump1LinerDiameter() | |||||
call CalcPump1OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'MudPump1VolumetricEfficiency=', MudPump1VolumetricEfficiency) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump1Output(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1Output | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1Output' :: SetMudPump1Output | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1Output = v | |||||
#ifdef deb | |||||
print*, 'MudPump1Output=', MudPump1Output | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump1OutputBblStroke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1OutputBblStroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1OutputBblStroke' :: SetMudPump1OutputBblStroke | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1OutputBblStroke = v | |||||
call CalcMudPump1LinerDiameter() | |||||
#ifdef deb | |||||
print*, 'MudPump1OutputBblStroke=', MudPump1OutputBblStroke | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump1Maximum(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1Maximum | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1Maximum' :: SetMudPump1Maximum | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1Maximum = v | |||||
end subroutine | |||||
subroutine SetMudPump1ReliefValvePressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1ReliefValvePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1ReliefValvePressure' :: SetMudPump1ReliefValvePressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump1ReliefValvePressure = v | |||||
end subroutine | |||||
subroutine SetMudPump2LinerDiameter(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2LinerDiameter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2LinerDiameter' :: SetMudPump2LinerDiameter | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2LinerDiameter = v | |||||
call CalcPump2OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'MudPump2LinerDiameter=', MudPump2LinerDiameter) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump2Stroke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2Stroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2Stroke' :: SetMudPump2Stroke | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2Stroke = v | |||||
!call CalcMudPump2LinerDiameter() | |||||
call CalcPump2OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'MudPump2Stroke=', MudPump2Stroke) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump2MechanicalEfficiency(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2MechanicalEfficiency | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2MechanicalEfficiency' :: SetMudPump2MechanicalEfficiency | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2MechanicalEfficiency = v | |||||
end subroutine | |||||
subroutine SetMudPump2VolumetricEfficiency(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2VolumetricEfficiency | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2VolumetricEfficiency' :: SetMudPump2VolumetricEfficiency | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2VolumetricEfficiency = v | |||||
!call CalcMudPump2LinerDiameter() | |||||
call CalcPump2OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'MudPump2VolumetricEfficiency=', MudPump2VolumetricEfficiency) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump2Output(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2Output | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2Output' :: SetMudPump2Output | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2Output = v | |||||
#ifdef deb | |||||
print*, 'MudPump2Output=', MudPump2Output | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump2OutputBblStroke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2OutputBblStroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2OutputBblStroke' :: SetMudPump2OutputBblStroke | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2OutputBblStroke = v | |||||
call CalcMudPump2LinerDiameter() | |||||
#ifdef deb | |||||
print*, 'MudPump2OutputBblStroke=', MudPump2OutputBblStroke | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump2Maximum(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2Maximum | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2Maximum' :: SetMudPump2Maximum | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2Maximum = v | |||||
end subroutine | |||||
subroutine SetMudPump2ReliefValvePressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2ReliefValvePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2ReliefValvePressure' :: SetMudPump2ReliefValvePressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MudPump2ReliefValvePressure = v | |||||
end subroutine | |||||
subroutine SetCementPumpLinerDiameter(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpLinerDiameter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpLinerDiameter' :: SetCementPumpLinerDiameter | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPumpLinerDiameter = v | |||||
call CalcPump3OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'CementPumpLinerDiameter=', CementPumpLinerDiameter) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCementPumpStroke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpStroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpStroke' :: SetCementPumpStroke | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPumpStroke = v | |||||
!call CalcMudPump3LinerDiameter() | |||||
call CalcPump3OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'CementPumpStroke=', CementPumpStroke) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCementPumpMechanicalEfficiency(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpMechanicalEfficiency | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpMechanicalEfficiency' :: SetCementPumpMechanicalEfficiency | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPumpMechanicalEfficiency = v | |||||
end subroutine | |||||
subroutine SetCementPumpVolumetricEfficiency(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpVolumetricEfficiency | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpVolumetricEfficiency' :: SetCementPumpVolumetricEfficiency | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPumpVolumetricEfficiency = v | |||||
!call CalcMudPump3LinerDiameter() | |||||
call CalcPump3OutputBblStroke() | |||||
#ifdef deb | |||||
call Log_4( 'CementPumpVolumetricEfficiency=', CementPumpVolumetricEfficiency) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCementPumpOutput(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpOutput | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpOutput' :: SetCementPumpOutput | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPumpOutput = v | |||||
#ifdef deb | |||||
print*, 'CementPumpOutput=', CementPumpOutput | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCementPumpOutputBblStroke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpOutputBblStroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpOutputBblStroke' :: SetCementPumpOutputBblStroke | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPumpOutputBblStroke = v | |||||
call CalcMudPump3LinerDiameter() | |||||
#ifdef deb | |||||
print*, 'CementPumpOutputBblStroke=', CementPumpOutputBblStroke | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCementPumpMaximum(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpMaximum | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpMaximum' :: SetCementPumpMaximum | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPumpMaximum = v | |||||
end subroutine | |||||
subroutine SetCementPumpReliefValvePressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpReliefValvePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpReliefValvePressure' :: SetCementPumpReliefValvePressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementPumpReliefValvePressure = v | |||||
end subroutine | |||||
subroutine SetMudPump1ReliefValveIsSet(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump1ReliefValveIsSet | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump1ReliefValveIsSet' :: SetMudPump1ReliefValveIsSet | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (MudPump1ReliefValveIsSet == v) return | |||||
MudPump1ReliefValveIsSet = v | |||||
#ifdef deb | |||||
print*, 'MudPump1ReliefValveIsSet=', MudPump1ReliefValveIsSet | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudPump2ReliefValveIsSet(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudPump2ReliefValveIsSet | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudPump2ReliefValveIsSet' :: SetMudPump2ReliefValveIsSet | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (MudPump2ReliefValveIsSet == v) return | |||||
MudPump2ReliefValveIsSet = v | |||||
#ifdef deb | |||||
print*, 'MudPump2ReliefValveIsSet=', MudPump2ReliefValveIsSet | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCementPumpReliefValveIsSet(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementPumpReliefValveIsSet | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementPumpReliefValveIsSet' :: SetCementPumpReliefValveIsSet | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (CementPumpReliefValveIsSet == v) return | |||||
CementPumpReliefValveIsSet = v | |||||
#ifdef deb | |||||
print*, 'CementPumpReliefValveIsSet=', CementPumpReliefValveIsSet | |||||
#endif | |||||
end subroutine | |||||
subroutine SetManualPumpPower(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetManualPumpPower | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetManualPumpPower' :: SetManualPumpPower | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ManualPumpPower = v | |||||
call ChangeValve(23, v) | |||||
#ifdef deb | |||||
print*, 'ManualPumpPower=', ManualPumpPower | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve1(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve1' :: SetValve1 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve1 = v | |||||
call ChangeValve(22, v) | |||||
#ifdef deb | |||||
print*, 'Valve1=', Valve1 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve2(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve2' :: SetValve2 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve2 = v | |||||
call ChangeValve(19, v) | |||||
#ifdef deb | |||||
print*, 'Valve2=', Valve2 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve3(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve3 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve3' :: SetValve3 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve3 = v | |||||
call ChangeValve(21, v) | |||||
#ifdef deb | |||||
print*, 'Valve3=', Valve3 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve4(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve4 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve4' :: SetValve4 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve4 = v | |||||
call ChangeValve(20, v) | |||||
#ifdef deb | |||||
print*, 'Valve4=', Valve4 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve5(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve5 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve5' :: SetValve5 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve5 = v | |||||
call ChangeValve(24, v) | |||||
#ifdef deb | |||||
print*, 'Valve5=', Valve5 | |||||
#endif | |||||
end subroutine | |||||
end module CPumps |
@@ -0,0 +1,260 @@ | |||||
module CPumpsVariables | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
! Pumps Specifications | |||||
real(8) :: MudPump1LinerDiameter | |||||
real(8) :: MudPump1Stroke | |||||
real(8) :: MudPump1MechanicalEfficiency | |||||
real(8) :: MudPump1VolumetricEfficiency | |||||
real(8) :: MudPump1Output | |||||
real(8) :: MudPump1OutputBblStroke | |||||
real(8) :: MudPump1Maximum | |||||
real(8) :: MudPump1ReliefValvePressure | |||||
real(8) :: MudPump2LinerDiameter | |||||
real(8) :: MudPump2Stroke | |||||
real(8) :: MudPump2MechanicalEfficiency | |||||
real(8) :: MudPump2VolumetricEfficiency | |||||
real(8) :: MudPump2Output | |||||
real(8) :: MudPump2OutputBblStroke | |||||
real(8) :: MudPump2Maximum | |||||
real(8) :: MudPump2ReliefValvePressure | |||||
real(8) :: CementPumpLinerDiameter | |||||
real(8) :: CementPumpStroke | |||||
real(8) :: CementPumpMechanicalEfficiency | |||||
real(8) :: CementPumpVolumetricEfficiency | |||||
real(8) :: CementPumpOutput | |||||
real(8) :: CementPumpOutputBblStroke | |||||
real(8) :: CementPumpMaximum | |||||
real(8) :: CementPumpReliefValvePressure | |||||
logical :: MudPump1ReliefValveIsSet | |||||
logical :: MudPump2ReliefValveIsSet | |||||
logical :: CementPumpReliefValveIsSet | |||||
logical :: ManualPumpPower | |||||
logical :: Valve1 | |||||
logical :: Valve2 | |||||
logical :: Valve3 | |||||
logical :: Valve4 | |||||
logical :: Valve5 | |||||
procedure (ActionDouble), pointer :: MudPump1LinerDiameterPtr | |||||
procedure (ActionDouble), pointer :: MudPump2LinerDiameterPtr | |||||
procedure (ActionDouble), pointer :: MudPump3LinerDiameterPtr | |||||
procedure (ActionDouble), pointer :: MudPump1OutputBblStrokePtr | |||||
procedure (ActionDouble), pointer :: MudPump2OutputBblStrokePtr | |||||
procedure (ActionDouble), pointer :: MudPump3OutputBblStrokePtr | |||||
real(8) :: MathPI = 3.14159265358979d0 | |||||
contains | |||||
subroutine OpenPump1() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(16, .true.) | |||||
end subroutine | |||||
subroutine ClosePump1() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(16, .false.) | |||||
end subroutine | |||||
subroutine OpenPump2() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(17, .true.) | |||||
end subroutine | |||||
subroutine ClosePump2() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(17, .false.) | |||||
end subroutine | |||||
subroutine OpenCementPump() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(18, .true.) | |||||
end subroutine | |||||
subroutine CloseCementPump() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(18, .false.) | |||||
end subroutine | |||||
subroutine SubscribeMudPump1LinerDiameter(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump1LinerDiameter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump1LinerDiameter' :: SubscribeMudPump1LinerDiameter | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
MudPump1LinerDiameterPtr => a | |||||
end subroutine | |||||
subroutine SubscribeMudPump2LinerDiameter(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump2LinerDiameter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump2LinerDiameter' :: SubscribeMudPump2LinerDiameter | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
MudPump2LinerDiameterPtr => a | |||||
end subroutine | |||||
subroutine SubscribeMudPump3LinerDiameter(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump3LinerDiameter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump3LinerDiameter' :: SubscribeMudPump3LinerDiameter | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
MudPump3LinerDiameterPtr => a | |||||
end subroutine | |||||
subroutine SubscribeMudPump1OutputBblStroke(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump1OutputBblStroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump1OutputBblStroke' :: SubscribeMudPump1OutputBblStroke | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
MudPump1OutputBblStrokePtr => a | |||||
end subroutine | |||||
subroutine SubscribeMudPump2OutputBblStroke(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump2OutputBblStroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump2OutputBblStroke' :: SubscribeMudPump2OutputBblStroke | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
MudPump2OutputBblStrokePtr => a | |||||
end subroutine | |||||
subroutine SubscribeMudPump3OutputBblStroke(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeMudPump3OutputBblStroke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeMudPump3OutputBblStroke' :: SubscribeMudPump3OutputBblStroke | |||||
implicit none | |||||
procedure (ActionDouble) :: a | |||||
MudPump3OutputBblStrokePtr => a | |||||
end subroutine | |||||
subroutine SetMudPump1LinerDiameterN(a) | |||||
implicit none | |||||
real(8) :: a | |||||
if(associated(MudPump1LinerDiameterPtr)) call MudPump1LinerDiameterPtr(a) | |||||
end subroutine | |||||
subroutine SetMudPump2LinerDiameterN(a) | |||||
implicit none | |||||
real(8) :: a | |||||
if(associated(MudPump2LinerDiameterPtr)) call MudPump2LinerDiameterPtr(a) | |||||
end subroutine | |||||
subroutine SetMudPump3LinerDiameterN(a) | |||||
implicit none | |||||
real(8) :: a | |||||
if(associated(MudPump3LinerDiameterPtr)) call MudPump3LinerDiameterPtr(a) | |||||
end subroutine | |||||
subroutine SetMudPump1OutputBblStrokeN(a) | |||||
implicit none | |||||
real(8) :: a | |||||
if(associated(MudPump1OutputBblStrokePtr)) call MudPump1OutputBblStrokePtr(a) | |||||
end subroutine | |||||
subroutine SetMudPump2OutputBblStrokeN(a) | |||||
implicit none | |||||
real(8) :: a | |||||
if(associated(MudPump2OutputBblStrokePtr)) call MudPump2OutputBblStrokePtr(a) | |||||
end subroutine | |||||
subroutine SetMudPump3OutputBblStrokeN(a) | |||||
implicit none | |||||
real(8) :: a | |||||
if(associated(MudPump3OutputBblStrokePtr)) call MudPump3OutputBblStrokePtr(a) | |||||
end subroutine | |||||
subroutine CalcMudPump1LinerDiameter() | |||||
use, intrinsic :: IEEE_ARITHMETIC | |||||
implicit none | |||||
real(8) :: a | |||||
a = (MathPI / 4.d0) * MudPump1Stroke * 3.0d0 * MudPump1VolumetricEfficiency / 9702.03d0 | |||||
a = dsqrt(MudPump1OutputBblStroke / a) | |||||
if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then | |||||
MudPump1LinerDiameter = 0.0 | |||||
else | |||||
MudPump1LinerDiameter = a | |||||
endif | |||||
call SetMudPump1LinerDiameterN(MudPump1LinerDiameter) | |||||
end subroutine | |||||
subroutine CalcMudPump2LinerDiameter() | |||||
use, intrinsic :: IEEE_ARITHMETIC | |||||
implicit none | |||||
real(8) :: a | |||||
a = (MathPI / 4.d0) * MudPump2Stroke * 3.0d0 * MudPump2VolumetricEfficiency / 9702.03d0 | |||||
a = dsqrt(MudPump2OutputBblStroke / a) | |||||
if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then | |||||
MudPump2LinerDiameter = 0.0 | |||||
else | |||||
MudPump2LinerDiameter = a | |||||
endif | |||||
call SetMudPump2LinerDiameterN(MudPump2LinerDiameter) | |||||
end subroutine | |||||
subroutine CalcMudPump3LinerDiameter() | |||||
use, intrinsic :: IEEE_ARITHMETIC | |||||
implicit none | |||||
real(8) :: a | |||||
a = (MathPI / 4.d0) * CementPumpStroke * 3.0d0 * CementPumpVolumetricEfficiency / 9702.03d0 | |||||
a = dsqrt(CementPumpOutputBblStroke / a) | |||||
if (.not.IEEE_IS_FINITE(a) .or. IEEE_IS_NAN(a)) then | |||||
CementPumpLinerDiameter = 0.0 | |||||
else | |||||
CementPumpLinerDiameter = a | |||||
endif | |||||
call SetMudPump3LinerDiameterN(CementPumpLinerDiameter) | |||||
end subroutine | |||||
subroutine CalcPump1OutputBblStroke() | |||||
implicit none | |||||
MudPump1OutputBblStroke = (MathPI / 4.d0) * (MudPump1LinerDiameter**2) * MudPump1Stroke * 3.0d0 * MudPump1VolumetricEfficiency / 9702.03d0 | |||||
call SetMudPump1OutputBblStrokeN(MudPump1OutputBblStroke) | |||||
end subroutine | |||||
subroutine CalcPump2OutputBblStroke() | |||||
implicit none | |||||
MudPump2OutputBblStroke = (MathPI / 4.d0) * (MudPump2LinerDiameter**2) * MudPump2Stroke * 3.0d0 * MudPump2VolumetricEfficiency / 9702.03d0 | |||||
call SetMudPump2OutputBblStrokeN(MudPump2OutputBblStroke) | |||||
end subroutine | |||||
subroutine CalcPump3OutputBblStroke() | |||||
implicit none | |||||
CementPumpOutputBblStroke = (MathPI / 4.d0) * (CementPumpLinerDiameter**2) * CementPumpStroke * 3.0d0 * CementPumpVolumetricEfficiency / 9702.03d0 | |||||
call SetMudPump3OutputBblStrokeN(CementPumpOutputBblStroke) | |||||
end subroutine | |||||
end module CPumpsVariables |
@@ -0,0 +1,37 @@ | |||||
module CRigSize | |||||
use CRigSizeVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetRigType(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRigType | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRigType' :: SetRigType | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
RigType = v | |||||
end subroutine | |||||
subroutine SetCrownHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCrownHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCrownHeight' :: SetCrownHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CrownHeight = v | |||||
end subroutine | |||||
subroutine SetMonkeyBoandHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMonkeyBoandHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMonkeyBoandHeight' :: SetMonkeyBoandHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MonkeyBoandHeight = v | |||||
end subroutine | |||||
subroutine SetRigFloorHeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRigFloorHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRigFloorHeight' :: SetRigFloorHeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
RigFloorHeight = v | |||||
end subroutine | |||||
end module CRigSize |
@@ -0,0 +1,13 @@ | |||||
module CRigSizeVariables | |||||
implicit none | |||||
public | |||||
!constants | |||||
integer :: Convensional_RigSize = 0 | |||||
! variables | |||||
integer :: RigType | |||||
real(8) :: CrownHeight | |||||
real(8) :: MonkeyBoandHeight | |||||
real(8) :: RigFloorHeight | |||||
contains | |||||
end module CRigSizeVariables |
@@ -0,0 +1,145 @@ | |||||
module CCasingLinerChoke | |||||
use CCasingLinerChokeVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetCasingDepth(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCasingDepth | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCasingDepth' :: SetCasingDepth | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CasingDepth = v | |||||
end subroutine | |||||
subroutine SetCasingId(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCasingId | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCasingId' :: SetCasingId | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CasingId = v | |||||
end subroutine | |||||
subroutine SetCasingOd(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCasingOd | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCasingOd' :: SetCasingOd | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CasingOd = v | |||||
end subroutine | |||||
subroutine SetCasingWeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCasingWeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCasingWeight' :: SetCasingWeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CasingWeight = v | |||||
end subroutine | |||||
subroutine SetCasingCollapsePressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCasingCollapsePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCasingCollapsePressure' :: SetCasingCollapsePressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CasingCollapsePressure = v | |||||
end subroutine | |||||
subroutine SetCasingTensileStrength(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCasingTensileStrength | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCasingTensileStrength' :: SetCasingTensileStrength | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CasingTensileStrength = v | |||||
end subroutine | |||||
subroutine SetLinerTopDepth(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLinerTopDepth | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLinerTopDepth' :: SetLinerTopDepth | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LinerTopDepth = v | |||||
end subroutine | |||||
subroutine SetLinerLength(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLinerLength | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLinerLength' :: SetLinerLength | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LinerLength = v | |||||
end subroutine | |||||
subroutine SetLinerId(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLinerId | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLinerId' :: SetLinerId | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LinerId = v | |||||
end subroutine | |||||
subroutine SetLinerOd(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLinerOd | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLinerOd' :: SetLinerOd | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LinerOd = v | |||||
end subroutine | |||||
subroutine SetLinerWeight(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLinerWeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLinerWeight' :: SetLinerWeight | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LinerWeight = v | |||||
end subroutine | |||||
subroutine SetLinerCollapsePressure(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLinerCollapsePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLinerCollapsePressure' :: SetLinerCollapsePressure | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LinerCollapsePressure = v | |||||
end subroutine | |||||
subroutine SetLinerTensileStrength(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLinerTensileStrength | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLinerTensileStrength' :: SetLinerTensileStrength | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LinerTensileStrength = v | |||||
end subroutine | |||||
subroutine SetOpenHoleId(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetOpenHoleId | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetOpenHoleId' :: SetOpenHoleId | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
OpenHoleId = v | |||||
#ifdef deb | |||||
print*, 'OpenHoleId=', OpenHoleId | |||||
#endif | |||||
end subroutine | |||||
subroutine SetOpenHoleLength(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetOpenHoleLength | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetOpenHoleLength' :: SetOpenHoleLength | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
OpenHoleLength = v | |||||
#ifdef deb | |||||
print*, 'OpenHoleLength=', OpenHoleLength | |||||
#endif | |||||
end subroutine | |||||
end module CCasingLinerChoke |
@@ -0,0 +1,24 @@ | |||||
module CCasingLinerChokeVariables | |||||
implicit none | |||||
public | |||||
! variables | |||||
real(8) :: CasingDepth | |||||
real(8) :: CasingId | |||||
real(8) :: CasingOd | |||||
real(8) :: CasingWeight | |||||
real(8) :: CasingCollapsePressure | |||||
real(8) :: CasingTensileStrength | |||||
real(8) :: LinerTopDepth | |||||
real(8) :: LinerLength | |||||
real(8) :: LinerId | |||||
real(8) :: LinerOd | |||||
real(8) :: LinerWeight | |||||
real(8) :: LinerCollapsePressure | |||||
real(8) :: LinerTensileStrength | |||||
real(8) :: OpenHoleId | |||||
real(8) :: OpenHoleLength | |||||
contains | |||||
end module CCasingLinerChokeVariables |
@@ -0,0 +1,59 @@ | |||||
module CPathGeneration | |||||
use CPathGenerationVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
integer function SetPathGeneration(count, array) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::SetPathGeneration | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetPathGeneration' :: SetPathGeneration | |||||
implicit none | |||||
integer, intent(in) :: count | |||||
integer :: i | |||||
type(CPathGenerationItem), intent(inout), target :: array(count) | |||||
type(CPathGenerationItem), pointer :: item | |||||
PathGenerationCount = count | |||||
if(size(PathGenerations) > 0) then | |||||
deallocate(PathGenerations) | |||||
end if | |||||
if(count > 0) then | |||||
allocate(PathGenerations(count)) | |||||
do i = 1, count | |||||
item => array(i) | |||||
PathGenerations(i)%HoleType = item%HoleType | |||||
PathGenerations(i)%Angle = item%Angle | |||||
PathGenerations(i)%Length = item%Length | |||||
PathGenerations(i)%FinalAngle = item%FinalAngle | |||||
PathGenerations(i)%TotalLength = item%TotalLength | |||||
PathGenerations(i)%MeasuredDepth = item%MeasuredDepth | |||||
PathGenerations(i)%TotalVerticalDepth = item%TotalVerticalDepth | |||||
end do | |||||
end if | |||||
SetPathGeneration = 0 | |||||
end function SetPathGeneration | |||||
integer function SetPathGenerationDataPoints(count, array) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::SetPathGenerationDataPoints | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetPathGenerationDataPoints' :: SetPathGenerationDataPoints | |||||
implicit none | |||||
integer, intent(in) :: count | |||||
integer :: i | |||||
type(CDataPointItem), intent(inout), target :: array(count) | |||||
type(CDataPointItem), pointer :: item | |||||
PathGenerationDataPointsCount = count | |||||
if(size(PathGenerationDataPoints) > 0) then | |||||
deallocate(PathGenerationDataPoints) | |||||
end if | |||||
if(count > 0) then | |||||
allocate(PathGenerationDataPoints(count)) | |||||
do i = 1, count | |||||
item => array(i) | |||||
PathGenerationDataPoints(i)%X = item%X | |||||
PathGenerationDataPoints(i)%Y = item%Y | |||||
end do | |||||
end if | |||||
SetPathGenerationDataPoints = 0 | |||||
end function SetPathGenerationDataPoints | |||||
end module CPathGeneration |
@@ -0,0 +1,28 @@ | |||||
module CPathGenerationVariables | |||||
implicit none | |||||
public | |||||
! types | |||||
type, bind(c), public :: CPathGenerationItem | |||||
integer :: HoleType | |||||
real(8) :: Angle | |||||
real(8) :: Length | |||||
real(8) :: FinalAngle | |||||
real(8) :: TotalLength | |||||
real(8) :: MeasuredDepth | |||||
real(8) :: TotalVerticalDepth | |||||
end type CPathGenerationItem | |||||
type, bind(c), public :: CDataPointItem | |||||
real(8) :: X | |||||
real(8) :: Y | |||||
end type CDataPointItem | |||||
integer :: PathGenerationCount = 0 | |||||
type(CPathGenerationItem), allocatable :: PathGenerations(:) | |||||
integer :: PathGenerationDataPointsCount = 0 | |||||
type(CDataPointItem), allocatable :: PathGenerationDataPoints(:) | |||||
contains | |||||
end module CPathGenerationVariables |
@@ -0,0 +1,34 @@ | |||||
module CWellSurveyData | |||||
use CWellSurveyDataVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
integer function SetSurveyData(count, array) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::SetSurveyData | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetSurveyData' :: SetSurveyData | |||||
implicit none | |||||
integer, intent(in) :: count | |||||
integer :: i | |||||
type(CSurveyDataItem), intent(inout), target :: array(count) | |||||
type(CSurveyDataItem), pointer :: item | |||||
SurveyDataCount = count | |||||
if(size(WellSurveyData) > 0) then | |||||
deallocate(WellSurveyData) | |||||
end if | |||||
if(count > 0) then | |||||
allocate(WellSurveyData(count)) | |||||
do i = 1, count | |||||
item => array(i) | |||||
WellSurveyData(i)%MeasuredDepth = item%MeasuredDepth | |||||
WellSurveyData(i)%Inclination = item%Inclination | |||||
WellSurveyData(i)%Azimoth = item%Azimoth | |||||
WellSurveyData(i)%TotalVerticalDepth = item%TotalVerticalDepth | |||||
WellSurveyData(i)%X = item%X | |||||
WellSurveyData(i)%Y = item%Y | |||||
WellSurveyData(i)%Z = item%Z | |||||
end do | |||||
end if | |||||
SetSurveyData = 0 | |||||
end function SetSurveyData | |||||
end module CWellSurveyData |
@@ -0,0 +1,20 @@ | |||||
module CWellSurveyDataVariables | |||||
implicit none | |||||
public | |||||
! types | |||||
type, bind(c), public :: CSurveyDataItem | |||||
real(8) :: MeasuredDepth | |||||
real(8) :: Inclination | |||||
real(8) :: Azimoth | |||||
real(8) :: TotalVerticalDepth | |||||
real(8) :: X | |||||
real(8) :: Y | |||||
real(8) :: Z | |||||
end type CSurveyDataItem | |||||
integer :: SurveyDataCount = 0 | |||||
type(CSurveyDataItem), allocatable :: WellSurveyData(:) | |||||
contains | |||||
end module CWellSurveyDataVariables |
@@ -0,0 +1,53 @@ | |||||
module CCommon | |||||
use CCommonVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
subroutine SetStandRack(v) | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
if(StandRack == v) return | |||||
StandRack = v | |||||
call OnStandRackChange%Run(v) | |||||
#ifdef deb | |||||
print*, 'StandRack=', StandRack | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandRack_WN(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandRack_WN | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandRack_WN' :: SetStandRack_WN | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
call SetStandRack(v) | |||||
end subroutine | |||||
! Output routines | |||||
logical function GetDrillWatchOperationMode() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetDrillWatchOperationMode | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetDrillWatchOperationMode' :: GetDrillWatchOperationMode | |||||
implicit none | |||||
GetDrillWatchOperationMode = DrillWatchOperationMode | |||||
end function | |||||
integer function GetStandRack() | |||||
implicit none | |||||
GetStandRack = StandRack | |||||
end function | |||||
integer function GetStandRack_WN() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetStandRack_WN | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStandRack_WN' :: GetStandRack_WN | |||||
implicit none | |||||
GetStandRack_WN = StandRack | |||||
end function | |||||
end module CCommon |
@@ -0,0 +1,15 @@ | |||||
module CCommonVariables | |||||
use CIntegerEventHandler | |||||
implicit none | |||||
public | |||||
! Input vars | |||||
integer :: StandRack | |||||
type(IntegerEventHandler) :: OnStandRackChange | |||||
! Output vars | |||||
logical :: DrillWatchOperationMode | |||||
contains | |||||
end module CCommonVariables |
@@ -0,0 +1,55 @@ | |||||
module CIActionReference | |||||
implicit none | |||||
abstract interface | |||||
subroutine ActionVoid() | |||||
end subroutine | |||||
subroutine ActionBool(i) | |||||
logical, intent (in) :: i | |||||
end subroutine | |||||
subroutine ActionInteger(i) | |||||
integer, intent (in) :: i | |||||
end subroutine | |||||
subroutine ActionIntegerArray(arr) | |||||
integer, allocatable, intent (in) :: arr(:) | |||||
end subroutine | |||||
subroutine ActionReal(i) | |||||
real, intent (in) :: i | |||||
end subroutine | |||||
subroutine ActionDouble(i) | |||||
real(8), intent (in) :: i | |||||
end subroutine | |||||
subroutine ActionDualDouble(a, b) | |||||
real(8), intent (in) :: a, b | |||||
end subroutine | |||||
subroutine ActionString(c) | |||||
character(len=*), intent(in) :: c | |||||
end subroutine | |||||
subroutine ActionStringInt(c, i) | |||||
character(len=*), intent(in) :: c | |||||
integer, intent (in) :: i | |||||
end subroutine | |||||
subroutine ActionStringFloat(c, f) | |||||
character(len=*), intent(in) :: c | |||||
real, intent (in) :: f | |||||
end subroutine | |||||
subroutine ActionStringDouble(c, d) | |||||
character(len=*), intent(in) :: c | |||||
real(8), intent (in) :: d | |||||
end subroutine | |||||
subroutine ActionStringBool(c, b) | |||||
character(len=*), intent(in) :: c | |||||
logical, intent (in) :: b | |||||
end subroutine | |||||
end interface | |||||
end module CIActionReference |
@@ -0,0 +1,15 @@ | |||||
module CLesson | |||||
use CLessonVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
subroutine SetWellProfileApproach(path, survey) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetWellProfileApproach | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetWellProfileApproach' :: SetWellProfileApproach | |||||
implicit none | |||||
logical, intent(in) :: path | |||||
logical, intent(in) :: survey | |||||
IsPathGeneration = path | |||||
IsWellSurveyData = survey | |||||
end subroutine | |||||
end module CLesson |
@@ -0,0 +1,9 @@ | |||||
module CLessonVariables | |||||
implicit none | |||||
public | |||||
logical :: IsPathGeneration | |||||
logical :: IsWellSurveyData | |||||
contains | |||||
end module CLessonVariables |
@@ -0,0 +1,17 @@ | |||||
module CQuery | |||||
implicit none | |||||
public GetCurrentProcessorNumber | |||||
interface | |||||
function GetCurrentProcessorNumber() bind(C,Name='GetCurrentProcessorNumber') | |||||
use ifwinty | |||||
implicit none | |||||
!DEC$ ATTRIBUTES STDCALL :: GetCurrentProcessorNumber | |||||
integer(DWORD) :: GetCurrentProcessorNumber | |||||
end function GetCurrentProcessorNumber | |||||
end interface | |||||
contains | |||||
end module CQuery |
@@ -0,0 +1,16 @@ | |||||
module CScaleRange | |||||
implicit none | |||||
public | |||||
contains | |||||
real function ScaleRange(x, toMin, toMax, fromMin, fromMax) | |||||
implicit none | |||||
real, intent(in) :: x | |||||
real, intent(in) :: toMin | |||||
real, intent(in) :: toMax | |||||
real, intent(in) :: fromMin | |||||
real, intent(in) :: fromMax | |||||
ScaleRange = ((toMax - toMin)*(x - fromMin)/(fromMax - fromMin)) + toMin | |||||
end function | |||||
end module CScaleRange |
@@ -0,0 +1,54 @@ | |||||
module CTimer | |||||
use ifwin, only: QueryPerformanceFrequency, QueryPerformanceCounter, T_LARGE_INTEGER | |||||
use ISO_C_BINDING | |||||
use ISO_FORTRAN_ENV | |||||
implicit none | |||||
public | |||||
type, public :: Timer | |||||
type(T_LARGE_INTEGER) :: StartTime | |||||
type(T_LARGE_INTEGER) :: EndTime | |||||
contains | |||||
procedure :: Start => Start | |||||
procedure :: Finish => Finish | |||||
procedure :: ElapsedTimeMs => ElapsedTime | |||||
end type Timer | |||||
contains | |||||
subroutine Start(this) | |||||
implicit none | |||||
class(Timer), intent(inout) :: this | |||||
integer :: ApiResult | |||||
ApiResult = QueryPerformanceCounter(this%StartTime) | |||||
end subroutine | |||||
subroutine Finish(this) | |||||
implicit none | |||||
class(Timer), intent(inout) :: this | |||||
integer :: ApiResult | |||||
ApiResult = QueryPerformanceCounter(this%EndTime) | |||||
end subroutine | |||||
integer function ElapsedTime(this) | |||||
implicit none | |||||
class(Timer), intent(inout) :: this | |||||
real(kind=REAL128) :: time | |||||
time = CalcTime(this%StartTime, this%EndTime) | |||||
ElapsedTime = int(time * 1000.0) | |||||
end function | |||||
real(kind=REAL128) function CalcTime(start, finish) | |||||
implicit none | |||||
type(T_LARGE_INTEGER), intent(in) :: start | |||||
type(T_LARGE_INTEGER), intent(in) :: finish | |||||
type(T_LARGE_INTEGER) :: freq | |||||
integer :: ApiResult | |||||
integer(kind=INT64) :: freq_64 | |||||
integer(kind=INT64) :: start_64 | |||||
integer(kind=INT64) :: finish_64 | |||||
start_64 = Make64(start) | |||||
finish_64 = Make64(finish) | |||||
ApiResult = QueryPerformanceFrequency(freq) | |||||
freq_64 = Make64( freq) | |||||
CalcTime = real(finish_64-start_64,kind=REAL128) / real(freq_64,kind=REAL128) | |||||
end function | |||||
integer(kind=INT64) function Make64(bit64_int) | |||||
type(T_LARGE_INTEGER), intent(in) :: bit64_int | |||||
Make64 = transfer(bit64_int, 0_INT64) | |||||
end function | |||||
end module CTimer |
@@ -0,0 +1,28 @@ | |||||
module CTimerLegacy | |||||
implicit none | |||||
public | |||||
type, public :: TimerLegacy | |||||
integer, dimension(8) :: StartTime | |||||
integer, dimension(8) :: EndTime | |||||
contains | |||||
procedure :: Start => Start | |||||
procedure :: Finish => Finish | |||||
procedure :: ElapsedTimeMs => ElapsedTime | |||||
end type TimerLegacy | |||||
contains | |||||
subroutine Start(this) | |||||
implicit none | |||||
class(TimerLegacy), intent(inout) :: this | |||||
call date_and_time(values=this%StartTime) | |||||
end subroutine | |||||
subroutine Finish(this) | |||||
implicit none | |||||
class(TimerLegacy), intent(inout) :: this | |||||
call date_and_time(values=this%EndTime) | |||||
end subroutine | |||||
integer function ElapsedTime(this) | |||||
implicit none | |||||
class(TimerLegacy), intent(inout) :: this | |||||
ElapsedTime = (this%EndTime(6)*60000+this%EndTime(7)*1000+this%EndTime(8)) - (this%StartTime(6)*60000+this%StartTime(7)*1000+this%StartTime(8)) | |||||
end function | |||||
end module CTimerLegacy |
@@ -0,0 +1,44 @@ | |||||
module CBoolEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: BoolEventHandler | |||||
procedure(ActionBool), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type BoolEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(BoolEventHandler), intent(inout) :: this | |||||
procedure (ActionBool), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(BoolEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(BoolEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(BoolEventHandler), intent(inout) :: this | |||||
logical, intent(in) :: arg | |||||
!if(.not.this%IsNull()) | |||||
call this%Delegate(arg) | |||||
end subroutine | |||||
end module CBoolEventHandler |
@@ -0,0 +1,103 @@ | |||||
module CBoolEventHandlerCollection | |||||
use CBoolEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: BoolEventHandlerCollection | |||||
type(BoolEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type BoolEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(inout) :: this | |||||
type(BoolEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionBool), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(BoolEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this, arg) | |||||
implicit none | |||||
class(BoolEventHandlerCollection), intent(inout) :: this | |||||
logical, intent(in) :: arg | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CBoolEventHandlerCollection |
@@ -0,0 +1,43 @@ | |||||
module CDoubleEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: DoubleEventHandler | |||||
procedure(ActionDouble), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type DoubleEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(DoubleEventHandler), intent(inout) :: this | |||||
procedure (ActionDouble), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(DoubleEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(DoubleEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(DoubleEventHandler), intent(inout) :: this | |||||
real(8), intent(in) :: arg | |||||
if(.not.this%IsNull()) call this%Delegate(arg) | |||||
end subroutine | |||||
end module CDoubleEventHandler |
@@ -0,0 +1,103 @@ | |||||
module CDoubleEventHandlerCollection | |||||
use CDoubleEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: DoubleEventHandlerCollection | |||||
type(DoubleEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type DoubleEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(inout) :: this | |||||
type(DoubleEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionDouble), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(DoubleEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this, arg) | |||||
implicit none | |||||
class(DoubleEventHandlerCollection), intent(inout) :: this | |||||
real(8), intent(in) :: arg | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CDoubleEventHandlerCollection |
@@ -0,0 +1,44 @@ | |||||
module CIntegerArrayEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: IntegerArrayEventHandler | |||||
procedure(ActionIntegerArray), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type IntegerArrayEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(IntegerArrayEventHandler), intent(inout) :: this | |||||
procedure (ActionIntegerArray), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(IntegerArrayEventHandler), intent(inout) :: this | |||||
integer, allocatable, intent (in) :: arg(:) | |||||
!if(.not.this%IsNull()) | |||||
call this%Delegate(arg) | |||||
end subroutine | |||||
end module CIntegerArrayEventHandler |
@@ -0,0 +1,103 @@ | |||||
module CIntegerArrayEventHandlerCollection | |||||
use CIntegerArrayEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: IntegerArrayEventHandlerCollection | |||||
type(IntegerArrayEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll_ | |||||
end type IntegerArrayEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(inout) :: this | |||||
type(IntegerArrayEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionIntegerArray), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(IntegerArrayEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll_(this, arg) | |||||
implicit none | |||||
class(IntegerArrayEventHandlerCollection), intent(inout) :: this | |||||
integer, allocatable, intent (in) :: arg(:) | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CIntegerArrayEventHandlerCollection |
@@ -0,0 +1,44 @@ | |||||
module CIntegerEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: IntegerEventHandler | |||||
procedure(ActionInteger), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type IntegerEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(IntegerEventHandler), intent(inout) :: this | |||||
procedure (ActionInteger), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(IntegerEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(IntegerEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(IntegerEventHandler), intent(inout) :: this | |||||
integer, intent(in) :: arg | |||||
!if(.not.this%IsNull()) | |||||
call this%Delegate(arg) | |||||
end subroutine | |||||
end module CIntegerEventHandler |
@@ -0,0 +1,103 @@ | |||||
module CIntegerEventHandlerCollection | |||||
use CIntegerEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: IntegerEventHandlerCollection | |||||
type(IntegerEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type IntegerEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(inout) :: this | |||||
type(IntegerEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionInteger), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(IntegerEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this, arg) | |||||
implicit none | |||||
class(IntegerEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: arg | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CIntegerEventHandlerCollection |
@@ -0,0 +1,44 @@ | |||||
module CRealEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: RealEventHandler | |||||
procedure(ActionReal), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type RealEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(RealEventHandler), intent(inout) :: this | |||||
procedure (ActionReal), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(RealEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(RealEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this, arg) | |||||
implicit none | |||||
class(RealEventHandler), intent(inout) :: this | |||||
real, intent(in) :: arg | |||||
!if(.not.this%IsNull()) | |||||
call this%Delegate(arg) | |||||
end subroutine | |||||
end module CRealEventHandler |
@@ -0,0 +1,103 @@ | |||||
module CRealEventHandlerCollection | |||||
use CRealEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: RealEventHandlerCollection | |||||
type(RealEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type RealEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(inout) :: this | |||||
type(RealEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionReal), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(RealEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this, arg) | |||||
implicit none | |||||
class(RealEventHandlerCollection), intent(inout) :: this | |||||
real, intent(in) :: arg | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run(arg) | |||||
end do | |||||
end subroutine | |||||
end module CRealEventHandlerCollection |
@@ -0,0 +1,44 @@ | |||||
module CVoidEventHandler | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
type :: VoidEventHandler | |||||
procedure(ActionVoid), pointer, nopass :: Delegate => null() | |||||
contains | |||||
procedure :: AssignTo => AssignTo | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Run => Run | |||||
end type VoidEventHandler | |||||
contains | |||||
subroutine AssignTo(this, proc) | |||||
implicit none | |||||
class(VoidEventHandler), intent(inout) :: this | |||||
procedure (ActionVoid), pointer, intent(in) :: proc | |||||
this%Delegate => proc | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(VoidEventHandler), intent(inout) :: this | |||||
this%Delegate => null() | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(VoidEventHandler), intent(in) :: this | |||||
IsNull = .not.associated(this%Delegate) | |||||
end function | |||||
subroutine Run(this) | |||||
implicit none | |||||
class(VoidEventHandler), intent(inout) :: this | |||||
!if(.not.this%IsNull()) then | |||||
call this%Delegate() | |||||
!endif | |||||
end subroutine | |||||
end module CVoidEventHandler |
@@ -0,0 +1,102 @@ | |||||
module CVoidEventHandlerCollection | |||||
use CVoidEventHandler | |||||
implicit none | |||||
public | |||||
type, public :: VoidEventHandlerCollection | |||||
type(VoidEventHandler), allocatable :: Delegates(:) | |||||
contains | |||||
procedure :: Length => Length | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Empty => Empty | |||||
procedure :: IsEmpty => IsEmpty | |||||
procedure :: RunAll => RunAll | |||||
end type VoidEventHandlerCollection | |||||
contains | |||||
integer function Length(this) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(in) :: this | |||||
if(allocated(this%Delegates)) then | |||||
Length = size(this%Delegates) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine Add(this, proc) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(inout) :: this | |||||
type(VoidEventHandler), allocatable :: tempArr(:) | |||||
procedure (ActionVoid), pointer, intent(in) :: proc | |||||
integer :: i, isize | |||||
if(allocated(this%Delegates)) then | |||||
isize = size(this%Delegates) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Delegates(i) | |||||
end do | |||||
call tempArr(isize+1)%MakeNull() | |||||
call tempArr(isize+1)%AssignTo(proc) | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
else | |||||
allocate(this%Delegates(1)) | |||||
call this%Delegates(1)%MakeNull() | |||||
call this%Delegates(1)%AssignTo(proc) | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
type(VoidEventHandler), allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Delegates)) return | |||||
if(.not.allocated(this%Delegates))return | |||||
allocate(tempArr(size(this%Delegates)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Delegates) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Delegates(i) | |||||
else | |||||
tempArr(i) = this%Delegates(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Delegates) | |||||
call move_alloc(tempArr, this%Delegates) | |||||
end subroutine | |||||
subroutine Empty(this) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(inout) :: this | |||||
if(allocated(this%Delegates)) deallocate(this%Delegates) | |||||
end subroutine | |||||
logical function IsEmpty(this) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(in) :: this | |||||
IsEmpty = .not.allocated(this%Delegates) | |||||
end function | |||||
subroutine RunAll(this) | |||||
implicit none | |||||
class(VoidEventHandlerCollection), intent(inout) :: this | |||||
integer :: i | |||||
do i=1, size(this%Delegates) | |||||
call this%Delegates(i)%Run() | |||||
end do | |||||
end subroutine | |||||
end module CVoidEventHandlerCollection |
@@ -0,0 +1,278 @@ | |||||
module CDownHole | |||||
use CDownHoleVariables | |||||
implicit none | |||||
public | |||||
!abstract interface | |||||
! subroutine ActionFluid(array) | |||||
! use CDownHoleVariables | |||||
! type(CFluid), intent(inout), target :: array | |||||
! end subroutine | |||||
!end interface | |||||
contains | |||||
subroutine AnnalusDrillMud | |||||
!DEC$ ATTRIBUTES DLLEXPORT::AnnalusDrillMud | |||||
!DEC$ ATTRIBUTES ALIAS: 'AnnalusDrillMud' :: AnnalusDrillMud | |||||
implicit none | |||||
AnnDrillMud = .true. | |||||
end subroutine AnnalusDrillMud | |||||
subroutine AnnalusCirculateMud | |||||
!DEC$ ATTRIBUTES DLLEXPORT::AnnalusCirculateMud | |||||
!DEC$ ATTRIBUTES ALIAS: 'AnnalusCirculateMud' :: AnnalusCirculateMud | |||||
implicit none | |||||
AnnCirculateMud = .true. | |||||
end subroutine AnnalusCirculateMud | |||||
!type(CFluid) function ActionFluid() !(array) | |||||
! !use CDownHoleVariables | |||||
! !integer, intent(in) :: count | |||||
! !type(CFluid), intent(inout), target :: array !(count) | |||||
! end function | |||||
integer function GetAnnalusFluidsCount() | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetAnnalusFluidsCount | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAnnalusFluidsCount' :: GetAnnalusFluidsCount | |||||
implicit none | |||||
GetAnnalusFluidsCount = size(AnnalusFluids) | |||||
!GetAnnalusFluidsCount = AnnalusFluidsCount | |||||
end function GetAnnalusFluidsCount | |||||
subroutine GetAnnalusFluids(count, array) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetAnnalusFluids | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAnnalusFluids' :: GetAnnalusFluids | |||||
implicit none | |||||
integer :: i | |||||
integer, intent(in) :: count | |||||
type(CFluid), intent(inout), target :: array(count) | |||||
type(CFluid), pointer :: item | |||||
if(.not.allocated(AnnalusFluids)) return | |||||
do i = 1, count | |||||
item => array(i) | |||||
item%StartMd = AnnalusFluids(i)%StartMd | |||||
item%EndMd = AnnalusFluids(i)%EndMd | |||||
item%Density = AnnalusFluids(i)%Density | |||||
item%MudType = AnnalusFluids(i)%MudType | |||||
end do | |||||
end subroutine GetAnnalusFluids | |||||
integer function GetStringFluidsCount() | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetStringFluidsCount | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStringFluidsCount' :: GetStringFluidsCount | |||||
implicit none | |||||
!GetStringFluidsCount = StringFluidsCount | |||||
GetStringFluidsCount = size(StringFluids) | |||||
end function GetStringFluidsCount | |||||
subroutine GetStringFluids(count, array) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetStringFluids | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStringFluids' :: GetStringFluids | |||||
implicit none | |||||
integer :: i | |||||
integer, intent(in) :: count | |||||
type(CFluid), intent(inout), target :: array(count) | |||||
type(CFluid), pointer :: item | |||||
if(.not.allocated(StringFluids)) return | |||||
do i = 1, count | |||||
item => array(i) | |||||
item%StartMd = StringFluids(i)%StartMd | |||||
item%EndMd = StringFluids(i)%EndMd | |||||
item%Density = StringFluids(i)%Density | |||||
item%MudType = StringFluids(i)%MudType | |||||
end do | |||||
end subroutine GetStringFluids | |||||
integer function GetStringCount() | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetStringCount | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStringCount' :: GetStringCount | |||||
implicit none | |||||
GetStringCount = StringCount | |||||
!GetStringCount = 4 | |||||
end function GetStringCount | |||||
subroutine GetString(count, array) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetString | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetString' :: GetString | |||||
implicit none | |||||
integer :: i | |||||
integer, intent(in) :: count | |||||
type(CStringComponent), intent(inout), target :: array(count) | |||||
type(CStringComponent), pointer :: item | |||||
!do i = 1, count | |||||
! item => array(i) | |||||
! item%Length = String(i)%Length | |||||
! item%TopDepth = String(i)%TopDepth | |||||
! item%DownDepth = String(i)%DownDepth | |||||
! item%Od = String(i)%Od | |||||
! item%Id = String(i)%Id | |||||
! item%ComponentType = String(i)%ComponentType | |||||
!end do | |||||
end subroutine GetString | |||||
subroutine GetDownhole() | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetDownhole | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetDownhole' :: GetDownhole | |||||
implicit none | |||||
!BopElement | |||||
if(associated(BopElementsPtr)) call BopElementsPtr(BopElements) | |||||
!Annalus | |||||
if(associated(AnnalusMudCountPtr)) call AnnalusMudCountPtr(AnnalusFluidsCount) | |||||
if(associated(AnnalusMudArrayPtr)) call AnnalusMudArrayPtr(AnnalusFluids) | |||||
!string | |||||
if(associated(StringMudCountPtr)) call StringMudCountPtr(StringFluidsCount) | |||||
if(associated(StringMudArrayPtr)) call StringMudArrayPtr(StringFluids) | |||||
!components | |||||
if(associated(StringComponentCountPtr)) call StringComponentCountPtr(StringCount) | |||||
if(associated(StringComponentArrayPtr)) call StringComponentArrayPtr(String) | |||||
end subroutine GetDownhole | |||||
real(8) function GetDrillPipePressureH() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetDrillPipePressureH | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetDrillPipePressureH' :: GetDrillPipePressureH | |||||
use PressureDisplayVARIABLES | |||||
implicit none | |||||
GetDrillPipePressureH = DrillPipePressure !real(PressureGauges(1), 8) ! | |||||
end function | |||||
real(8) function GetCasingPressureH() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetCasingPressureH | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetCasingPressureH' :: GetCasingPressureH | |||||
use FricPressDropVars | |||||
implicit none | |||||
!if (allocated(FinalFlowEl)) then | |||||
! if(size(FinalFlowEl) > 0) then | |||||
! CasingPressure = real(int(FinalFlowEl(AnnulusLastEl)%EndPress), 8) !CasingPressure | |||||
! endif | |||||
!endif | |||||
GetCasingPressureH = CasingPressure | |||||
end function | |||||
real(8) function GetShoePressure() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetShoePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetShoePressure' :: GetShoePressure | |||||
use PressureDisplayVARIABLES | |||||
implicit none | |||||
GetShoePressure = ShoePressure !real(PressureGauges(5), 8) ! | |||||
end function | |||||
real(8) function GetBottomHolePressure() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetBottomHolePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetBottomHolePressure' :: GetBottomHolePressure | |||||
use PressureDisplayVARIABLES | |||||
implicit none | |||||
GetBottomHolePressure = BottomHolePressure !real(PressureGauges(3), 8) ! | |||||
end function | |||||
real(8) function GetFormationPressure() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetFormationPressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetFormationPressure' :: GetFormationPressure | |||||
implicit none | |||||
GetFormationPressure = FormationPressure | |||||
end function | |||||
real function GetInfluxRate() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetInfluxRate | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetInfluxRate' :: GetInfluxRate | |||||
implicit none | |||||
GetInfluxRate = InfluxRate | |||||
end function | |||||
real function GetKickVolume() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetKickVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetKickVolume' :: GetKickVolume | |||||
implicit none | |||||
!KickVolume = KickVolume + 1 | |||||
GetKickVolume = KickVolume | |||||
end function | |||||
real function GetSecondKickVolume() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetSecondKickVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetSecondKickVolume' :: GetSecondKickVolume | |||||
implicit none | |||||
!SecondKickVolume = SecondKickVolume + 1 | |||||
GetSecondKickVolume = SecondKickVolume | |||||
end function | |||||
real function GetPermeabilityExposedHeight() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPermeabilityExposedHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPermeabilityExposedHeight' :: GetPermeabilityExposedHeight | |||||
implicit none | |||||
GetPermeabilityExposedHeight = PermeabilityExposedHeight | |||||
end function | |||||
real(8) function GetDensityH() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetDensityH | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetDensityH' :: GetDensityH | |||||
implicit none | |||||
GetDensityH = Density | |||||
end function | |||||
real(8) function GetPressureH() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPressureH | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPressureH' :: GetPressureH | |||||
implicit none | |||||
GetPressureH = Pressure | |||||
end function | |||||
real(8) function GetTemperatureH() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTemperatureH | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTemperatureH' :: GetTemperatureH | |||||
implicit none | |||||
GetTemperatureH = Temperature | |||||
end function | |||||
real(8) function GetHeightH() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetHeightH | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetHeightH' :: GetHeightH | |||||
implicit none | |||||
GetHeightH = Height | |||||
end function | |||||
real(8) function GetVolumeH() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetVolumeH | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetVolumeH' :: GetVolumeH | |||||
implicit none | |||||
GetVolumeH = Volume | |||||
end function | |||||
end module CDownHole |
@@ -0,0 +1,105 @@ | |||||
module CDownHoleActions | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
abstract interface | |||||
subroutine ActionFluid(array) | |||||
use CDownHoleTypes | |||||
type(CFluid), allocatable, intent(in), target :: array(:) | |||||
end subroutine | |||||
subroutine ActionComponent(array) | |||||
use CDownHoleTypes | |||||
type(CStringComponent), allocatable, intent(in), target :: array(:) | |||||
end subroutine | |||||
subroutine ActionBopElement(array) | |||||
use CDownHoleTypes | |||||
type(CBopElement), allocatable, intent(in), target :: array(:) | |||||
end subroutine | |||||
end interface | |||||
procedure (ActionInteger), pointer :: AnnalusMudCountPtr | |||||
procedure (ActionFluid), pointer :: AnnalusMudArrayPtr | |||||
procedure (ActionInteger), pointer :: StringMudCountPtr | |||||
procedure (ActionFluid), pointer :: StringMudArrayPtr | |||||
procedure (ActionInteger), pointer :: StringComponentCountPtr | |||||
procedure (ActionComponent), pointer :: StringComponentArrayPtr | |||||
procedure (ActionBopElement), pointer :: BopElementsPtr | |||||
contains | |||||
subroutine SubscribeAnnalusMudCount(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAnnalusMudCount | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeAnnalusMudCount' :: SubscribeAnnalusMudCount | |||||
implicit none | |||||
procedure (ActionInteger) :: a | |||||
AnnalusMudCountPtr => a | |||||
end subroutine | |||||
subroutine SubscribeAnnalusMudArray(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeAnnalusMudArray | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeAnnalusMudArray' :: SubscribeAnnalusMudArray | |||||
implicit none | |||||
procedure (ActionFluid) :: a | |||||
AnnalusMudArrayPtr => a | |||||
end subroutine | |||||
subroutine SubscribeStringMudCount(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeStringMudCount | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeStringMudCount' :: SubscribeStringMudCount | |||||
implicit none | |||||
procedure (ActionInteger) :: a | |||||
StringMudCountPtr => a | |||||
end subroutine | |||||
subroutine SubscribeStringMudArray(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeStringMudArray | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeStringMudArray' :: SubscribeStringMudArray | |||||
implicit none | |||||
procedure (ActionFluid) :: a | |||||
StringMudArrayPtr => a | |||||
end subroutine | |||||
subroutine SubscribeStringComponentCount(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeStringComponentCount | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeStringComponentCount' :: SubscribeStringComponentCount | |||||
implicit none | |||||
procedure (ActionInteger) :: a | |||||
StringComponentCountPtr => a | |||||
end subroutine | |||||
subroutine SubscribeStringComponentArray(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeStringComponentArray | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeStringComponentArray' :: SubscribeStringComponentArray | |||||
implicit none | |||||
procedure (ActionComponent) :: a | |||||
StringComponentArrayPtr => a | |||||
end subroutine | |||||
subroutine SubscribeBopElements(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeBopElements | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeBopElements' :: SubscribeBopElements | |||||
implicit none | |||||
procedure (ActionBopElement) :: a | |||||
BopElementsPtr => a | |||||
end subroutine | |||||
end module CDownHoleActions |
@@ -0,0 +1,52 @@ | |||||
module CDownHoleTypes | |||||
implicit none | |||||
public | |||||
!enums | |||||
enum, bind(c) | |||||
enumerator STRING_BIT !0 | |||||
enumerator STRING_STABILIZER !1 | |||||
enumerator STRING_COLLAR !2 | |||||
enumerator STRING_DRILLPIPE !3 | |||||
enumerator STRING_HEAVYWEIGHT !4 | |||||
end enum | |||||
enum, bind(c) | |||||
enumerator FLUID_NORMAL_MUD !0 | |||||
enumerator FLUID_GAS_KICK !1 | |||||
enumerator FLUID_WATER_KICK !2 | |||||
enumerator FLUID_OIL_KICK !3 | |||||
enumerator FLUID_NO_MUD !4 | |||||
end enum | |||||
! new types | |||||
type, bind(c), public :: CFluid | |||||
real(8) :: StartMd | |||||
real(8) :: EndMd | |||||
real(8) :: Density | |||||
integer :: MudType | |||||
end type CFluid | |||||
type, bind(c), public :: CStringComponents | |||||
real(8) :: Length | |||||
real(8) :: TopDepth | |||||
real(8) :: DownDepth | |||||
real(8) :: Od | |||||
real(8) :: Id | |||||
integer :: ComponentType | |||||
end type CStringComponents | |||||
type, bind(c), public :: CStringComponent | |||||
real(8) :: StartMd | |||||
real(8) :: EndMd | |||||
integer :: ComponentType | |||||
end type CStringComponent | |||||
type, bind(c), public :: CBopElement | |||||
integer :: ElementType | |||||
real :: ElementStart | |||||
real :: ElementEnd | |||||
end type CBopElement | |||||
contains | |||||
end module CDownHoleTypes |
@@ -0,0 +1,292 @@ | |||||
module CDownHoleVariables | |||||
use CDownHoleTypes | |||||
use CStringConfigurationVariables | |||||
use CDownHoleActions | |||||
use CLog4 | |||||
implicit none | |||||
public | |||||
logical :: AnnDrillMud | |||||
logical :: AnnCirculateMud | |||||
integer :: AnnalusFluidsCount = 0 | |||||
integer :: StringFluidsCount = 0 | |||||
type(CFluid), allocatable, target :: AnnalusFluids(:) | |||||
type(CFluid), allocatable :: StringFluids(:) | |||||
integer :: StringCount = 0 | |||||
type(CStringComponent), allocatable :: String(:) | |||||
type(CBopElement), allocatable :: BopElements(:) | |||||
real(8) :: DrillPipePressure | |||||
real(8) :: CasingPressure | |||||
real(8) :: ShoePressure | |||||
real(8) :: BottomHolePressure | |||||
real(8) :: FormationPressure | |||||
real :: InfluxRate | |||||
real :: KickVolume | |||||
real :: SecondKickVolume | |||||
real :: PermeabilityExposedHeight | |||||
real(8) :: Density | |||||
real(8) :: Pressure | |||||
real(8) :: Temperature | |||||
real(8) :: Height | |||||
real(8) :: Volume | |||||
contains | |||||
subroutine SetAnnalusFluids(count, array) | |||||
implicit none | |||||
integer, intent(in) :: count | |||||
integer :: i, offset | |||||
type(CFluid), intent(inout), target :: array(count) | |||||
type(CFluid), pointer :: item | |||||
AnnalusFluidsCount = count | |||||
print*, 'AnnalusFluidsCount = ', count | |||||
if(size(AnnalusFluids) > 0) then | |||||
deallocate(AnnalusFluids) | |||||
end if | |||||
if(count > 0) then | |||||
offset = 0; | |||||
item => array(1) | |||||
if(item%StartMd > 0) then | |||||
AnnalusFluidsCount = AnnalusFluidsCount + 1 | |||||
offset = 1; | |||||
allocate(AnnalusFluids(AnnalusFluidsCount)) | |||||
AnnalusFluids(1)%StartMd = 0 | |||||
AnnalusFluids(1)%EndMd = item%StartMd | |||||
AnnalusFluids(1)%Density = 0 | |||||
AnnalusFluids(1)%MudType = FLUID_NO_MUD | |||||
endif | |||||
!if(associated(AnnalusMudCountPtr)) then | |||||
! call AnnalusMudCountPtr(AnnalusFluidsCount) | |||||
!end if | |||||
if(.not.allocated(AnnalusFluids))allocate(AnnalusFluids(AnnalusFluidsCount)) | |||||
!print*, '============START-AN============' | |||||
if(item%StartMd < 0) AnnalusFluids(1)%StartMd = 0 | |||||
do i = 1, count | |||||
item => array(i) | |||||
AnnalusFluids(i + offset)%StartMd = item%StartMd | |||||
if(i==1) AnnalusFluids(i)%StartMd = 0 | |||||
!print*, 'AnnalusFluids(',i,')%StartMd=', AnnalusFluids(i)%StartMd | |||||
AnnalusFluids(i + offset)%EndMd = item%EndMd | |||||
!print*, 'AnnalusFluids(',i,')%EndMd=', AnnalusFluids(i)%EndMd | |||||
AnnalusFluids(i + offset)%Density = item%Density | |||||
!print*, 'AnnalusFluids(',i,')%Density=', AnnalusFluids(i)%Density | |||||
AnnalusFluids(i + offset)%MudType = item%MudType | |||||
!print*, 'AnnalusFluids(',i,')%MudType=', AnnalusFluids(i)%MudType | |||||
!print*, '----------------------------' | |||||
end do | |||||
!print*, '============END-AN============' | |||||
!if(associated(AnnalusMudArrayPtr)) then | |||||
! !AnnalusFluidsPtr => AnnalusFluids | |||||
! call AnnalusMudArrayPtr(AnnalusFluids) | |||||
!end if | |||||
end if | |||||
end subroutine SetAnnalusFluids | |||||
subroutine SetStringFluids(count, array) | |||||
implicit none | |||||
integer, intent(in) :: count | |||||
integer :: i, offset !, startArr | |||||
type(CFluid), intent(inout), target :: array(count) | |||||
type(CFluid), pointer :: item | |||||
StringFluidsCount = count | |||||
print*, 'StringFluidsCount = ', count | |||||
if(size(StringFluids) > 0) then | |||||
deallocate(StringFluids) | |||||
end if | |||||
!startArr = 1 | |||||
if(count > 0) then | |||||
offset = 0; | |||||
item => array(1) | |||||
! | |||||
!if(item%StartMd <= 0 .and. item%EndMd <= 0) then | |||||
! StringFluidsCount = StringFluidsCount - 1 | |||||
! count = count - 1 | |||||
! offset = offset + 1 | |||||
! startArr = startArr + 1 | |||||
!endif | |||||
! | |||||
!if(count <= 0) return | |||||
if(item%StartMd > 0) then | |||||
StringFluidsCount = StringFluidsCount + 1 | |||||
offset = offset + 1 | |||||
allocate(StringFluids(StringFluidsCount)) | |||||
StringFluids(1)%StartMd = 0 | |||||
StringFluids(1)%EndMd = item%StartMd | |||||
StringFluids(1)%Density = 0 | |||||
StringFluids(1)%MudType = FLUID_NO_MUD | |||||
endif | |||||
!if(associated(StringMudCountPtr)) then | |||||
! call StringMudCountPtr(count) | |||||
!end if | |||||
if(.not.allocated(StringFluids))allocate(StringFluids(StringFluidsCount)) | |||||
!print*, '============START-ST============' | |||||
!print*, 'count=', count | |||||
do i = 1, count | |||||
item => array(i) | |||||
StringFluids(i + offset)%StartMd = item%StartMd | |||||
if(i==1) StringFluids(i)%StartMd = 0 | |||||
!print*, 'StringFluids(i)%StartMd=', StringFluids(i)%StartMd | |||||
StringFluids(i + offset)%EndMd = item%EndMd | |||||
!print*, 'StringFluids(i)%EndMd=', StringFluids(i)%EndMd | |||||
StringFluids(i + offset)%Density = item%Density | |||||
StringFluids(i + offset)%MudType = item%MudType | |||||
!print*, '----------------------------' | |||||
end do | |||||
!!if(item%StartMd < 0) StringFluids(1)%StartMd = 0 | |||||
!!print*, '============END-ST============' | |||||
!if(associated(StringMudArrayPtr)) then | |||||
! call StringMudArrayPtr(StringFluids) | |||||
!end if | |||||
end if | |||||
end subroutine SetStringFluids | |||||
subroutine SetString(count, array) | |||||
use CLog3 | |||||
implicit none | |||||
integer, intent(in) :: count | |||||
integer :: i !, j | |||||
type(CStringComponents), intent(inout), target :: array(count) | |||||
type(CStringComponents), pointer :: item | |||||
StringCount = count | |||||
if(size(String) > 0) then | |||||
deallocate(String) | |||||
end if | |||||
if(count > 0) then | |||||
!if(associated(StringComponentCountPtr)) then | |||||
! call StringComponentCountPtr(count) | |||||
!end if | |||||
allocate(String(count)) | |||||
!j = 0 | |||||
!print*, '============CMP-ST============' | |||||
!call Log_3( '============CMP-ST============') | |||||
!do i = count, 1, -1 | |||||
do i = 1, count | |||||
item => array(i) | |||||
!String(i)%Length = item%Length | |||||
!String(i)%TopDepth = item%TopDepth | |||||
!String(i)%DownDepth = item%DownDepth | |||||
!String(i)%Od = item%Od | |||||
!String(i)%Id = item%Id | |||||
String(i)%ComponentType= item%ComponentType | |||||
!j = j + 1 | |||||
String(i)%StartMd = item%TopDepth | |||||
String(i)%EndMd = item%DownDepth | |||||
String(i)%ComponentType=0 | |||||
!if(item%ComponentType > 4 ) then | |||||
! String(i)%ComponentType=0 | |||||
! String(i)%StartMd = 0 | |||||
!endif | |||||
if(item%ComponentType == 3) String(i)%ComponentType=0 | |||||
if(item%ComponentType == 4) String(i)%ComponentType=1 | |||||
if(item%ComponentType == 2) String(i)%ComponentType=2 | |||||
if(item%ComponentType == 1) String(i)%ComponentType=3 | |||||
!print*, 'item%ComponentType=', item%ComponentType | |||||
!print*, 'String(i)%ComponentType=', String(i)%ComponentType | |||||
!print*, 'String(i)%StartMd=', String(i)%StartMd | |||||
!print*, 'String(i)%EndMd=', String(i)%EndMd | |||||
!print*, '----------------------------' | |||||
!call Log_3( 'item%ComponentType=', item%ComponentType) | |||||
!call Log_3( 'String(i)%ComponentType=', String(i)%ComponentType) | |||||
!call Log_3( 'String(i)%StartMd=', String(i)%StartMd) | |||||
!call Log_3( 'String(i)%EndMd=', String(i)%EndMd) | |||||
!call Log_3( '----------------------------') | |||||
end do | |||||
!!print*, '============CMP-ST============' | |||||
!!call Log_3( '============CMP-ST============') | |||||
!if(associated(StringComponentArrayPtr)) then | |||||
! call StringComponentArrayPtr(String) | |||||
!end if | |||||
end if | |||||
end subroutine SetString | |||||
subroutine SetBopElements(array) | |||||
use CLog4 | |||||
implicit none | |||||
integer, parameter :: count = 4 | |||||
integer :: i = 1 !, j | |||||
type(CBopElement), intent(inout), target :: array(count) | |||||
type(CBopElement), pointer :: item | |||||
if(size(BopElements) > 0) deallocate(BopElements) | |||||
allocate(BopElements(count)) | |||||
do i = 1, count | |||||
item => array(i) | |||||
!call Log_4('item%ElementStart', item%ElementStart) | |||||
!call Log_4('item%ElementEnd', item%ElementEnd) | |||||
!call Log_4('item%ElementType', item%ElementType) | |||||
!call Log_4('=====================================================') | |||||
BopElements(i)%ElementStart = item%ElementStart | |||||
BopElements(i)%ElementEnd = item%ElementEnd | |||||
BopElements(i)%ElementType = item%ElementType | |||||
end do | |||||
!if(associated(BopElementsPtr)) call BopElementsPtr(BopElements) | |||||
end subroutine SetBopElements | |||||
subroutine GetAnnalusFluidInfo(md) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetAnnalusFluidInfo | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAnnalusFluidInfo' :: GetAnnalusFluidInfo | |||||
!use ElementFinderVars | |||||
implicit none | |||||
integer, intent(in) :: md | |||||
call AnnulusPropertyCalculator(md, Density, Pressure, Temperature) | |||||
!ObservationPoint(2)%MeasureDepth = md | |||||
!Density = md + Density - 10 | |||||
!Pressure = md + Pressure - 20 | |||||
!Temperature = md + Temperature - 30 | |||||
!Height = Height * 100.0 | |||||
!Volume = Volume * 200.0 | |||||
! | |||||
!call Log_4('GetAnnalusFluidInfo=', md) | |||||
!call Log_4('A_Height=', Height) | |||||
!call Log_4('A_Volume=', Volume) | |||||
#ifdef deb | |||||
print*, 'GetAnnalusFluidInfo=', md | |||||
#endif | |||||
end subroutine GetAnnalusFluidInfo | |||||
subroutine GetStringFluidInfo(md) | |||||
!DEC$ ATTRIBUTES DLLEXPORT::GetStringFluidInfo | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStringFluidInfo' :: GetStringFluidInfo | |||||
implicit none | |||||
integer, intent(in) :: md | |||||
call StringPropertyCalculator(md, Density, Pressure, Temperature) | |||||
!ObservationPoint(1)%MeasureDepth = md | |||||
!Density = md + Density + 100 | |||||
!Pressure = md + Pressure + 200 | |||||
!Temperature = md + Temperature + 300 | |||||
!Height = Height * 100.0 | |||||
!Volume = Volume * 200.0 | |||||
! | |||||
!call Log_4('GetStringFluidInfo=', md) | |||||
!call Log_4('S_Height=', Height) | |||||
!call Log_4('S_Volume=', Volume) | |||||
#ifdef deb | |||||
print*, 'GetStringFluidInfo=', md | |||||
#endif | |||||
end subroutine GetStringFluidInfo | |||||
end module CDownHoleVariables |
@@ -0,0 +1,250 @@ | |||||
module CBopControlPanel | |||||
use CBopControlPanelVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
subroutine SetAnnularRegulatorSetControl(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAnnularRegulatorSetControl | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAnnularRegulatorSetControl' :: SetAnnularRegulatorSetControl | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AnnularRegulatorSetControl = v | |||||
#ifdef deb | |||||
print*, 'AnnularRegulatorSetControl=', AnnularRegulatorSetControl | |||||
#endif | |||||
end subroutine | |||||
subroutine SetAirMasterValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAirMasterValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAirMasterValve' :: SetAirMasterValve | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AirMasterValve = v | |||||
#ifdef deb | |||||
print*, 'AirMasterValve=', AirMasterValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetByePassValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetByePassValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetByePassValve' :: SetByePassValve | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ByePassValve = v | |||||
#ifdef deb | |||||
print*, 'ByePassValve=', ByePassValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetAnnularValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAnnularValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAnnularValve' :: SetAnnularValve | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
AnnularValve = v | |||||
#ifdef deb | |||||
print*, 'AnnularValve=', AnnularValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetUpperRamsValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetUpperRamsValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetUpperRamsValve' :: SetUpperRamsValve | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
UpperRamsValve = v | |||||
#ifdef deb | |||||
print*, 'UpperRamsValve=', UpperRamsValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMiddleRamsValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMiddleRamsValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMiddleRamsValve' :: SetMiddleRamsValve | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MiddleRamsValve = v | |||||
#ifdef deb | |||||
print*, 'MiddleRamsValve=', MiddleRamsValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetKillLineValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetKillLineValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetKillLineValve' :: SetKillLineValve | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
KillLineValve = v | |||||
#ifdef deb | |||||
print*, 'KillLineValve=', KillLineValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeLineValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeLineValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeLineValve' :: SetChokeLineValve | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ChokeLineValve = v | |||||
#ifdef deb | |||||
print*, 'ChokeLineValve=', ChokeLineValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetLowerRamsValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLowerRamsValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLowerRamsValve' :: SetLowerRamsValve | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
LowerRamsValve = v | |||||
#ifdef deb | |||||
print*, 'LowerRamsValve=', LowerRamsValve | |||||
#endif | |||||
end subroutine | |||||
! Output routines | |||||
real(8) function GetManifoldPressureGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetManifoldPressureGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetManifoldPressureGauge' :: GetManifoldPressureGauge | |||||
implicit none | |||||
GetManifoldPressureGauge = ManifoldPressureGauge | |||||
end function | |||||
real(8) function GetAirSupplyPressureGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetAirSupplyPressureGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAirSupplyPressureGauge' :: GetAirSupplyPressureGauge | |||||
implicit none | |||||
GetAirSupplyPressureGauge = AirSupplyPressureGauge | |||||
end function | |||||
real(8) function GetAccumulatorPressureGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetAccumulatorPressureGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAccumulatorPressureGauge' :: GetAccumulatorPressureGauge | |||||
implicit none | |||||
GetAccumulatorPressureGauge = AccumulatorPressureGauge | |||||
!GetAccumulatorPressureGauge = 2000.0d0 | |||||
end function | |||||
real(8) function GetAnnularPressureGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetAnnularPressureGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAnnularPressureGauge' :: GetAnnularPressureGauge | |||||
implicit none | |||||
GetAnnularPressureGauge = AnnularPressureGauge | |||||
end function | |||||
integer function GetAnnularOpenLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetAnnularOpenLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAnnularOpenLED' :: GetAnnularOpenLED | |||||
implicit none | |||||
GetAnnularOpenLED = AnnularOpenLED | |||||
end function | |||||
integer function GetAnnularCloseLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetAnnularCloseLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAnnularCloseLED' :: GetAnnularCloseLED | |||||
implicit none | |||||
GetAnnularCloseLED = AnnularCloseLED | |||||
end function | |||||
integer function GetUpperRamsOpenLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetUpperRamsOpenLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetUpperRamsOpenLED' :: GetUpperRamsOpenLED | |||||
implicit none | |||||
GetUpperRamsOpenLED = UpperRamsOpenLED | |||||
end function | |||||
integer function GetUpperRamsCloseLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetUpperRamsCloseLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetUpperRamsCloseLED' :: GetUpperRamsCloseLED | |||||
implicit none | |||||
GetUpperRamsCloseLED = UpperRamsCloseLED | |||||
end function | |||||
integer function GetMiddleRamsOpenLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMiddleRamsOpenLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMiddleRamsOpenLED' :: GetMiddleRamsOpenLED | |||||
implicit none | |||||
GetMiddleRamsOpenLED = MiddleRamsOpenLED | |||||
end function | |||||
integer function GetMiddleRamsCloseLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMiddleRamsCloseLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMiddleRamsCloseLED' :: GetMiddleRamsCloseLED | |||||
implicit none | |||||
GetMiddleRamsCloseLED = MiddleRamsCloseLED | |||||
end function | |||||
integer function GetKillLineOpenLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetKillLineOpenLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetKillLineOpenLED' :: GetKillLineOpenLED | |||||
implicit none | |||||
GetKillLineOpenLED = KillLineOpenLED | |||||
end function | |||||
integer function GetKillLineCloseLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetKillLineCloseLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetKillLineCloseLED' :: GetKillLineCloseLED | |||||
implicit none | |||||
GetKillLineCloseLED = KillLineCloseLED | |||||
end function | |||||
integer function GetChokeLineOpenLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetChokeLineOpenLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetChokeLineOpenLED' :: GetChokeLineOpenLED | |||||
implicit none | |||||
GetChokeLineOpenLED = ChokeLineOpenLED | |||||
end function | |||||
integer function GetChokeLineCloseLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetChokeLineCloseLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetChokeLineCloseLED' :: GetChokeLineCloseLED | |||||
implicit none | |||||
GetChokeLineCloseLED = ChokeLineCloseLED | |||||
end function | |||||
integer function GetLowerRamsOpenLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetLowerRamsOpenLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetLowerRamsOpenLED' :: GetLowerRamsOpenLED | |||||
implicit none | |||||
GetLowerRamsOpenLED = LowerRamsOpenLED | |||||
end function | |||||
integer function GetLowerRamsCloseLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetLowerRamsCloseLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetLowerRamsCloseLED' :: GetLowerRamsCloseLED | |||||
implicit none | |||||
GetLowerRamsCloseLED = LowerRamsCloseLED | |||||
end function | |||||
real(8) function GetAnnularStatus() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetAnnularStatus | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAnnularStatus' :: GetAnnularStatus | |||||
implicit none | |||||
GetAnnularStatus = AnnularStatus | |||||
end function | |||||
real(8) function GetUpperRamsStatus() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetUpperRamsStatus | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetUpperRamsStatus' :: GetUpperRamsStatus | |||||
implicit none | |||||
GetUpperRamsStatus = UpperRamsStatus | |||||
end function | |||||
real(8) function GetMiddleRamsStatus() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMiddleRamsStatus | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMiddleRamsStatus' :: GetMiddleRamsStatus | |||||
implicit none | |||||
GetMiddleRamsStatus = MiddleRamsStatus | |||||
end function | |||||
real(8) function GetLowerRamsStatus() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetLowerRamsStatus | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetLowerRamsStatus' :: GetLowerRamsStatus | |||||
implicit none | |||||
GetLowerRamsStatus = LowerRamsStatus | |||||
end function | |||||
end module CBopControlPanel |
@@ -0,0 +1,116 @@ | |||||
module CBopControlPanelVariables | |||||
implicit none | |||||
public | |||||
! Input vars | |||||
real(8) :: AnnularRegulatorSetControl | |||||
real(8) :: AirMasterValve | |||||
real(8) :: ByePassValve | |||||
real(8) :: AnnularValve | |||||
real(8) :: UpperRamsValve | |||||
real(8) :: MiddleRamsValve | |||||
real(8) :: KillLineValve | |||||
real(8) :: ChokeLineValve | |||||
real(8) :: LowerRamsValve | |||||
! Output vars | |||||
real(8) :: ManifoldPressureGauge | |||||
real(8) :: AirSupplyPressureGauge | |||||
real(8) :: AccumulatorPressureGauge | |||||
real(8) :: AnnularPressureGauge | |||||
integer :: AnnularOpenLED | |||||
integer :: AnnularCloseLED | |||||
integer :: UpperRamsOpenLED | |||||
integer :: UpperRamsCloseLED | |||||
integer :: MiddleRamsOpenLED | |||||
integer :: MiddleRamsCloseLED | |||||
integer :: KillLineOpenLED | |||||
integer :: KillLineCloseLED | |||||
integer :: ChokeLineOpenLED | |||||
integer :: ChokeLineCloseLED | |||||
integer :: LowerRamsOpenLED | |||||
integer :: LowerRamsCloseLED | |||||
real(8) :: AnnularStatus | |||||
real(8) :: UpperRamsStatus | |||||
real(8) :: MiddleRamsStatus | |||||
real(8) :: LowerRamsStatus | |||||
contains | |||||
subroutine OpenAnnular() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(52, .true.) | |||||
end subroutine | |||||
subroutine CloseAnnular() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(52, .false.) | |||||
end subroutine | |||||
subroutine OpenUpperRams() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(51, .true.) | |||||
end subroutine | |||||
subroutine CloseUpperRams() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(51, .false.) | |||||
end subroutine | |||||
subroutine OpenMiddleRams() | |||||
use CManifolds | |||||
implicit none | |||||
call ToggleMiddleRams(.true.) | |||||
end subroutine | |||||
subroutine CloseMiddleRams() | |||||
use CManifolds | |||||
implicit none | |||||
call ToggleMiddleRams(.false.) | |||||
end subroutine | |||||
subroutine OpenKillLine() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(46, .true.) | |||||
end subroutine | |||||
subroutine CloseKillLine() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(46, .false.) | |||||
end subroutine | |||||
subroutine OpenChokeLine() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(47, .true.) | |||||
!WRITE (*,*) ' valve 47 true ' | |||||
end subroutine | |||||
subroutine CloseChokeLine() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(47, .false.) | |||||
!WRITE (*,*) ' valve 47 false ' | |||||
end subroutine | |||||
subroutine OpenLowerRams() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(49, .true.) | |||||
!WRITE (*,*) ' valve 49 true ' | |||||
end subroutine | |||||
subroutine CloseLowerRams() | |||||
use CManifolds | |||||
implicit none | |||||
call ChangeValve(49, .false.) | |||||
!WRITE (*,*) ' valve 49 false ' | |||||
end subroutine | |||||
end module CBopControlPanelVariables |
@@ -0,0 +1,161 @@ | |||||
module CChokeControlPanel | |||||
use CChokeControlPanelVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
subroutine SetChokePanelPumpSelectorSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokePanelPumpSelectorSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokePanelPumpSelectorSwitch' :: SetChokePanelPumpSelectorSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
ChokePanelPumpSelectorSwitch = v | |||||
#ifdef deb | |||||
print*, 'ChokePanelPumpSelectorSwitch=', ChokePanelPumpSelectorSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokePanelStrokeResetSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokePanelStrokeResetSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokePanelStrokeResetSwitch' :: SetChokePanelStrokeResetSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokePanelStrokeResetSwitch = v | |||||
#ifdef deb | |||||
print*, 'ChokePanelStrokeResetSwitch=', ChokePanelStrokeResetSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeSelectorSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeSelectorSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeSelectorSwitch' :: SetChokeSelectorSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeSelectorSwitch = v | |||||
#ifdef deb | |||||
print*, 'ChokeSelectorSwitch=', ChokeSelectorSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeRateControlKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeRateControlKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeRateControlKnob' :: SetChokeRateControlKnob | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!character(8) :: date | |||||
!character(10) :: time | |||||
!character(5) :: zone | |||||
!integer,dimension(8) :: values | |||||
ChokeRateControlKnob = v | |||||
#ifdef deb | |||||
!call date_and_time(date,time,zone,values) | |||||
!!print '(a,2x,a,2x,a)', date, time, zone | |||||
!print '(8i5)', values | |||||
print*, 'ChokeRateControlKnob=', ChokeRateControlKnob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeControlLever(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeControlLever | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeControlLever' :: SetChokeControlLever | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
ChokeControlLever = v | |||||
#ifdef deb | |||||
print*, 'ChokeControlLever=', ChokeControlLever | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokePanelRigAirSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokePanelRigAirSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokePanelRigAirSwitch' :: SetChokePanelRigAirSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokePanelRigAirSwitch = v | |||||
#ifdef deb | |||||
print*, 'ChokePanelRigAirSwitch=', ChokePanelRigAirSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetEnableAutoChoke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetEnableAutoChoke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetEnableAutoChoke' :: SetEnableAutoChoke | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
EnableAutoChoke = v | |||||
#ifdef deb | |||||
print*, 'EnableAutoChoke=', EnableAutoChoke | |||||
#endif | |||||
end subroutine | |||||
! Output routines | |||||
real(8) function GetStandPipePressure() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetStandPipePressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStandPipePressure' :: GetStandPipePressure | |||||
implicit none | |||||
GetStandPipePressure = StandPipePressure | |||||
end function | |||||
real(8) function GetCasingPressure() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetCasingPressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetCasingPressure' :: GetCasingPressure | |||||
implicit none | |||||
GetCasingPressure = CasingPressure | |||||
end function | |||||
real(8) function GetChokePosition() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetChokePosition | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetChokePosition' :: GetChokePosition | |||||
implicit none | |||||
GetChokePosition = ChokePosition | |||||
end function | |||||
real(8) function GetChokePanelSPMCounter() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetChokePanelSPMCounter | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetChokePanelSPMCounter' :: GetChokePanelSPMCounter | |||||
implicit none | |||||
!GetChokePanelSPMCounter = 0 | |||||
GetChokePanelSPMCounter = ChokePanelSPMCounter | |||||
end function | |||||
real(8) function GetChokePanelTotalStrokeCounter() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetChokePanelTotalStrokeCounter | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetChokePanelTotalStrokeCounter' :: GetChokePanelTotalStrokeCounter | |||||
implicit none | |||||
!GetChokePanelTotalStrokeCounter = 0 | |||||
GetChokePanelTotalStrokeCounter = ChokePanelTotalStrokeCounter | |||||
end function | |||||
integer function GetChoke1LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetChoke1LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetChoke1LED' :: GetChoke1LED | |||||
implicit none | |||||
GetChoke1LED = Choke1LED | |||||
end function | |||||
integer function GetChoke2LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetChoke2LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetChoke2LED' :: GetChoke2LED | |||||
implicit none | |||||
GetChoke2LED = Choke2LED | |||||
end function | |||||
end module CChokeControlPanel |
@@ -0,0 +1,25 @@ | |||||
module CChokeControlPanelVariables | |||||
implicit none | |||||
public | |||||
! Input vars | |||||
integer :: ChokePanelPumpSelectorSwitch | |||||
logical :: ChokePanelStrokeResetSwitch | |||||
logical :: ChokeSelectorSwitch | |||||
real(8) :: ChokeRateControlKnob | |||||
real(8) :: ChokeControlLever | |||||
logical :: ChokePanelRigAirSwitch | |||||
logical :: EnableAutoChoke | |||||
! Output vars | |||||
real(8) :: StandPipePressure | |||||
real(8) :: CasingPressure | |||||
real(8) :: ChokePosition | |||||
real(8) :: ChokePanelSPMCounter | |||||
real(8) :: ChokePanelTotalStrokeCounter | |||||
integer :: Choke1LED | |||||
integer :: Choke2LED | |||||
contains | |||||
end module CChokeControlPanelVariables |
@@ -0,0 +1,212 @@ | |||||
module CChokeManifold | |||||
use CChokeManifoldVariables | |||||
use CLog2 | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
subroutine SetChokeManifoldValve1(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve1' :: SetChokeManifoldValve1 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve1 = v | |||||
call ChangeValve(61, v) | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve1=', ChokeManifoldValve1 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve2(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve2' :: SetChokeManifoldValve2 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve2 = v | |||||
call ChangeValve(64, v) | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve2=', ChokeManifoldValve2 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetLeftManualChoke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLeftManualChoke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLeftManualChoke' :: SetLeftManualChoke | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!LeftManualChoke = abs(v-100) | |||||
LeftManualChoke = v | |||||
if(LeftManChokeOnProblem) then | |||||
call ChangeValve(32, .true.) | |||||
else | |||||
if(LeftManualChoke > 99.9) then | |||||
!call Log_2( 'valve 32 is closed=', LeftManualChoke) | |||||
call ChangeValve(32, .false.) | |||||
else | |||||
!call Log_2( 'valve 32 is open=', LeftManualChoke) | |||||
call ChangeValve(32, .true.) | |||||
endif | |||||
endif | |||||
#ifdef deb | |||||
!print*, 'LeftManualChoke=', LeftManualChoke | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve4(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve4 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve4' :: SetChokeManifoldValve4 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve4 = v | |||||
call ChangeValve(62, v) | |||||
!WRITE (*,*) ' valve 62 ', v | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve4=', ChokeManifoldValve4 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve5(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve5 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve5' :: SetChokeManifoldValve5 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve5 = v | |||||
call ChangeValve(63, v) | |||||
!WRITE (*,*) ' valve 63 ', v | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve5=', ChokeManifoldValve5 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetRightManualChoke(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRightManualChoke | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRightManualChoke' :: SetRightManualChoke | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!RightManualChoke = abs(v -100) | |||||
RightManualChoke = v | |||||
if(RightManChokeOnProblem) then | |||||
call ChangeValve(35, .true.) | |||||
else | |||||
if(RightManualChoke > 99.9) then | |||||
!call Log_2( 'valve 35 is closed=', RightManualChoke) | |||||
call ChangeValve(35, .false.) | |||||
else | |||||
!call Log_2( 'valve 35 is open=', RightManualChoke) | |||||
call ChangeValve(35, .true.) | |||||
endif | |||||
endif | |||||
#ifdef deb | |||||
!print*, 'RightManualChoke=', RightManualChoke | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve7(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve7 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve7' :: SetChokeManifoldValve7 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve7 = v | |||||
call ChangeValve(27, v) | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve7=', ChokeManifoldValve7 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve8(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve8 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve8' :: SetChokeManifoldValve8 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve8 = v | |||||
call ChangeValve(28, v) | |||||
!WRITE (*,*) ' valve 28 ', v | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve8=', ChokeManifoldValve8 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve9(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve9 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve9' :: SetChokeManifoldValve9 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve9 = v | |||||
call ChangeValve(29, v) | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve9=', ChokeManifoldValve9 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve10(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve10 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve10' :: SetChokeManifoldValve10 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve10 = v | |||||
call ChangeValve(30, v) | |||||
!WRITE (*,*) ' valve 30 ', v | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve10=', ChokeManifoldValve10 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve11(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve11 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve11' :: SetChokeManifoldValve11 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve11 = v | |||||
call ChangeValve(31, v) | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve11=', ChokeManifoldValve11 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve12(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve12 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve12' :: SetChokeManifoldValve12 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve12 = v | |||||
call ChangeValve(25, v) | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve12=', ChokeManifoldValve12 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetChokeManifoldValve13(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetChokeManifoldValve13 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetChokeManifoldValve13' :: SetChokeManifoldValve13 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ChokeManifoldValve13 = v | |||||
call ChangeValve(26, v) | |||||
!WRITE (*,*) ' valve 26 ', v | |||||
#ifdef deb | |||||
!print*, 'ChokeManifoldValve13=', ChokeManifoldValve13 | |||||
#endif | |||||
end subroutine | |||||
! Output routines | |||||
integer function GetHydraulicChock1() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetHydraulicChock1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetHydraulicChock1' :: GetHydraulicChock1 | |||||
implicit none | |||||
GetHydraulicChock1 = HydraulicChock1 | |||||
!GetHydraulicChock1 = 23 | |||||
end function | |||||
integer function GetHydraulicChock2() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetHydraulicChock2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetHydraulicChock2' :: GetHydraulicChock2 | |||||
implicit none | |||||
GetHydraulicChock2 = HydraulicChock2 | |||||
!GetHydraulicChock2 = 54 | |||||
end function | |||||
end module CChokeManifold |
@@ -0,0 +1,65 @@ | |||||
module CChokeManifoldVariables | |||||
use CManifolds | |||||
implicit none | |||||
public | |||||
! Input vars | |||||
logical :: ChokeManifoldValve1 | |||||
logical :: ChokeManifoldValve2 | |||||
real(8) :: LeftManualChoke | |||||
logical :: ChokeManifoldValve4 | |||||
logical :: ChokeManifoldValve5 | |||||
real(8) :: RightManualChoke | |||||
logical :: ChokeManifoldValve7 | |||||
logical :: ChokeManifoldValve8 | |||||
logical :: ChokeManifoldValve9 | |||||
logical :: ChokeManifoldValve10 | |||||
logical :: ChokeManifoldValve11 | |||||
logical :: ChokeManifoldValve12 | |||||
logical :: ChokeManifoldValve13 | |||||
! Output vars | |||||
integer :: HydraulicChock1 | |||||
integer :: HydraulicChock2 | |||||
! Control vars | |||||
logical :: HyChock1OnProblem = .false. | |||||
logical :: HyChock2OnProblem = .false. | |||||
logical :: LeftManChokeOnProblem = .false. | |||||
logical :: RightManChokeOnProblem = .false. | |||||
contains | |||||
subroutine SetHydraulicChock1(v) | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
HydraulicChock1 = v | |||||
if(HyChock1OnProblem) then | |||||
call ChangeValve(33, .true.) | |||||
else | |||||
if(v == 100) then | |||||
if(Valve(33)%Status) call ChangeValve(33, .false.) | |||||
else | |||||
if(.not.Valve(33)%Status) call ChangeValve(33, .true.) | |||||
endif | |||||
endif | |||||
!WRITE (*,*) ' valve 33 ', Valve(33)%Status, ' arg ', v | |||||
end subroutine | |||||
subroutine SetHydraulicChock2(v) | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
HydraulicChock2 = v | |||||
if(HyChock2OnProblem) then | |||||
call ChangeValve(34, .true.) | |||||
else | |||||
if(v==100) then | |||||
if(Valve(34)%Status) call ChangeValve(34, .false.) | |||||
else | |||||
if(.not.Valve(34)%Status) call ChangeValve(34, .true.) | |||||
endif | |||||
endif | |||||
!WRITE (*,*) ' valve 34 ', Valve(34)%Status, ' arg ', v | |||||
end subroutine | |||||
endmodule CChokeManifoldVariables |
@@ -0,0 +1,798 @@ | |||||
module CDataDisplayConsole | |||||
use CDataDisplayConsoleVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
!Portable | |||||
subroutine SetTripAlarmLow(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripAlarmLow | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripAlarmLow' :: SetTripAlarmLow | |||||
!use MudSystemVARIABLES, only: TripTank_MinVol_Allowded | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TripAlarmLow = v | |||||
!TripTank_MinVol_Allowded = v | |||||
#ifdef deb | |||||
print*, 'TripAlarmLow=', TripAlarmLow | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTripAlarmHigh(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripAlarmHigh | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripAlarmHigh' :: SetTripAlarmHigh | |||||
!use MudSystemVARIABLES, only: TripTank_MaxVol_Allowded | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TripAlarmHigh = v | |||||
!TripTank_MaxVol_Allowded = v | |||||
#ifdef deb | |||||
print*, 'TripAlarmHigh=', TripAlarmHigh | |||||
#endif | |||||
end subroutine | |||||
subroutine SetRetFlowAlarmLow(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRetFlowAlarmLow | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRetFlowAlarmLow' :: SetRetFlowAlarmLow | |||||
!use MudSystemVARIABLES, only: MFFI_MinPercent_Allowded | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
RetFlowAlarmLow = v | |||||
!MFFI_MinPercent_Allowded = v | |||||
#ifdef deb | |||||
print*, 'RetFlowAlarmLow=', RetFlowAlarmLow | |||||
#endif | |||||
end subroutine | |||||
subroutine SetRetFlowAlarmHigh(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRetFlowAlarmHigh | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRetFlowAlarmHigh' :: SetRetFlowAlarmHigh | |||||
!use MudSystemVARIABLES, only: MFFI_MaxPercent_Allowded | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
RetFlowAlarmHigh = v | |||||
!MFFI_MaxPercent_Allowded = v | |||||
#ifdef deb | |||||
print*, 'RetFlowAlarmHigh=', RetFlowAlarmHigh | |||||
#endif | |||||
end subroutine | |||||
subroutine SetPitAlarmLow(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetPitAlarmLow | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetPitAlarmLow' :: SetPitAlarmLow | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
PitAlarmLow = v | |||||
!call Log_4('PitAlarmLow=', PitAlarmLow) | |||||
#ifdef deb | |||||
print*, 'PitAlarmLow=', PitAlarmLow | |||||
#endif | |||||
end subroutine | |||||
subroutine SetPitAlarmHigh(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetPitAlarmHigh | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetPitAlarmHigh' :: SetPitAlarmHigh | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
PitAlarmHigh = v | |||||
!call Log_4('PitAlarmHigh=', PitAlarmHigh) | |||||
#ifdef deb | |||||
print*, 'PitAlarmHigh=', PitAlarmHigh | |||||
#endif | |||||
end subroutine | |||||
! Input routines | |||||
subroutine SetTripTankSetAlarmLow(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripTankSetAlarmLow | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripTankSetAlarmLow' :: SetTripTankSetAlarmLow | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TripTankSetAlarmLow = v | |||||
#ifdef deb | |||||
print*, 'TripTankSetAlarmLow=', TripTankSetAlarmLow | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTripTankSetAlarmHigh(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripTankSetAlarmHigh | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripTankSetAlarmHigh' :: SetTripTankSetAlarmHigh | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TripTankSetAlarmHigh = v | |||||
#ifdef deb | |||||
print*, 'TripTankSetAlarmHigh=', TripTankSetAlarmHigh | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTripTankSetAlarmSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripTankSetAlarmSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripTankSetAlarmSwitch' :: SetTripTankSetAlarmSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
TripTankSetAlarmSwitch = v | |||||
#ifdef deb | |||||
print*, 'TripTankSetAlarmSwitch=', TripTankSetAlarmSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTripTankPowerSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripTankPowerSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripTankPowerSwitch' :: SetTripTankPowerSwitch | |||||
use CTanksVariables, only: Set_ManualPumpPower | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
TripTankPowerSwitch = v | |||||
if(TripTankPowerSwitch) call Set_ManualPumpPower(TripTankPumpSwitch) | |||||
#ifdef deb | |||||
print*, 'TripTankPowerSwitch=', TripTankPowerSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTripTankPumpSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripTankPumpSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripTankPumpSwitch' :: SetTripTankPumpSwitch | |||||
use CTanksVariables, only: Set_ManualPumpPower | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
TripTankPumpSwitch = v | |||||
if(TripTankPowerSwitch) call Set_ManualPumpPower(TripTankPumpSwitch) | |||||
#ifdef deb | |||||
print*, 'TripTankPumpSwitch=', TripTankPumpSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTripTankHornSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripTankHornSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripTankHornSwitch' :: SetTripTankHornSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
TripTankHornSwitch = v | |||||
#ifdef deb | |||||
print*, 'TripTankHornSwitch=', TripTankHornSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetAcidGasDetectionHornSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAcidGasDetectionHornSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAcidGasDetectionHornSwitch' :: SetAcidGasDetectionHornSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
AcidGasDetectionHornSwitch = v | |||||
#ifdef deb | |||||
print*, 'AcidGasDetectionHornSwitch=', AcidGasDetectionHornSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTotalStrokeCounterResetSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTotalStrokeCounterResetSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTotalStrokeCounterResetSwitch' :: SetTotalStrokeCounterResetSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
TotalStrokeCounterResetSwitch = v | |||||
#ifdef deb | |||||
print*, 'TotalStrokeCounterResetSwitch=', TotalStrokeCounterResetSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDrillingTrippingSelectorSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDrillingTrippingSelectorSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDrillingTrippingSelectorSwitch' :: SetDrillingTrippingSelectorSwitch | |||||
use CCommonVariables | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
DrillingTrippingSelectorSwitch = v | |||||
DrillWatchOperationMode = v | |||||
#ifdef deb | |||||
print*, 'DrillingTrippingSelectorSwitch=', DrillingTrippingSelectorSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMVTSetAlarmLowKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMVTSetAlarmLowKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMVTSetAlarmLowKnob' :: SetMVTSetAlarmLowKnob | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MVTSetAlarmLowKnob = v | |||||
#ifdef deb | |||||
print*, 'MVTSetAlarmLowKnob=', MVTSetAlarmLowKnob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMVTSetAlarmHighKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMVTSetAlarmHighKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMVTSetAlarmHighKnob' :: SetMVTSetAlarmHighKnob | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MVTSetAlarmHighKnob = v | |||||
#ifdef deb | |||||
print*, 'MVTSetAlarmHighKnob=', MVTSetAlarmHighKnob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMVTSetAlarmSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMVTSetAlarmSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMVTSetAlarmSwitch' :: SetMVTSetAlarmSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
MVTSetAlarmSwitch = v | |||||
#ifdef deb | |||||
print*, 'MVTSetAlarmSwitch=', MVTSetAlarmSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudTank1Switch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudTank1Switch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudTank1Switch' :: SetMudTank1Switch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MudTank1Switch = v | |||||
#ifdef deb | |||||
print*, 'MudTank1Switch=', MudTank1Switch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudTank2Switch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudTank2Switch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudTank2Switch' :: SetMudTank2Switch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MudTank2Switch = v | |||||
#ifdef deb | |||||
print*, 'MudTank2Switch=', MudTank2Switch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudTank3Switch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudTank3Switch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudTank3Switch' :: SetMudTank3Switch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MudTank3Switch = v | |||||
#ifdef deb | |||||
print*, 'MudTank3Switch=', MudTank3Switch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMudTank4Switch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMudTank4Switch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMudTank4Switch' :: SetMudTank4Switch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MudTank4Switch = v | |||||
#ifdef deb | |||||
print*, 'MudTank4Switch=', MudTank4Switch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMVTFineKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMVTFineKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMVTFineKnob' :: SetMVTFineKnob | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MVTFineKnob = v | |||||
#ifdef deb | |||||
print*, 'MVTFineKnob=', MVTFineKnob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMVTCoarseKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMVTCoarseKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMVTCoarseKnob' :: SetMVTCoarseKnob | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MVTCoarseKnob = v | |||||
#ifdef deb | |||||
print*, 'MVTCoarseKnob=', MVTCoarseKnob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMVTHornSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMVTHornSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMVTHornSwitch' :: SetMVTHornSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MVTHornSwitch = v | |||||
#ifdef deb | |||||
print*, 'MVTHornSwitch=', MVTHornSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMVTDeviationTripSelectionSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMVTDeviationTripSelectionSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMVTDeviationTripSelectionSwitch' :: SetMVTDeviationTripSelectionSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MVTDeviationTripSelectionSwitch = v | |||||
#ifdef deb | |||||
print*, 'MVTDeviationTripSelectionSwitch=', MVTDeviationTripSelectionSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMVTPowerSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMVTPowerSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMVTPowerSwitch' :: SetMVTPowerSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MVTPowerSwitch = v | |||||
#ifdef deb | |||||
print*, 'MVTPowerSwitch=', MVTPowerSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFIResetTotalStrokes(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFIResetTotalStrokes | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFIResetTotalStrokes' :: SetMFFIResetTotalStrokes | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MFFIResetTotalStrokes = v | |||||
#ifdef deb | |||||
print*, 'MFFIResetTotalStrokes=', MFFIResetTotalStrokes | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFIResetFillCounter(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFIResetFillCounter | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFIResetFillCounter' :: SetMFFIResetFillCounter | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MFFIResetFillCounter = v | |||||
#ifdef deb | |||||
print*, 'MFFIResetFillCounter=', MFFIResetFillCounter | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFIPumpSelectorSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFIPumpSelectorSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFIPumpSelectorSwitch' :: SetMFFIPumpSelectorSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
MFFIPumpSelectorSwitch = v | |||||
#ifdef deb | |||||
print*, 'MFFIPumpSelectorSwitch=', MFFIPumpSelectorSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFIFillSPMSelectorSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFIFillSPMSelectorSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFIFillSPMSelectorSwitch' :: SetMFFIFillSPMSelectorSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MFFIFillSPMSelectorSwitch = v | |||||
#ifdef deb | |||||
print*, 'MFFIFillSPMSelectorSwitch=', MFFIFillSPMSelectorSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFISetAlarmLowKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFISetAlarmLowKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFISetAlarmLowKnob' :: SetMFFISetAlarmLowKnob | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MFFISetAlarmLowKnob = v | |||||
#ifdef deb | |||||
print*, 'MFFISetAlarmLowKnob=', MFFISetAlarmLowKnob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFISetAlarmHighKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFISetAlarmHighKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFISetAlarmHighKnob' :: SetMFFISetAlarmHighKnob | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
MFFISetAlarmHighKnob = v | |||||
#ifdef deb | |||||
print*, 'MFFISetAlarmHighKnob=', MFFISetAlarmHighKnob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFISetAlarmSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFISetAlarmSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFISetAlarmSwitch' :: SetMFFISetAlarmSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
MFFISetAlarmSwitch = v | |||||
#ifdef deb | |||||
print*, 'MFFISetAlarmSwitch=', MFFISetAlarmSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFIPowerSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFIPowerSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFIPowerSwitch' :: SetMFFIPowerSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MFFIPowerSwitch = v | |||||
#ifdef deb | |||||
print*, 'MFFIPowerSwitch=', MFFIPowerSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMFFIHornSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMFFIHornSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMFFIHornSwitch' :: SetMFFIHornSwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
MFFIHornSwitch = v | |||||
#ifdef deb | |||||
print*, 'MFFIHornSwitch=', MFFIHornSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTotalWellDepth(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTotalWellDepth | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTotalWellDepth' :: SetTotalWellDepth | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
call Set_TotalDepth(v) | |||||
#ifdef deb | |||||
print*, 'TotalWellDepth=', v | |||||
#endif | |||||
end subroutine | |||||
subroutine SetResetWob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetResetWob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetResetWob' :: SetResetWob | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ResetWob = v | |||||
#ifdef deb | |||||
print*, 'ResetWob=', ResetWob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetClutch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetClutch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetClutch' :: SetClutch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Clutch = v | |||||
#ifdef deb | |||||
print*, 'Clutch=', Clutch | |||||
#endif | |||||
end subroutine | |||||
! Output routines | |||||
real(8) function GetWOBPointer() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetWOBPointer | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetWOBPointer' :: GetWOBPointer | |||||
implicit none | |||||
GetWOBPointer = WOBPointer | |||||
end function | |||||
real(8) function GetHookLoadPointer() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetHookLoadPointer | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetHookLoadPointer' :: GetHookLoadPointer | |||||
implicit none | |||||
GetHookLoadPointer = HookLoadPointer | |||||
end function | |||||
real(8) function GetTripTankGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTripTankGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTripTankGauge' :: GetTripTankGauge | |||||
implicit none | |||||
GetTripTankGauge = TripTankGauge / 42.0 | |||||
!GetTripTankGauge = 23 | |||||
end function | |||||
integer function GetTripTankAlarmLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTripTankAlarmLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTripTankAlarmLED' :: GetTripTankAlarmLED | |||||
implicit none | |||||
GetTripTankAlarmLED = TripTankAlarmLED | |||||
!GetTripTankAlarmLED = 1 | |||||
end function | |||||
integer function GetTripTankPumpLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTripTankPumpLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTripTankPumpLED' :: GetTripTankPumpLED | |||||
implicit none | |||||
GetTripTankPumpLED = TripTankPumpLED | |||||
end function | |||||
real(8) function GetStandPipePressureGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetStandPipePressureGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStandPipePressureGauge' :: GetStandPipePressureGauge | |||||
implicit none | |||||
GetStandPipePressureGauge = StandPipePressureGauge | |||||
end function | |||||
real(8) function GetCasingPressureGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetCasingPressureGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetCasingPressureGauge' :: GetCasingPressureGauge | |||||
implicit none | |||||
GetCasingPressureGauge = CasingPressureGauge | |||||
end function | |||||
real(8) function GetMP1SPMGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMP1SPMGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMP1SPMGauge' :: GetMP1SPMGauge | |||||
implicit none | |||||
GetMP1SPMGauge = MP1SPMGauge | |||||
end function | |||||
real(8) function GetMP2SPMGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMP2SPMGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMP2SPMGauge' :: GetMP2SPMGauge | |||||
implicit none | |||||
GetMP2SPMGauge = MP2SPMGauge | |||||
end function | |||||
real(8) function GetReturnLineTempGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetReturnLineTempGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetReturnLineTempGauge' :: GetReturnLineTempGauge | |||||
implicit none | |||||
GetReturnLineTempGauge = ReturnLineTempGauge | |||||
end function | |||||
real(8) function GetRotaryTorqueGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetRotaryTorqueGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetRotaryTorqueGauge' :: GetRotaryTorqueGauge | |||||
implicit none | |||||
GetRotaryTorqueGauge = RotaryTorqueGauge | |||||
end function | |||||
real(8) function GetRotaryRPMGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetRotaryRPMGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetRotaryRPMGauge' :: GetRotaryRPMGauge | |||||
implicit none | |||||
GetRotaryRPMGauge = RotaryRPMGauge | |||||
end function | |||||
integer function GetAcidGasDetectionLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetAcidGasDetectionLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAcidGasDetectionLED' :: GetAcidGasDetectionLED | |||||
implicit none | |||||
GetAcidGasDetectionLED = AcidGasDetectionLED | |||||
end function | |||||
real(8) function GetTotalStrokeCounter() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTotalStrokeCounter | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTotalStrokeCounter' :: GetTotalStrokeCounter | |||||
implicit none | |||||
GetTotalStrokeCounter = TotalStrokeCounter | |||||
!GetTotalStrokeCounter = 456.9 | |||||
end function | |||||
real(8) function GetPitGainLossGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPitGainLossGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPitGainLossGauge' :: GetPitGainLossGauge | |||||
implicit none | |||||
GetPitGainLossGauge = PitGainLossGauge | |||||
!GetPitGainLossGauge = 44 | |||||
end function | |||||
real(8) function GetMudTanksVolumeGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMudTanksVolumeGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMudTanksVolumeGauge' :: GetMudTanksVolumeGauge | |||||
implicit none | |||||
GetMudTanksVolumeGauge = MudTanksVolumeGauge / 42.0 | |||||
end function | |||||
integer function GetMVTAlarmLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMVTAlarmLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMVTAlarmLED' :: GetMVTAlarmLED | |||||
implicit none | |||||
GetMVTAlarmLED = MVTAlarmLED | |||||
!GetMVTAlarmLED = 1 | |||||
end function | |||||
real(8) function GetReturnMudFlowGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetReturnMudFlowGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetReturnMudFlowGauge' :: GetReturnMudFlowGauge | |||||
implicit none | |||||
GetReturnMudFlowGauge = ReturnMudFlowGauge | |||||
!GetReturnMudFlowGauge = 12 | |||||
end function | |||||
real(8) function GetFillStrokeCounter() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetFillStrokeCounter | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetFillStrokeCounter' :: GetFillStrokeCounter | |||||
implicit none | |||||
GetFillStrokeCounter = FillStrokeCounter | |||||
end function | |||||
real(8) function GetMFFITotalStrokeCounter() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMFFITotalStrokeCounter | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMFFITotalStrokeCounter' :: GetMFFITotalStrokeCounter | |||||
implicit none | |||||
GetMFFITotalStrokeCounter = MFFITotalStrokeCounter | |||||
end function | |||||
integer function GetMFFIAlarmLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMFFIAlarmLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMFFIAlarmLED' :: GetMFFIAlarmLED | |||||
implicit none | |||||
GetMFFIAlarmLED = MFFIAlarmLED | |||||
!GetMFFIAlarmLED = 1 | |||||
end function | |||||
integer function GetMFFIPumpLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMFFIPumpLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMFFIPumpLED' :: GetMFFIPumpLED | |||||
implicit none | |||||
GetMFFIPumpLED = MFFIPumpLED | |||||
end function | |||||
real(8) function GetTotalWellDepth() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTotalWellDepth | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTotalWellDepth' :: GetTotalWellDepth | |||||
implicit none | |||||
GetTotalWellDepth = TotalWellDepth | |||||
end function | |||||
real(8) function GetBitDepth() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetBitDepth | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetBitDepth' :: GetBitDepth | |||||
implicit none | |||||
GetBitDepth = BitDepth | |||||
end function | |||||
real(8) function GetHookLoad() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetHookLoad | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetHookLoad' :: GetHookLoad | |||||
implicit none | |||||
GetHookLoad = HookLoad | |||||
end function | |||||
real(8) function GetStandPipePressure2() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetStandPipePressure2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStandPipePressure2' :: GetStandPipePressure2 | |||||
implicit none | |||||
GetStandPipePressure2 = StandPipePressure | |||||
end function | |||||
real(8) function GetCasingPressure2() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetCasingPressure2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetCasingPressure2' :: GetCasingPressure2 | |||||
implicit none | |||||
GetCasingPressure2 = CasingPressure | |||||
end function | |||||
real(8) function GetMP1SPM() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMP1SPM | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMP1SPM' :: GetMP1SPM | |||||
implicit none | |||||
GetMP1SPM = MP1SPM | |||||
end function | |||||
real(8) function GetMP2SPM() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMP2SPM | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMP2SPM' :: GetMP2SPM | |||||
implicit none | |||||
GetMP2SPM = MP2SPM | |||||
end function | |||||
real(8) function GetRTTorque() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetRTTorque | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetRTTorque' :: GetRTTorque | |||||
implicit none | |||||
GetRTTorque = RTTorque | |||||
end function | |||||
real(8) function GetRTRPM() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetRTRPM | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetRTRPM' :: GetRTRPM | |||||
implicit none | |||||
GetRTRPM = RTRPM | |||||
end function | |||||
real(8) function GetWOP() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetWOP | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetWOP' :: GetWOP | |||||
implicit none | |||||
GetWOP = WOP | |||||
end function | |||||
real(8) function GetROP() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetROP | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetROP' :: GetROP | |||||
implicit none | |||||
GetROP = ROP | |||||
end function | |||||
real(8) function GetMudWeightIn() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMudWeightIn | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMudWeightIn' :: GetMudWeightIn | |||||
implicit none | |||||
GetMudWeightIn = MudWeightIn | |||||
end function | |||||
real(8) function GetMudWeightOut() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMudWeightOut | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMudWeightOut' :: GetMudWeightOut | |||||
implicit none | |||||
GetMudWeightOut = MudWeightOut | |||||
end function | |||||
logical function GetBuzzer1() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetBuzzer1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetBuzzer1' :: GetBuzzer1 | |||||
implicit none | |||||
GetBuzzer1 = Buzzer1 | |||||
!GetBuzzer1 = .true. | |||||
end function | |||||
logical function GetBuzzer2() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetBuzzer2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetBuzzer2' :: GetBuzzer2 | |||||
implicit none | |||||
GetBuzzer2 = Buzzer2 | |||||
!GetBuzzer2 = .true. | |||||
end function | |||||
logical function GetBuzzer3() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetBuzzer3 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetBuzzer3' :: GetBuzzer3 | |||||
implicit none | |||||
GetBuzzer3 = Buzzer3 | |||||
!GetBuzzer3 = .true. | |||||
end function | |||||
logical function GetBuzzer4() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetBuzzer4 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetBuzzer4' :: GetBuzzer4 | |||||
implicit none | |||||
GetBuzzer4 = Buzzer4 | |||||
!GetBuzzer4 = .true. | |||||
end function | |||||
!portable | |||||
real(8) function GetPortWeightOnBit() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPortWeightOnBit | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPortWeightOnBit' :: GetPortWeightOnBit | |||||
implicit none | |||||
GetPortWeightOnBit = PortWeightOnBit | |||||
end function | |||||
real(8) function GetPortHookLoad() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPortHookLoad | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPortHookLoad' :: GetPortHookLoad | |||||
implicit none | |||||
GetPortHookLoad = PortHookLoad | |||||
end function | |||||
real(8) function GetPortCasingPressure() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPortCasingPressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPortCasingPressure' :: GetPortCasingPressure | |||||
implicit none | |||||
GetPortCasingPressure = PortCasingPressure | |||||
end function | |||||
real(8) function GetPortPumpPressure() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPortPumpPressure | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPortPumpPressure' :: GetPortPumpPressure | |||||
implicit none | |||||
GetPortPumpPressure = PortPumpPressure | |||||
end function | |||||
end module CDataDisplayConsole |
@@ -0,0 +1,258 @@ | |||||
module CDataDisplayConsoleVariables | |||||
use CIActionReference | |||||
use CDoubleEventHandlerCollection | |||||
implicit none | |||||
public | |||||
!portable | |||||
real(8) :: TripAlarmLow | |||||
real(8) :: TripAlarmHigh | |||||
real(8) :: RetFlowAlarmLow | |||||
real(8) :: RetFlowAlarmHigh | |||||
real(8) :: PitAlarmLow | |||||
real(8) :: PitAlarmHigh | |||||
real(8) :: PortWeightOnBit | |||||
real(8) :: PortHookLoad | |||||
real(8) :: PortCasingPressure | |||||
real(8) :: PortPumpPressure | |||||
! Input vars | |||||
real(8) :: TripTankSetAlarmLow | |||||
real(8) :: TripTankSetAlarmHigh | |||||
integer :: TripTankSetAlarmSwitch | |||||
logical :: TripTankPowerSwitch | |||||
logical :: TripTankPumpSwitch | |||||
logical :: TripTankHornSwitch | |||||
logical :: AcidGasDetectionHornSwitch | |||||
logical :: TotalStrokeCounterResetSwitch | |||||
logical :: DrillingTrippingSelectorSwitch | |||||
real(8) :: MVTSetAlarmLowKnob | |||||
real(8) :: MVTSetAlarmHighKnob | |||||
integer :: MVTSetAlarmSwitch | |||||
logical :: MudTank1Switch | |||||
logical :: MudTank2Switch | |||||
logical :: MudTank3Switch | |||||
logical :: MudTank4Switch | |||||
real(8) :: MVTFineKnob | |||||
real(8) :: MVTCoarseKnob | |||||
logical :: MVTHornSwitch | |||||
logical :: MVTDeviationTripSelectionSwitch | |||||
logical :: MVTPowerSwitch | |||||
logical :: MFFIResetTotalStrokes | |||||
logical :: MFFIResetFillCounter | |||||
integer :: MFFIPumpSelectorSwitch | |||||
logical :: MFFIFillSPMSelectorSwitch | |||||
real(8) :: MFFISetAlarmLowKnob | |||||
real(8) :: MFFISetAlarmHighKnob | |||||
integer :: MFFISetAlarmSwitch | |||||
logical :: MFFIPowerSwitch | |||||
logical :: MFFIHornSwitch | |||||
logical :: ResetWob | |||||
logical :: Clutch | |||||
! Output vars | |||||
real(8) :: WOBPointer | |||||
real(8) :: HookLoadPointer | |||||
real(8) :: TripTankGauge | |||||
integer :: TripTankAlarmLED | |||||
integer :: TripTankPumpLED | |||||
real(8) :: StandPipePressureGauge | |||||
real(8) :: CasingPressureGauge | |||||
real(8) :: MP1SPMGauge | |||||
real(8) :: MP2SPMGauge | |||||
real(8) :: ReturnLineTempGauge | |||||
real(8) :: RotaryTorqueGauge | |||||
real(8) :: RotaryRPMGauge | |||||
type(DoubleEventHandlerCollection) :: OnRotaryRpmChange | |||||
integer :: AcidGasDetectionLED | |||||
real(8) :: TotalStrokeCounter | |||||
!real(8) :: TotalStrokeCounter_temp | |||||
real(8) :: PitGainLossGauge | |||||
real(8) :: MudTanksVolumeGauge | |||||
integer :: MVTAlarmLED | |||||
real(8) :: ReturnMudFlowGauge | |||||
real(8) :: FillStrokeCounter | |||||
real(8) :: MFFITotalStrokeCounter | |||||
integer :: MFFIAlarmLED | |||||
integer :: MFFIPumpLED | |||||
real(8) :: TotalWellDepth | |||||
real(8) :: BitDepth | |||||
real(8) :: HookLoad | |||||
real(8) :: StandPipePressure | |||||
real(8) :: CasingPressure | |||||
real(8) :: MP1SPM | |||||
real(8) :: MP2SPM | |||||
real(8) :: RTTorque | |||||
real(8) :: RTRPM | |||||
real(8) :: WOP | |||||
real(8) :: ROP | |||||
real(8) :: MudWeightIn | |||||
real(8) :: MudWeightOut | |||||
logical :: Buzzer1 | |||||
logical :: Buzzer2 | |||||
logical :: Buzzer3 | |||||
logical :: Buzzer4 | |||||
! events | |||||
procedure (ActionDualDouble), pointer :: PumpsSpmChanges => null() | |||||
contains | |||||
subroutine Set_TotalDepth(v) | |||||
use CDrillWatchVariables, only: Depth | |||||
use CSimulationVariables, only: SetDistanceDrilled | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
TotalWellDepth = v | |||||
Depth = v | |||||
call SetDistanceDrilled(v) | |||||
end subroutine | |||||
subroutine Set_BitPosition(v) | |||||
use CDrillWatchVariables, only: BitPosition | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
BitDepth = v | |||||
BitPosition = v | |||||
end subroutine | |||||
subroutine Set_RotaryTorque(v) | |||||
use CDrillWatchVariables, only: Torque | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
RotaryTorqueGauge = v | |||||
Torque = v | |||||
RTTorque = v | |||||
end subroutine | |||||
subroutine Set_MudWeightIn(v) | |||||
use CDrillWatchVariables, only: MudWeightInDw => MudWeightIn | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
MudWeightIn = v | |||||
MudWeightInDw = v | |||||
end subroutine | |||||
subroutine Set_MudWeightOut(v) | |||||
use CDrillWatchVariables, only: MudWeightOutDw => MudWeightOut | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
MudWeightOut = v | |||||
MudWeightOutDw = v | |||||
end subroutine | |||||
subroutine Set_TripTankVolume(v) | |||||
use CDrillWatchVariables, only: TripTankVolume | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
TripTankVolume = v | |||||
end subroutine | |||||
subroutine Set_FillVolume(v) | |||||
use CDrillWatchVariables, only: FillVolume | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
FillVolume = v | |||||
end subroutine | |||||
subroutine Set_HookLoad(v) | |||||
use CDrillWatchVariables, only: HookLoadDw => HookLoad | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
HookLoadPointer = v | |||||
HookLoadDw = v * 1000 | |||||
HookLoad = v | |||||
end subroutine | |||||
subroutine Set_WeightOnBit(v) | |||||
use CDrillWatchVariables, only: WeightOnBit | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
WOBPointer = v | |||||
WeightOnBit = v | |||||
WOP = v | |||||
end subroutine | |||||
subroutine Set_ROP(v) | |||||
use CDrillWatchVariables, only: ROPDw => ROP | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
ROP = v | |||||
ROPDw = v | |||||
end subroutine | |||||
subroutine Set_CasingPressure(v) | |||||
use CDrillWatchVariables, only: CasingPressureDw => CasingPressure | |||||
use CChokeControlPanelVariables, only: CasingPressureChoke => CasingPressure | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
CasingPressureGauge = v | |||||
CasingPressureDw = v | |||||
CasingPressureChoke = v | |||||
CasingPressure = v | |||||
end subroutine | |||||
subroutine Set_StandPipePressure(v) | |||||
use CDrillWatchVariables, only: PumpPressure | |||||
use CChokeControlPanelVariables, only: StandPipePressureChoke => StandPipePressure | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
StandPipePressureGauge = v | |||||
PumpPressure = v | |||||
StandPipePressureChoke = v | |||||
StandPipePressure = v | |||||
end subroutine | |||||
subroutine Set_RotaryRPMGauge(v) | |||||
use CDrillWatchVariables, only: RPM | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
RotaryRPMGauge = v | |||||
RPM = v | |||||
RTRPM = v | |||||
call OnRotaryRpmChange%RunAll(v) | |||||
end subroutine | |||||
subroutine Set_MP1SPMGauge(v) | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
MP1SPMGauge = v | |||||
MP1SPM = v | |||||
if(associated(PumpsSpmChanges)) call PumpsSpmChanges(MP1SPMGauge, MP2SPMGauge) | |||||
#ifdef deb | |||||
print*, 'MP1SPMGauge=', MP1SPMGauge | |||||
#endif | |||||
end subroutine | |||||
subroutine Set_MP2SPMGauge(v) | |||||
implicit none | |||||
real(8), intent(in) :: v | |||||
MP2SPMGauge = v | |||||
MP2SPM = v | |||||
if(associated(PumpsSpmChanges)) call PumpsSpmChanges(MP1SPMGauge, MP2SPMGauge) | |||||
#ifdef deb | |||||
print*, 'MP2SPMGauge=', MP2SPMGauge | |||||
#endif | |||||
end subroutine | |||||
end module CDataDisplayConsoleVariables |
@@ -0,0 +1,871 @@ | |||||
module CDrillingConsole | |||||
use CDrillingConsoleVariables | |||||
use CSimulationVariables | |||||
use CLog4 | |||||
use CLog3 | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
subroutine SetAssignmentSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAssignmentSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAssignmentSwitch' :: SetAssignmentSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
AssignmentSwitch = v | |||||
#ifdef deb | |||||
call Log_4( 'AssignmentSwitch=', AssignmentSwitch) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetEmergencySwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetEmergencySwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetEmergencySwitch' :: SetEmergencySwitch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
EmergencySwitch = v | |||||
#ifdef deb | |||||
print*, 'EmergencySwitch=', EmergencySwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetRTTorqueLimitKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRTTorqueLimitKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRTTorqueLimitKnob' :: SetRTTorqueLimitKnob | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
RTTorqueLimitKnob = v | |||||
#ifdef deb | |||||
print*, 'RTTorqueLimitKnob=', RTTorqueLimitKnob | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMP1CPSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMP1CPSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMP1CPSwitch' :: SetMP1CPSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
if(MP1CPSwitch == v) return | |||||
if(SimulationState == SimulationState_Started) then | |||||
MP1CPSwitchI = MP1CPSwitchI + 1 | |||||
if(MP1CPSwitchI >= 1) MP1CPSwitch = v | |||||
if(MP1CPSwitchI >= 100) MP1CPSwitchI = 1 | |||||
!call Log_3( "MP1CPSwitchI=", MP1CPSwitchI) | |||||
!call Log_3( "MP1CPSwitch=", MP1CPSwitch) | |||||
!MP1CPSwitch = v | |||||
endif | |||||
! if(SimulationState == SimulationState_Started) then | |||||
! !call Log_3( 'MP1CPSwitc(s)h=', MP1CPSwitch) | |||||
! if(MP1CPSwitchT /= v) then | |||||
! MP1CPSwitchT = v | |||||
! MP1CPSwitch = v | |||||
!#ifdef deb | |||||
! !print*, 'MP1CPSwitch=', MP1CPSwitch | |||||
! !call Log_3( 'MP1CPSwitch=', MP1CPSwitch) | |||||
!#endif | |||||
! endif | |||||
! else | |||||
! MP1CPSwitchT = v | |||||
! endif | |||||
end subroutine | |||||
subroutine SetMP1Throttle(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMP1Throttle | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMP1Throttle' :: SetMP1Throttle | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
if(MP1Throttle == v) return | |||||
if(SimulationState == SimulationState_Started) then | |||||
if( abs(v - MP1Throttle) > 0.1) MP1ThrottleUpdate = .true. | |||||
if(MP1ThrottleUpdate) MP1Throttle = v | |||||
!call Log_3( 'v-mp1=', v) | |||||
!call Log_3( 'MP1Throttle=', MP1Throttle) | |||||
!call Log_3( 'MP1ThrottleUpdate=', MP1ThrottleUpdate) | |||||
!MP1Throttle = v | |||||
endif | |||||
#ifdef deb | |||||
print*, 'MP1Throttle=', MP1Throttle | |||||
#endif | |||||
end subroutine | |||||
subroutine SetMP2Switch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMP2Switch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMP2Switch' :: SetMP2Switch | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
!call Log_3( 'v=', MP2SwitchT) | |||||
if(MP2Switch == v) return | |||||
if(SimulationState == SimulationState_Started) then | |||||
MP2SwitchI = MP2SwitchI + 1 | |||||
if(MP2SwitchI >= 1) MP2Switch = v | |||||
if(MP2SwitchI >= 100) MP2SwitchI = 1 | |||||
!call Log_3( "MP1CPSwitchI=", MP1CPSwitchI) | |||||
!call Log_3( "MP2Switch=", MP2Switch) | |||||
!MP2Switch = v | |||||
endif | |||||
! if(SimulationState == SimulationState_Started) then | |||||
! !call Log_3( 'MP2Switch(s)=', MP2Switch) | |||||
! if(MP2SwitchT /= v) then | |||||
! MP2SwitchT = v | |||||
! MP2Switch = v | |||||
!#ifdef deb | |||||
! !print*, 'MP2Switch=', MP2Switch | |||||
! !call Log_3( 'MP2Switch=', MP2Switch) | |||||
!#endif | |||||
! endif | |||||
! else | |||||
! MP2SwitchT = v | |||||
! !call Log_3( 'MP2SwitchTMP2SwitchTMP2SwitchT=', MP2SwitchT) | |||||
! endif | |||||
end subroutine | |||||
subroutine SetMP2Throttle(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetMP2Throttle | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetMP2Throttle' :: SetMP2Throttle | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
if(MP2Throttle == v) return | |||||
if(SimulationState == SimulationState_Started) then | |||||
if( abs(v - MP2Throttle) > 0.1) MP2ThrottleUpdate = .true. | |||||
if(MP2ThrottleUpdate) MP2Throttle = v | |||||
!call Log_3( 'v-mp2=', v) | |||||
!call Log_3( 'MP2Throttle=', MP2Throttle) | |||||
!call Log_3( 'MP2ThrottleUpdate=', MP2ThrottleUpdate) | |||||
!MP2Throttle = v | |||||
endif | |||||
#ifdef deb | |||||
print*, 'MP2Throttle=', MP2Throttle | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDWSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDWSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDWSwitch' :: SetDWSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
DWSwitch = v | |||||
#ifdef deb | |||||
print*, 'DWSwitch=', DWSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDWThrottle(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDWThrottle | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDWThrottle' :: SetDWThrottle | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
DWThrottle = v | |||||
#ifdef deb | |||||
print*, 'DWThrottle=', DWThrottle | |||||
#endif | |||||
end subroutine | |||||
subroutine SetRTSwitch(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRTSwitch | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRTSwitch' :: SetRTSwitch | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
RTSwitch = v | |||||
#ifdef deb | |||||
print*, 'RTSwitch=', RTSwitch | |||||
#endif | |||||
end subroutine | |||||
subroutine SetRTThrottle(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRTThrottle | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRTThrottle' :: SetRTThrottle | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
RTThrottle = v | |||||
#ifdef deb | |||||
print*, 'RTThrottle=', RTThrottle | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDWBreak(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDWBreak | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDWBreak' :: SetDWBreak | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
!if(ForceBreak) return | |||||
PreviousDWBreak = DWBreak | |||||
DWBreak = v | |||||
#ifdef deb | |||||
print*, 'DWBreak=', DWBreak | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDWAcceleretor(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDWAcceleretor | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDWAcceleretor' :: SetDWAcceleretor | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
DWAcceleretor = v | |||||
#ifdef deb | |||||
print*, 'DWAcceleretor=', DWAcceleretor | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDWTransmisionLever(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDWTransmisionLever | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDWTransmisionLever' :: SetDWTransmisionLever | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
DWTransmisionLever = v | |||||
#ifdef deb | |||||
print*, 'DWTransmisionLever=', DWTransmisionLever | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDWPowerLever(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDWPowerLever | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDWPowerLever' :: SetDWPowerLever | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
DWPowerLever = v | |||||
#ifdef deb | |||||
print*, 'DWPowerLever=', DWPowerLever | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTongLever(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTongLever | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTongLever' :: SetTongLever | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
if (TongLever == v) return | |||||
TongLever = v | |||||
! if(dint(TongLever) == 1.0) then | |||||
! call OnBreakoutLeverPress%RunAll() | |||||
! #ifdef deb | |||||
! print*, 'OnBreakoutLeverPress=', size(OnBreakoutLeverPress%Delegates) | |||||
! #endif | |||||
! endif | |||||
! if(dint(TongLever) == -1.0) then | |||||
! call OnMakeupLeverPress%RunAll() | |||||
! #ifdef deb | |||||
! print*, 'OnMakeupPress=', size(OnMakeupLeverPress%Delegates) | |||||
! #endif | |||||
! endif | |||||
! if(dint(TongLever) == 0.0) then | |||||
! call OnTongNeutralPress%RunAll() | |||||
! #ifdef deb | |||||
! print*, 'OnTongNeutralPress=', size(OnTongNeutralPress%Delegates) | |||||
! #endif | |||||
! endif | |||||
#ifdef deb | |||||
print*, 'TongLever=', TongLever | |||||
#endif | |||||
end subroutine | |||||
subroutine SetRTTransmissionLever(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRTTransmissionLever | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRTTransmissionLever' :: SetRTTransmissionLever | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
RTTransmissionLever = v | |||||
#ifdef deb | |||||
print*, 'RTTransmissionLever=', RTTransmissionLever | |||||
#endif | |||||
end subroutine | |||||
subroutine SetDWClutchLever(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDWClutchLever | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDWClutchLever' :: SetDWClutchLever | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
DWClutchLever = v | |||||
#ifdef deb | |||||
print*, 'DWClutchLever=', DWClutchLever | |||||
#endif | |||||
end subroutine | |||||
subroutine SetEddyBreakLever(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetEddyBreakLever | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetEddyBreakLever' :: SetEddyBreakLever | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
EddyBreakLever = v | |||||
#ifdef deb | |||||
print*, 'EddyBreakLever=', EddyBreakLever | |||||
#endif | |||||
end subroutine | |||||
subroutine SetAutoDW(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetAutoDW | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetAutoDW' :: SetAutoDW | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
AutoDW = v | |||||
#ifdef deb | |||||
print*, 'AutoDW=', AutoDW | |||||
#endif | |||||
end subroutine | |||||
subroutine SetGEN1(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetGEN1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetGEN1' :: SetGEN1 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
GEN1 = v | |||||
#ifdef deb | |||||
print*, 'GEN1=', GEN1 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetGEN2(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetGEN2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetGEN2' :: SetGEN2 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
GEN2 = v | |||||
#ifdef deb | |||||
print*, 'GEN2=', GEN2 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetGEN3(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetGEN3 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetGEN3' :: SetGEN3 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
GEN3 = v | |||||
#ifdef deb | |||||
print*, 'GEN3=', GEN3 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetGEN4(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetGEN4 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetGEN4' :: SetGEN4 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
GEN4 = v | |||||
#ifdef deb | |||||
print*, 'GEN4=', GEN4 | |||||
#endif | |||||
end subroutine | |||||
! subroutine SetInstallSafetyValve(v) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SetInstallSafetyValve | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SetInstallSafetyValve' :: SetInstallSafetyValve | |||||
! implicit none | |||||
! logical, intent(in) :: v | |||||
! InstallSafetyValve = v | |||||
!#ifdef deb | |||||
! print*, 'InstallSafetyValve=', InstallSafetyValve | |||||
!#endif | |||||
! end subroutine | |||||
! | |||||
! subroutine SetOpenSafetyValve(v) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SetOpenSafetyValve | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SetOpenSafetyValve' :: SetOpenSafetyValve | |||||
! implicit none | |||||
! logical, intent(in) :: v | |||||
! OpenSafetyValve = v | |||||
!#ifdef deb | |||||
! print*, 'OpenSafetyValve=', OpenSafetyValve | |||||
!#endif | |||||
! end subroutine | |||||
! | |||||
! subroutine SetRemoveSafetyValve(v) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SetRemoveSafetyValve | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SetRemoveSafetyValve' :: SetRemoveSafetyValve | |||||
! implicit none | |||||
! logical, intent(in) :: v | |||||
! RemoveSafetyValve = v | |||||
!#ifdef deb | |||||
! print*, 'RemoveSafetyValve=', RemoveSafetyValve | |||||
!#endif | |||||
! end subroutine | |||||
! | |||||
! subroutine SetCloseSafetyValve(v) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SetCloseSafetyValve | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SetCloseSafetyValve' :: SetCloseSafetyValve | |||||
! implicit none | |||||
! logical, intent(in) :: v | |||||
! CloseSafetyValve = v | |||||
!#ifdef deb | |||||
! print*, 'CloseSafetyValve=', CloseSafetyValve | |||||
!#endif | |||||
! end subroutine | |||||
! | |||||
! subroutine SetMakeJoint(v) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SetMakeJoint | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SetMakeJoint' :: SetMakeJoint | |||||
! implicit none | |||||
! logical, intent(in) :: v | |||||
! MakeJoint = v | |||||
!#ifdef deb | |||||
! print*, 'MakeJoint=', MakeJoint | |||||
!#endif | |||||
! end subroutine | |||||
! | |||||
! subroutine SetBreakJoint(v) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SetBreakJoint | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SetBreakJoint' :: SetBreakJoint | |||||
! implicit none | |||||
! logical, intent(in) :: v | |||||
! BreakJoint = v | |||||
!#ifdef deb | |||||
! print*, 'BreakJoint=', BreakJoint | |||||
!#endif | |||||
! end subroutine | |||||
subroutine SetOpenKellyCock(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetOpenKellyCock | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetOpenKellyCock' :: SetOpenKellyCock | |||||
use CManifolds, OpenKellyCockSub => OpenKellyCock | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (OpenKellyCock == v) return | |||||
OpenKellyCock = v | |||||
! if (v) call OnOpenKellyCockPress%RunAll() | |||||
if(v .and. Permission_OpenKellyCock) call OpenKellyCockSub() | |||||
#ifdef deb | |||||
print*, 'OpenKellyCock=', OpenKellyCock | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCloseKellyCock(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCloseKellyCock | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCloseKellyCock' :: SetCloseKellyCock | |||||
use CManifolds, CloseKellyCockSub => CloseKellyCock | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (CloseKellyCock == v) return | |||||
CloseKellyCock = v | |||||
! if (v) call OnCloseKellyCockPress%RunAll() | |||||
if(v .and. Permission_CloseKellyCock) call CloseKellyCockSub() | |||||
#ifdef deb | |||||
print*, 'CloseKellyCock=', CloseKellyCock | |||||
#endif | |||||
end subroutine | |||||
subroutine SetOpenSafetyValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetOpenSafetyValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetOpenSafetyValve' :: SetOpenSafetyValve | |||||
!use CManifolds, OpenSafetyValveSub => OpenSafetyValve | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (OpenSafetyValve == v) return | |||||
OpenSafetyValve = v | |||||
! if (v) call OnOpenSafetyValvePress%RunAll() | |||||
!if(v .and. Permission_OpenSafetyValve) call OpenSafetyValveSub() | |||||
#ifdef deb | |||||
print*, 'OpenSafetyValve=', OpenSafetyValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCloseSafetyValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCloseSafetyValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCloseSafetyValve' :: SetCloseSafetyValve | |||||
!use CManifolds, CloseSafetyValveSub => CloseSafetyValve | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (CloseSafetyValve == v) return | |||||
CloseSafetyValve = v | |||||
! if (v) call OnCloseSafetyValvePress%RunAll() | |||||
!if(v .and. Permission_CloseSafetyValve) call CloseSafetyValveSub() | |||||
#ifdef deb | |||||
print*, 'CloseSafetyValve=', CloseSafetyValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetIRSafetyValve(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetIRSafetyValve | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetIRSafetyValve' :: SetIRSafetyValve | |||||
use CManifolds | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
logical :: prev | |||||
if (IRSafetyValve == v) return | |||||
prev = IRSafetyValve | |||||
IRSafetyValve = v | |||||
! if (v) call OnIRSafetyValvePress%RunAll() | |||||
!if(prev /= IRSafetyValve .and. v .and. Permission_IRSafetyValve) call ToggleSafetyValve() | |||||
!if(prev /= IRSafetyValve .and. v) call ToggleSafetyValve() | |||||
#ifdef deb | |||||
print*, 'IRSafetyValve=', IRSafetyValve | |||||
#endif | |||||
end subroutine | |||||
subroutine SetIRIBop(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetIRIBop | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetIRIBop' :: SetIRIBop | |||||
use CManifolds | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
logical :: prev | |||||
if (IRIBop == v) return | |||||
prev = IRIBop | |||||
IRIBop = v | |||||
! if (v) call OnIRIBopPress%RunAll() | |||||
!if(prev /= IRIBop .and. v .and. Permission_IRIBop) call ToggleIBop() | |||||
!if(prev /= IRIBop .and. v) call ToggleIBop() | |||||
#ifdef deb | |||||
print*, 'IRIBop=', IRIBop | |||||
#endif | |||||
end subroutine | |||||
subroutine SetLatchPipe(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetLatchPipe | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetLatchPipe' :: SetLatchPipe | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (LatchPipe .eqv. v) return | |||||
LatchPipe = v | |||||
! if (v) call OnLatchPipePress%RunAll() | |||||
#ifdef deb | |||||
print*, 'LatchPipe=', LatchPipe | |||||
#endif | |||||
end subroutine | |||||
subroutine SetUnlatchPipe(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetUnlatchPipe | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetUnlatchPipe' :: SetUnlatchPipe | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (UnlatchPipe .eqv. v) return | |||||
UnlatchPipe = v | |||||
! if (v) call OnUnlatchPipePress%RunAll() | |||||
#ifdef deb | |||||
print*, 'UnlatchPipe=', UnlatchPipe | |||||
#endif | |||||
end subroutine | |||||
subroutine SetSwing(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetSwing | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetSwing' :: SetSwing | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (Swing .eqv. v) return | |||||
Swing = v | |||||
! if (v) call OnSwingPress%RunAll() | |||||
#ifdef deb | |||||
print*, 'Swing=', Swing | |||||
#endif | |||||
end subroutine | |||||
subroutine SetFillMouseHole(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetFillMouseHole | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetFillMouseHole' :: SetFillMouseHole | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (FillMouseHole .eqv. v) return | |||||
FillMouseHole = v | |||||
! if (v) call OnFillMouseHolePress%RunAll() | |||||
#ifdef deb | |||||
print*, 'FillMouseHole=', FillMouseHole | |||||
#endif | |||||
end subroutine | |||||
subroutine SetSlips(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetSlips | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetSlips' :: SetSlips | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
if (Slips .eqv. v) return | |||||
Slips = v | |||||
#ifdef deb | |||||
print*, 'Slips=', Slips | |||||
#endif | |||||
! if (v) call OnSlipsPress%RunAll() | |||||
end subroutine | |||||
subroutine SetBrakeLeverCoefficient(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetBrakeLeverCoefficient | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetBrakeLeverCoefficient' :: SetBrakeLeverCoefficient | |||||
implicit none | |||||
real, intent(in) :: v | |||||
BrakeLeverCoefficient = v | |||||
#ifdef deb | |||||
print*, 'BrakeLeverCoefficient=', BrakeLeverCoefficient | |||||
#endif | |||||
end subroutine | |||||
subroutine SetHideDrillingBrake(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetHideDrillingBrake | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetHideDrillingBrake' :: SetHideDrillingBrake | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
HideDrillingBrake = v | |||||
#ifdef deb | |||||
print*, 'HideDrillingBrake=', HideDrillingBrake | |||||
#endif | |||||
end subroutine | |||||
subroutine SetParkingBrake(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetParkingBrake | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetParkingBrake' :: SetParkingBrake | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ParkingBrakeBtn = v | |||||
#ifdef deb | |||||
print*, 'ParkingBrakeBtn=', ParkingBrakeBtn | |||||
#endif | |||||
end subroutine | |||||
! Output routines | |||||
logical function GetParkingBrakeLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetParkingBrakeLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetParkingBrakeLed' :: GetParkingBrakeLed | |||||
implicit none | |||||
GetParkingBrakeLed = ParkingBrakeLed | |||||
!GetParkingBrakeLed = .true. | |||||
end function | |||||
integer function GetGEN1LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetGEN1LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetGEN1LED' :: GetGEN1LED | |||||
implicit none | |||||
GetGEN1LED = 1 | |||||
!GetGEN1LED = GEN1LED | |||||
end function | |||||
integer function GetGEN2LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetGEN2LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetGEN2LED' :: GetGEN2LED | |||||
implicit none | |||||
GetGEN2LED = 1 | |||||
!GetGEN2LED = GEN2LED | |||||
end function | |||||
integer function GetGEN3LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetGEN3LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetGEN3LED' :: GetGEN3LED | |||||
implicit none | |||||
GetGEN3LED = 1 | |||||
!GetGEN3LED = GEN3LED | |||||
end function | |||||
integer function GetGEN4LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetGEN4LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetGEN4LED' :: GetGEN4LED | |||||
implicit none | |||||
GetGEN4LED = 1 | |||||
!GetGEN4LED = GEN4LED | |||||
end function | |||||
integer function GetSCR1LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetSCR1LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetSCR1LED' :: GetSCR1LED | |||||
implicit none | |||||
GetSCR1LED = SCR1LED | |||||
end function | |||||
integer function GetSCR2LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetSCR2LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetSCR2LED' :: GetSCR2LED | |||||
implicit none | |||||
GetSCR2LED = SCR2LED | |||||
end function | |||||
integer function GetSCR3LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetSCR3LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetSCR3LED' :: GetSCR3LED | |||||
implicit none | |||||
GetSCR3LED = SCR3LED | |||||
end function | |||||
integer function GetSCR4LED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetSCR4LED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetSCR4LED' :: GetSCR4LED | |||||
implicit none | |||||
GetSCR4LED = SCR4LED | |||||
end function | |||||
integer function GetMP1BLWR() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMP1BLWR | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMP1BLWR' :: GetMP1BLWR | |||||
implicit none | |||||
GetMP1BLWR = MP1BLWR | |||||
end function | |||||
integer function GetMP2BLWR() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMP2BLWR | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMP2BLWR' :: GetMP2BLWR | |||||
implicit none | |||||
GetMP2BLWR = MP2BLWR | |||||
end function | |||||
integer function GetDWBLWR() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetDWBLWR | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetDWBLWR' :: GetDWBLWR | |||||
implicit none | |||||
GetDWBLWR = DWBLWR | |||||
end function | |||||
integer function GetRTBLWR() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetRTBLWR | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetRTBLWR' :: GetRTBLWR | |||||
implicit none | |||||
GetRTBLWR = RTBLWR | |||||
end function | |||||
integer function GetPWRLIM() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPWRLIM | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPWRLIM' :: GetPWRLIM | |||||
implicit none | |||||
GetPWRLIM = PWRLIM | |||||
end function | |||||
real(8) function GetPWRLIMMTR() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPWRLIMMTR | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPWRLIMMTR' :: GetPWRLIMMTR | |||||
implicit none | |||||
GetPWRLIMMTR = PWRLIMMTR | |||||
end function | |||||
real(8) function GetRTTorqueLimitGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetRTTorqueLimitGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetRTTorqueLimitGauge' :: GetRTTorqueLimitGauge | |||||
implicit none | |||||
GetRTTorqueLimitGauge = RTTorqueLimitGauge | |||||
end function | |||||
integer function GetAutoDWLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetAutoDWLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetAutoDWLED' :: GetAutoDWLED | |||||
implicit none | |||||
GetAutoDWLED = AutoDWLED | |||||
end function | |||||
integer function GetGEN1BTNLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetGEN1BTNLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetGEN1BTNLED' :: GetGEN1BTNLED | |||||
implicit none | |||||
GetGEN1BTNLED = GEN1BTNLED | |||||
end function | |||||
integer function GetGEN2BTNLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetGEN2BTNLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetGEN2BTNLED' :: GetGEN2BTNLED | |||||
implicit none | |||||
GetGEN2BTNLED = GEN2BTNLED | |||||
end function | |||||
integer function GetGEN3BTNLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetGEN3BTNLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetGEN3BTNLED' :: GetGEN3BTNLED | |||||
implicit none | |||||
GetGEN3BTNLED = GEN3BTNLED | |||||
end function | |||||
integer function GetGEN4BTNLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetGEN4BTNLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetGEN4BTNLED' :: GetGEN4BTNLED | |||||
implicit none | |||||
GetGEN4BTNLED = GEN4BTNLED | |||||
end function | |||||
integer function GetOpenKellyCockLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetOpenKellyCockLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetOpenKellyCockLed' :: GetOpenKellyCockLed | |||||
implicit none | |||||
GetOpenKellyCockLed = OpenKellyCockLed | |||||
end function | |||||
integer function GetCloseKellyCockLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetCloseKellyCockLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetCloseKellyCockLed' :: GetCloseKellyCockLed | |||||
implicit none | |||||
GetCloseKellyCockLed = CloseKellyCockLed | |||||
end function | |||||
integer function GetOpenSafetyValveLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetOpenSafetyValveLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetOpenSafetyValveLed' :: GetOpenSafetyValveLed | |||||
implicit none | |||||
GetOpenSafetyValveLed = OpenSafetyValveLed | |||||
end function | |||||
integer function GetCloseSafetyValveLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetCloseSafetyValveLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetCloseSafetyValveLed' :: GetCloseSafetyValveLed | |||||
implicit none | |||||
GetCloseSafetyValveLed = CloseSafetyValveLed | |||||
end function | |||||
integer function GetIRSafetyValveLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetIRSafetyValveLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetIRSafetyValveLed' :: GetIRSafetyValveLed | |||||
implicit none | |||||
GetIRSafetyValveLed = IRSafetyValveLed | |||||
end function | |||||
integer function GetIRIBopLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetIRIBopLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetIRIBopLed' :: GetIRIBopLed | |||||
implicit none | |||||
GetIRIBopLed = IRIBopLed | |||||
end function | |||||
integer function GetLatchPipeLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetLatchPipeLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetLatchPipeLED' :: GetLatchPipeLED | |||||
implicit none | |||||
GetLatchPipeLED = LatchPipeLED | |||||
end function | |||||
integer function GetUnlatchPipeLED() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetUnlatchPipeLED | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetUnlatchPipeLED' :: GetUnlatchPipeLED | |||||
implicit none | |||||
GetUnlatchPipeLED = UnlatchPipeLED | |||||
end function | |||||
integer function GetSwingLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetSwingLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetSwingLed' :: GetSwingLed | |||||
implicit none | |||||
GetSwingLed = SwingLed | |||||
end function | |||||
integer function GetFillMouseHoleLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetFillMouseHoleLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetFillMouseHoleLed' :: GetFillMouseHoleLed | |||||
implicit none | |||||
GetFillMouseHoleLed = FillMouseHoleLed | |||||
end function | |||||
end module CDrillingConsole |
@@ -0,0 +1,132 @@ | |||||
module CDrillingConsoleVariables | |||||
use CVoidEventHandlerCollection | |||||
implicit none | |||||
public | |||||
! Input vars | |||||
integer :: AssignmentSwitch | |||||
logical :: EmergencySwitch | |||||
real(8) :: RTTorqueLimitKnob | |||||
integer :: MP1CPSwitchI = 0 !for not turning on pump1 on simulation start | |||||
integer :: MP1CPSwitchT !for not turning on pump1 on simulation start | |||||
integer :: MP1CPSwitch | |||||
logical :: MP1ThrottleUpdate = .false. | |||||
real(8) :: MP1Throttle = -1.0 | |||||
integer :: MP2SwitchI = 0 !for not turning on pump2 on simulation start | |||||
logical :: MP2SwitchT !for not turning on pump2 on simulation start | |||||
logical :: MP2Switch | |||||
logical :: MP2ThrottleUpdate = .false. | |||||
real(8) :: MP2Throttle = -1.0 | |||||
integer :: DWSwitch | |||||
real(8) :: DWThrottle | |||||
integer :: RTSwitch | |||||
real(8) :: RTThrottle | |||||
real(8) :: DWBreak | |||||
real(8) :: PreviousDWBreak | |||||
logical :: ForceBreak = .false. | |||||
real(8) :: DWAcceleretor | |||||
real(8) :: DWTransmisionLever | |||||
real(8) :: DWPowerLever | |||||
real(8) :: TongLever | |||||
! type(VoidEventHandlerCollection) :: OnBreakoutLeverPress | |||||
! type(VoidEventHandlerCollection) :: OnMakeupLeverPress | |||||
! type(VoidEventHandlerCollection) :: OnTongNeutralPress | |||||
real(8) :: RTTransmissionLever | |||||
real(8) :: DWClutchLever | |||||
real(8) :: EddyBreakLever | |||||
logical :: AutoDW | |||||
logical :: GEN1 | |||||
logical :: GEN2 | |||||
logical :: GEN3 | |||||
logical :: GEN4 | |||||
logical :: Permission_OpenKellyCock = .false. | |||||
logical :: OpenKellyCock | |||||
! type(VoidEventHandlerCollection) :: OnOpenKellyCockPress | |||||
logical :: Permission_CloseKellyCock = .false. | |||||
logical :: CloseKellyCock | |||||
! type(VoidEventHandlerCollection) :: OnCloseKellyCockPress | |||||
logical :: Permission_OpenSafetyValve = .false. | |||||
logical :: OpenSafetyValve | |||||
! typeVoidEventHandlerCollection) :: OnOpenSafetyValvePress | |||||
logical :: Permission_CloseSafetyValve = .false. | |||||
logical :: CloseSafetyValve | |||||
! typeVoidEventHandlerCollection) :: OnCloseSafetyValvePress | |||||
logical :: Permission_IRSafetyValve = .false. | |||||
logical :: IRSafetyValve | |||||
! typeVoidEventHandlerCollection) :: OnIRSafetyValvePress | |||||
logical :: Permission_IRIBop = .false. | |||||
logical :: IRIBop | |||||
! typeVoidEventHandlerCollection) :: OnIRIBopPress | |||||
logical :: LatchPipe | |||||
! typeVoidEventHandlerCollection) :: OnLatchPipePress | |||||
logical :: UnlatchPipe | |||||
! typeVoidEventHandlerCollection) :: OnUnlatchPipePress | |||||
logical :: Swing | |||||
! typeVoidEventHandlerCollection) :: OnSwingPress | |||||
logical :: FillMouseHole | |||||
! typeVoidEventHandlerCollection) :: OnFillMouseHolePress | |||||
logical :: Slips | |||||
! typeVoidEventHandlerCollection) :: OnSlipsPress | |||||
!logical :: TopDriveIBop | |||||
! | |||||
!logical :: TopDriveDrillTorque | |||||
!integer :: TopDriveRevOffFwd | |||||
!integer :: TopDriveDrillOffTilt | |||||
real :: BrakeLeverCoefficient | |||||
logical :: HideDrillingBrake | |||||
logical :: ParkingBrakeBtn | |||||
! Output vars | |||||
logical :: ParkingBrakeLed | |||||
integer :: GEN1LED | |||||
integer :: GEN2LED | |||||
integer :: GEN3LED | |||||
integer :: GEN4LED | |||||
integer :: SCR1LED | |||||
integer :: SCR2LED | |||||
integer :: SCR3LED | |||||
integer :: SCR4LED | |||||
integer :: MP1BLWR | |||||
integer :: MP2BLWR | |||||
integer :: DWBLWR | |||||
integer :: RTBLWR | |||||
integer :: PWRLIM | |||||
real(8) :: PWRLIMMTR | |||||
real(8) :: RTTorqueLimitGauge | |||||
integer :: AutoDWLED | |||||
integer :: GEN1BTNLED | |||||
integer :: GEN2BTNLED | |||||
integer :: GEN3BTNLED | |||||
integer :: GEN4BTNLED | |||||
integer :: OpenKellyCockLed | |||||
integer :: CloseKellyCockLed | |||||
integer :: OpenSafetyValveLed | |||||
integer :: CloseSafetyValveLed | |||||
integer :: IRSafetyValveLed | |||||
integer :: IRIBopLed | |||||
integer :: LatchPipeLED | |||||
integer :: UnlatchPipeLED | |||||
integer :: SwingLed | |||||
integer :: FillMouseHoleLed | |||||
contains | |||||
end module CDrillingConsoleVariables |
@@ -0,0 +1,11 @@ | |||||
module CEquipmentsConstants | |||||
implicit none | |||||
public | |||||
! LED State Types | |||||
integer :: LedOff = 0 | |||||
integer :: LedOn = 1 | |||||
integer :: LedBlinking = 2 | |||||
contains | |||||
end module CEquipmentsConstants |
@@ -0,0 +1,6 @@ | |||||
module CHook | |||||
use CHookVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
end module CHook |
@@ -0,0 +1,16 @@ | |||||
module CHookActions | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
procedure (ActionReal), pointer :: HookHeightPtr | |||||
contains | |||||
subroutine SubscribeHookHeight(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeHookHeight | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeHookHeight' :: SubscribeHookHeight | |||||
implicit none | |||||
procedure (ActionReal) :: a | |||||
HookHeightPtr => a | |||||
end subroutine | |||||
end module CHookActions |
@@ -0,0 +1,79 @@ | |||||
module CHookVariables | |||||
use CRealEventHandlerCollection | |||||
use CHookActions | |||||
implicit none | |||||
public | |||||
real :: HookHeight_S = 0.0 | |||||
real :: HookHeight | |||||
type(RealEventHandlerCollection) :: OnHookHeightChange | |||||
contains | |||||
subroutine Set_HookHeight(v) | |||||
use CDrillingConsoleVariables | |||||
implicit none | |||||
real , intent(in) :: v | |||||
#ifdef ExcludeExtraChanges | |||||
if(HookHeight == v) return | |||||
#endif | |||||
HookHeight = v | |||||
if(associated(HookHeightPtr)) then | |||||
call HookHeightPtr(HookHeight) | |||||
end if | |||||
#ifdef deb | |||||
print*, 'HookHeight=', HookHeight | |||||
#endif | |||||
call OnHookHeightChange%RunAll(HookHeight) | |||||
end subroutine | |||||
subroutine Set_HookHeight_S(v) | |||||
implicit none | |||||
real , intent(in) :: v | |||||
if(v == HookHeight) then | |||||
return | |||||
elseif (v > HookHeight) then | |||||
loop1: do | |||||
call Set_HookHeight(HookHeight + 0.2) | |||||
if(abs(v - HookHeight) <= 0.1) then | |||||
call Set_HookHeight(v) | |||||
exit loop1 | |||||
endif | |||||
call sleepqq(100) | |||||
enddo loop1 | |||||
else ! v < HookHeight | |||||
loop2: do | |||||
call Set_HookHeight(HookHeight - 0.2) | |||||
if(abs(HookHeight - v) <= 0.1) then | |||||
call Set_HookHeight(v) | |||||
exit loop2 | |||||
endif | |||||
call sleepqq(100) | |||||
enddo loop2 | |||||
endif | |||||
end subroutine | |||||
subroutine Set_HookHeight_WN(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: Set_HookHeight_WN | |||||
!DEC$ ATTRIBUTES ALIAS: 'Set_HookHeight_WN' :: Set_HookHeight_WN | |||||
implicit none | |||||
real , intent(in) :: v | |||||
!call Set_HookHeight(v) | |||||
HookHeight_S = v | |||||
end subroutine | |||||
subroutine Update_HookHeight_From_Snapshot() | |||||
implicit none | |||||
call Set_HookHeight_S(HookHeight_S) | |||||
end subroutine | |||||
end module CHookVariables |
@@ -0,0 +1,206 @@ | |||||
module CStandPipeManifold | |||||
use CStandPipeManifoldVariables | |||||
use CManifolds | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
subroutine SetStandPipeManifoldValve1(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve1' :: SetStandPipeManifoldValve1 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve1 = v | |||||
call ChangeValve(13, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve1=', StandPipeManifoldValve1 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve2(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve2' :: SetStandPipeManifoldValve2 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve2 = v | |||||
call ChangeValve(14, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve2=', StandPipeManifoldValve2 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve3(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve3 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve3' :: SetStandPipeManifoldValve3 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve3 = v | |||||
call ChangeValve(15, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve3=', StandPipeManifoldValve3 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve4(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve4 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve4' :: SetStandPipeManifoldValve4 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve4 = v | |||||
call ChangeValve(11, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve4=', StandPipeManifoldValve4 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve5(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve5 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve5' :: SetStandPipeManifoldValve5 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve5 = v | |||||
call ChangeValve(12, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve5=', StandPipeManifoldValve5 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve6(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve6 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve6' :: SetStandPipeManifoldValve6 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve6 = v | |||||
call ChangeValve(9, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve6=', StandPipeManifoldValve6 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve7(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve7 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve7' :: SetStandPipeManifoldValve7 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve7 = v | |||||
call ChangeValve(10, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve7=', StandPipeManifoldValve7 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve8(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve8 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve8' :: SetStandPipeManifoldValve8 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve8 = v | |||||
call ChangeValve(6, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve8=', StandPipeManifoldValve8 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve9(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve9 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve9' :: SetStandPipeManifoldValve9 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve9 = v | |||||
call ChangeValve(7, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve9=', StandPipeManifoldValve9 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve10(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve10 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve10' :: SetStandPipeManifoldValve10 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve10 = v | |||||
call ChangeValve(8, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve10=', StandPipeManifoldValve10 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve11(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve11 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve11' :: SetStandPipeManifoldValve11 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve11 = v | |||||
call ChangeValve(1, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve11=', StandPipeManifoldValve11 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve12(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve12 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve12' :: SetStandPipeManifoldValve12 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve12 = v | |||||
call ChangeValve(2, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve12=', StandPipeManifoldValve12 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve13(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve13 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve13' :: SetStandPipeManifoldValve13 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve13 = v | |||||
call ChangeValve(3, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve13=', StandPipeManifoldValve13 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve14(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve14 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve14' :: SetStandPipeManifoldValve14 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve14 = v | |||||
call ChangeValve(4, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve14=', StandPipeManifoldValve14 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetStandPipeManifoldValve15(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetStandPipeManifoldValve15 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetStandPipeManifoldValve15' :: SetStandPipeManifoldValve15 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
StandPipeManifoldValve15 = v | |||||
call ChangeValve(5, v) | |||||
#ifdef deb | |||||
print*, 'StandPipeManifoldValve15=', StandPipeManifoldValve15 | |||||
#endif | |||||
end subroutine | |||||
! Output routines | |||||
real(8) function GetStandPipeGauge1() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetStandPipeGauge1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStandPipeGauge1' :: GetStandPipeGauge1 | |||||
implicit none | |||||
GetStandPipeGauge1 = StandPipeGauge1 | |||||
!GetStandPipeGauge1 = 567.4 | |||||
end function | |||||
real(8) function GetStandPipeGauge2() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetStandPipeGauge2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetStandPipeGauge2' :: GetStandPipeGauge2 | |||||
implicit none | |||||
GetStandPipeGauge2 = StandPipeGauge2 | |||||
!GetStandPipeGauge2 = 1564.0 | |||||
end function | |||||
end module CStandPipeManifold |
@@ -0,0 +1,27 @@ | |||||
module CStandPipeManifoldVariables | |||||
implicit none | |||||
public | |||||
! Input vars | |||||
logical :: StandPipeManifoldValve1 | |||||
logical :: StandPipeManifoldValve2 | |||||
logical :: StandPipeManifoldValve3 | |||||
logical :: StandPipeManifoldValve4 | |||||
logical :: StandPipeManifoldValve5 | |||||
logical :: StandPipeManifoldValve6 | |||||
logical :: StandPipeManifoldValve7 | |||||
logical :: StandPipeManifoldValve8 | |||||
logical :: StandPipeManifoldValve9 | |||||
logical :: StandPipeManifoldValve10 | |||||
logical :: StandPipeManifoldValve11 | |||||
logical :: StandPipeManifoldValve12 | |||||
logical :: StandPipeManifoldValve13 | |||||
logical :: StandPipeManifoldValve14 | |||||
logical :: StandPipeManifoldValve15 | |||||
! Output vars | |||||
real(8) :: StandPipeGauge1 | |||||
real(8) :: StandPipeGauge2 | |||||
contains | |||||
end module CStandPipeManifoldVariables |
@@ -0,0 +1,211 @@ | |||||
module CTopDrivePanel | |||||
use CTopDrivePanelVariables | |||||
use CLog3 | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
subroutine SetTopDriveTdsPowerState(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveTdsPowerState | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDriveTdsPowerState' :: SetTopDriveTdsPowerState | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
TopDriveTdsPowerState = v | |||||
#ifdef deb | |||||
call Log_3( 'TopDriveTdsPowerState=', TopDriveTdsPowerState) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTopDriveTorqueWrench(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveTorqueWrench | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDriveTorqueWrench' :: SetTopDriveTorqueWrench | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
TopDriveTorqueWrench = v | |||||
#ifdef deb | |||||
call Log_3( 'TopDriveTorqueWrench=', TopDriveTorqueWrench) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTopDriveDrillTorqueState(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveDrillTorqueState | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDriveDrillTorqueState' :: SetTopDriveDrillTorqueState | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
TopDriveDrillTorqueState = v | |||||
#ifdef deb | |||||
call Log_3( 'TopDriveDrillTorqueState=', TopDriveDrillTorqueState) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTopDriveLinkTiltState(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveLinkTiltState | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDriveLinkTiltState' :: SetTopDriveLinkTiltState | |||||
implicit none | |||||
integer, intent(in) :: v | |||||
TopDriveLinkTiltState = v | |||||
#ifdef deb | |||||
call Log_3( 'TopDriveLinkTiltState=', TopDriveLinkTiltState) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTopDriveIbop(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveIbop | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDriveIbop' :: SetTopDriveIbop | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
TopDriveIbop = v | |||||
#ifdef deb | |||||
call Log_3( 'TopDriveIbop=', TopDriveIbop) | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTopDriveTorqueLimitKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTopDriveTorqueLimitKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTopDriveTorqueLimitKnob' :: SetTopDriveTorqueLimitKnob | |||||
use CSimulationVariables, only: IsPortable | |||||
use CDrillingConsoleVariables, only: RTSwitch, RTTorqueLimitKnob | |||||
use CWarningsVariables, only: Activate_TopdriveRotaryTableConfilict | |||||
use CScaleRange | |||||
implicit none | |||||
real, intent(in) :: v | |||||
if (IsPortable) then | |||||
if(TopDriveTdsPowerState /= 0 .and. RTSwitch /= 0) call Activate_TopdriveRotaryTableConfilict() | |||||
if(TopDriveTdsPowerState /= 0 .and. RTSwitch == 0) then | |||||
RTTorqueLimitKnob = 0 | |||||
TopDriveTorqueLimitKnob = v | |||||
#ifdef deb | |||||
call Log_3( 'RTTorqueLimitKnob=', RTTorqueLimitKnob ) | |||||
call Log_3( 'TopDriveTorqueLimitKnob=', TopDriveTorqueLimitKnob ) | |||||
#endif | |||||
endif | |||||
if(TopDriveTdsPowerState == 0 .and. RTSwitch /= 0) then | |||||
TopDriveTorqueLimitKnob = 0 | |||||
RTTorqueLimitKnob = real(ScaleRange(v, 0.0, 10.0, 0.0, 6000.0), 8) | |||||
#ifdef deb | |||||
call Log_3( 'RTTorqueLimitKnob=', RTTorqueLimitKnob ) | |||||
call Log_3( 'TopDriveTorqueLimitKnob=', TopDriveTorqueLimitKnob ) | |||||
#endif | |||||
endif | |||||
else | |||||
TopDriveTorqueLimitKnob = v | |||||
#ifdef deb | |||||
call Log_3( 'TopDriveTorqueLimitKnob=', TopDriveTorqueLimitKnob) | |||||
#endif | |||||
endif | |||||
end subroutine | |||||
subroutine SetRpmKnob(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetRpmKnob | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetRpmKnob' :: SetRpmKnob | |||||
use CSimulationVariables, only: IsPortable | |||||
use CDrillingConsoleVariables, only: RTSwitch, RTThrottle | |||||
use CWarningsVariables, only: Activate_TopdriveRotaryTableConfilict | |||||
use CScaleRange | |||||
implicit none | |||||
real, intent(in) :: v | |||||
if (IsPortable) then | |||||
if(TopDriveTdsPowerState /= 0 .and. RTSwitch /= 0) call Activate_TopdriveRotaryTableConfilict() | |||||
if(TopDriveTdsPowerState /= 0 .and. RTSwitch == 0) then | |||||
RTThrottle = 0 | |||||
RpmKnob = v | |||||
#ifdef deb | |||||
call Log_3( 'RTThrottle=', RTThrottle ) | |||||
call Log_3( 'RpmKnob=', RpmKnob ) | |||||
#endif | |||||
endif | |||||
if(TopDriveTdsPowerState == 0 .and. RTSwitch /= 0) then | |||||
RpmKnob = 0 | |||||
RTThrottle = real(ScaleRange(v, 0.0, 965.0, 0.0, 250.0), 8) | |||||
#ifdef deb | |||||
call Log_3( 'RpmKnob=', RpmKnob ) | |||||
call Log_3( 'RTThrottle=', RTThrottle ) | |||||
#endif | |||||
endif | |||||
else | |||||
RpmKnob = v | |||||
endif | |||||
if (IsPortable) then | |||||
! | |||||
else | |||||
RpmKnob = v | |||||
#ifdef deb | |||||
call Log_3( 'RpmKnob=', RpmKnob ) | |||||
#endif | |||||
endif | |||||
end subroutine | |||||
! Output routines | |||||
integer function GetTopDriveOperationFaultLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveOperationFaultLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTopDriveOperationFaultLed' :: GetTopDriveOperationFaultLed | |||||
implicit none | |||||
GetTopDriveOperationFaultLed = TopDriveOperationFaultLed | |||||
!GetTopDriveOperationFaultLed = 1 | |||||
end function | |||||
integer function GetTopDriveTdsPowerLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveTdsPowerLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTopDriveTdsPowerLed' :: GetTopDriveTdsPowerLed | |||||
implicit none | |||||
GetTopDriveTdsPowerLed = TopDriveTdsPowerLed | |||||
!GetTopDriveTdsPowerLed = 1 | |||||
end function | |||||
integer function GetTopDriveTorqueWrenchLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveTorqueWrenchLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTopDriveTorqueWrenchLed' :: GetTopDriveTorqueWrenchLed | |||||
implicit none | |||||
GetTopDriveTorqueWrenchLed = TopDriveTorqueWrenchLed | |||||
!GetTopDriveTorqueWrenchLed = 1 | |||||
end function | |||||
integer function GetTopDriveLinkTiltLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveLinkTiltLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTopDriveLinkTiltLed' :: GetTopDriveLinkTiltLed | |||||
implicit none | |||||
GetTopDriveLinkTiltLed = TopDriveLinkTiltLed | |||||
!GetTopDriveLinkTiltLed = 1 | |||||
end function | |||||
integer function GetTopDriveIbopLed() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveIbopLed | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTopDriveIbopLed' :: GetTopDriveIbopLed | |||||
implicit none | |||||
GetTopDriveIbopLed = TopDriveIbopLed | |||||
!GetTopDriveIbopLed = 1 | |||||
end function | |||||
real function GetTopDriveTorqueGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveTorqueGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTopDriveTorqueGauge' :: GetTopDriveTorqueGauge | |||||
implicit none | |||||
GetTopDriveTorqueGauge = TopDriveTorqueGauge | |||||
!GetTopDriveTorqueGauge = 340 | |||||
end function | |||||
real function GetTopDriveTorqueLimitGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveTorqueLimitGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTopDriveTorqueLimitGauge' :: GetTopDriveTorqueLimitGauge | |||||
implicit none | |||||
GetTopDriveTorqueLimitGauge = TopDriveTorqueLimitGauge | |||||
!GetTopDriveTorqueLimitGauge = 442 | |||||
end function | |||||
real function GetTopDriveRpmGauge() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTopDriveRpmGauge | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTopDriveRpmGauge' :: GetTopDriveRpmGauge | |||||
implicit none | |||||
GetTopDriveRpmGauge = TopDriveRpmGauge | |||||
!GetTopDriveRpmGauge = 67 | |||||
end function | |||||
end module CTopDrivePanel |
@@ -0,0 +1,43 @@ | |||||
module CTopDrivePanelVariables | |||||
implicit none | |||||
public | |||||
! const | |||||
integer :: TdsPower_REV = 1 | |||||
integer :: TdsPower_OFF = 0 | |||||
integer :: TdsPower_FWD = -1 | |||||
integer :: TdsMu_TORQ = 1 | |||||
integer :: TdsMu_SPINE = 0 | |||||
integer :: TdsMu_DRILL = -1 | |||||
integer :: TdsLinkTilt_TILT = 1 | |||||
integer :: TdsLinkTilt_OFF = 0 | |||||
integer :: TdsLinkTilt_DRILL = -1 | |||||
integer :: LED_OFF = 0 | |||||
integer :: LED_ON = 1 | |||||
integer :: LED_BLINK = 2 | |||||
! Input vars | |||||
integer :: TopDriveTdsPowerState | |||||
logical :: TopDriveTorqueWrench | |||||
integer :: TopDriveDrillTorqueState | |||||
integer :: TopDriveLinkTiltState | |||||
logical :: TopDriveIbop | |||||
real :: TopDriveTorqueLimitKnob | |||||
real :: RpmKnob | |||||
! Output vars | |||||
integer :: TopDriveOperationFaultLed | |||||
integer :: TopDriveTdsPowerLed | |||||
integer :: TopDriveTorqueWrenchLed | |||||
integer :: TopDriveLinkTiltLed | |||||
integer :: TopDriveIbopLed | |||||
real :: TopDriveTorqueLimitGauge | |||||
real :: TopDriveTorqueGauge | |||||
real :: TopDriveRpmGauge | |||||
contains | |||||
end module CTopDrivePanelVariables |
@@ -0,0 +1,171 @@ | |||||
module CDrillWatch | |||||
use CDrillWatchVariables | |||||
!use CSimulationVariables | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
! Output routines | |||||
real(8) function GetDepth() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetDepth | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetDepth' :: GetDepth | |||||
implicit none | |||||
GetDepth = Depth | |||||
!GetDepth = Depth + 10 + SimulationTime | |||||
end function | |||||
real(8) function GetBitPosition() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetBitPosition | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetBitPosition' :: GetBitPosition | |||||
implicit none | |||||
GetBitPosition = BitPosition | |||||
!GetBitPosition = BitPosition + 20 + SimulationTime | |||||
end function | |||||
real(8) function GetHookLoadD() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetHookLoadD | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetHookLoadD' :: GetHookLoadD | |||||
implicit none | |||||
GetHookLoadD = HookLoad | |||||
!GetHookLoadD = HookLoad + 30 + SimulationTime | |||||
end function | |||||
real(8) function GetWeightOnBit() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetWeightOnBit | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetWeightOnBit' :: GetWeightOnBit | |||||
implicit none | |||||
GetWeightOnBit = WeightOnBit | |||||
!GetWeightOnBit = WeightOnBit + 40 + SimulationTime | |||||
end function | |||||
real(8) function GetRPM() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetRPM | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetRPM' :: GetRPM | |||||
implicit none | |||||
GetRPM = RPM | |||||
!GetRPM = RPM + 50 + SimulationTime | |||||
end function | |||||
real(8) function GetROP2() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetROP2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetROP2' :: GetROP2 | |||||
implicit none | |||||
GetROP2 = ROP | |||||
!GetROP2 = ROP + 60 + SimulationTime | |||||
end function | |||||
real(8) function GetTorque() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTorque | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTorque' :: GetTorque | |||||
implicit none | |||||
GetTorque = Torque | |||||
!GetTorque = Torque + 70 + SimulationTime | |||||
end function | |||||
real(8) function GetPumpPressureD() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPumpPressureD | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPumpPressureD' :: GetPumpPressureD | |||||
implicit none | |||||
GetPumpPressureD = PumpPressure | |||||
!GetPumpPressureD = PumpPressure + 80 + SimulationTime | |||||
end function | |||||
real(8) function GetSPM1() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetSPM1 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetSPM1' :: GetSPM1 | |||||
implicit none | |||||
GetSPM1 = SPM1 | |||||
!GetSPM1 = SPM1 + 90 + SimulationTime | |||||
end function | |||||
real(8) function GetSPM2() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetSPM2 | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetSPM2' :: GetSPM2 | |||||
implicit none | |||||
GetSPM2 = SPM2 | |||||
!GetSPM2 = SPM2 + 100 + SimulationTime | |||||
end function | |||||
! real(8) function GetSPM3() | |||||
!!DEC$ ATTRIBUTES DLLEXPORT :: GetSPM3 | |||||
!!DEC$ ATTRIBUTES ALIAS: 'GetSPM3' :: GetSPM3 | |||||
! implicit none | |||||
! GetSPM3 = SPM3 | |||||
!end function | |||||
real(8) function GetCasingPressureD() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetCasingPressureD | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetCasingPressureD' :: GetCasingPressureD | |||||
implicit none | |||||
GetCasingPressureD = CasingPressure | |||||
!GetCasingPressureD = CasingPressure + 110 + SimulationTime | |||||
end function | |||||
real(8) function GetPercentFlow() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPercentFlow | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPercentFlow' :: GetPercentFlow | |||||
implicit none | |||||
GetPercentFlow = PercentFlow | |||||
!GetPercentFlow = PercentFlow + 120 + SimulationTime | |||||
end function | |||||
real(8) function GetPitGainLose() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPitGainLose | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPitGainLose' :: GetPitGainLose | |||||
implicit none | |||||
GetPitGainLose = PitGainLose | |||||
!GetPitGainLose = PitGainLose + 130 + SimulationTime | |||||
end function | |||||
real(8) function GetPitVolume() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetPitVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetPitVolume' :: GetPitVolume | |||||
implicit none | |||||
GetPitVolume = PitVolume | |||||
!GetPitVolume = PitVolume + 140 + SimulationTime | |||||
end function | |||||
real(8) function GetKillMudVolume() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetKillMudVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetKillMudVolume' :: GetKillMudVolume | |||||
implicit none | |||||
GetKillMudVolume = KillMudVolume | |||||
!GetKillMudVolume = KillMudVolume + 150 + SimulationTime | |||||
end function | |||||
real(8) function GetTripTankVolume() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTripTankVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTripTankVolume' :: GetTripTankVolume | |||||
implicit none | |||||
GetTripTankVolume = TripTankVolume | |||||
!GetTripTankVolume = TripTankVolume + 160 + SimulationTime | |||||
end function | |||||
real(8) function GetMudWeightInD() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMudWeightInD | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMudWeightInD' :: GetMudWeightInD | |||||
implicit none | |||||
GetMudWeightInD = MudWeightIn | |||||
!GetMudWeightInD = MudWeightIn + 170 + SimulationTime | |||||
end function | |||||
real(8) function GetFillVolume() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetFillVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetFillVolume' :: GetFillVolume | |||||
implicit none | |||||
GetFillVolume = FillVolume | |||||
!GetFillVolume = FillVolume + 180 + SimulationTime | |||||
end function | |||||
real(8) function GetMudWeightOutD() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetMudWeightOutD | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetMudWeightOutD' :: GetMudWeightOutD | |||||
implicit none | |||||
GetMudWeightOutD = MudWeightOut | |||||
!GetMudWeightOutD = MudWeightOut + 190 + SimulationTime | |||||
end function | |||||
end module CDrillWatch |
@@ -0,0 +1,33 @@ | |||||
module CDrillWatchVariables | |||||
implicit none | |||||
public | |||||
! Input vars | |||||
! Output vars | |||||
real(8) :: Depth | |||||
real(8) :: BitPosition | |||||
real(8) :: HookLoad | |||||
real(8) :: WeightOnBit | |||||
real(8) :: RPM | |||||
real(8) :: ROP | |||||
real(8) :: Torque | |||||
real(8) :: PumpPressure | |||||
real(8) :: SPM1 | |||||
real(8) :: SPM2 | |||||
!real(8) :: SPM3 | |||||
real(8) :: CasingPressure | |||||
real(8) :: PercentFlow | |||||
real(8) :: PitGainLose | |||||
real(8) :: PitVolume | |||||
real(8) :: KillMudVolume | |||||
real(8) :: TripTankVolume | |||||
real(8) :: MudWeightIn | |||||
real(8) :: FillVolume | |||||
real(8) :: MudWeightOut | |||||
contains | |||||
end module CDrillWatchVariables |
@@ -0,0 +1,137 @@ | |||||
module CArrangement | |||||
implicit none | |||||
public | |||||
integer, parameter :: Normal = 0 | |||||
integer, parameter :: Relation = 1 | |||||
integer, parameter :: Input = 2 | |||||
integer, parameter :: Output = 3 | |||||
integer, parameter :: InputOutput = 4 | |||||
type, public :: Arrangement | |||||
integer, allocatable :: Adjacent(:) !adjacent valves that is connected to this valve | |||||
logical :: Status !valve status ... open/close ... true/false | |||||
integer :: ValveType ! Normal/Input/Output/InputOutput | |||||
integer :: Number | |||||
logical :: IsTraversed | |||||
contains | |||||
procedure :: Init => Init | |||||
procedure :: IsConnectedTo => IsConnectedTo | |||||
procedure :: IsSource => IsSource | |||||
procedure :: Length => Length | |||||
procedure :: AdjacentTo => AdjacentTo | |||||
procedure :: RemoveAdjacent => RemoveAdjacent | |||||
end type Arrangement | |||||
contains | |||||
subroutine Init(this, value) | |||||
implicit none | |||||
class(Arrangement), intent(inout) :: this | |||||
integer, intent(in) :: value | |||||
if(allocated(this%Adjacent)) deallocate(this%Adjacent) | |||||
this%Status = .false. | |||||
this%IsTraversed = .false. | |||||
this%ValveType = Normal | |||||
this%Number = value | |||||
end subroutine | |||||
integer function Length(this) | |||||
implicit none | |||||
class(Arrangement), intent(in) :: this | |||||
if(allocated(this%Adjacent)) then | |||||
Length = size(this%Adjacent) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
subroutine AdjacentTo(this, value) | |||||
implicit none | |||||
class(Arrangement), intent(inout) :: this | |||||
integer, intent(in) :: value | |||||
integer, allocatable :: tempArr(:) | |||||
integer :: i, isize | |||||
if(allocated(this%Adjacent)) then | |||||
isize = size(this%Adjacent) | |||||
! check to see if already AdjacentTo that valve# | |||||
do i=1,isize | |||||
if(this%Adjacent(i)==value) return | |||||
end do | |||||
! if value is a new entry then add it to the collection | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Adjacent(i) | |||||
end do | |||||
tempArr(isize+1) = value | |||||
deallocate(this%Adjacent) | |||||
call move_alloc(tempArr, this%Adjacent) | |||||
else | |||||
allocate(this%Adjacent(1)) | |||||
this%Adjacent(1) = value | |||||
end if | |||||
end subroutine | |||||
logical function IsConnectedTo(this, value) | |||||
implicit none | |||||
class(Arrangement), intent(in) :: this | |||||
integer, intent(in) :: value | |||||
if(.not.allocated(this%Adjacent)) then | |||||
IsConnectedTo = .false. | |||||
return | |||||
endif | |||||
IsConnectedTo = any(this%Adjacent == value) | |||||
return | |||||
end function | |||||
logical function IsSource(this) | |||||
implicit none | |||||
class(Arrangement), intent(in) :: this | |||||
IsSource = this%ValveType > Relation | |||||
end function | |||||
subroutine RemoveAdjacent(this, value) | |||||
implicit none | |||||
class(Arrangement), intent(inout) :: this | |||||
integer, intent(in) :: value | |||||
integer, allocatable :: tempArr(:) | |||||
integer :: i, index, isize | |||||
logical :: found | |||||
if(.not.allocated(this%Adjacent))return | |||||
index = -1 | |||||
do i=1, size(this%Adjacent) | |||||
if(this%Adjacent(i)==value) then | |||||
index = i | |||||
exit | |||||
end if | |||||
end do | |||||
if(index <= 0 .or. index > size(this%Adjacent)) return | |||||
allocate(tempArr(size(this%Adjacent)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Adjacent) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Adjacent(i) | |||||
else | |||||
tempArr(i) = this%Adjacent(i) | |||||
endif | |||||
end do | |||||
deallocate(this%Adjacent) | |||||
call move_alloc(tempArr, this%Adjacent) | |||||
end subroutine | |||||
end module CArrangement |
@@ -0,0 +1,231 @@ | |||||
module CPath | |||||
use CLog5 | |||||
implicit none | |||||
public | |||||
type, public :: Path | |||||
integer, allocatable :: Valves(:) | |||||
logical :: IsClosed | |||||
contains | |||||
procedure :: Display => Display | |||||
procedure :: DisplayWrite => DisplayWrite | |||||
procedure :: First => First | |||||
procedure :: Last => Last | |||||
procedure :: Length => Length | |||||
procedure :: Get => Get | |||||
procedure :: Add => Add | |||||
procedure :: Remove => Remove | |||||
procedure :: Purge => Purge | |||||
procedure :: Copy => Copy | |||||
procedure :: MakeNull => MakeNull | |||||
procedure :: IsNull => IsNull | |||||
procedure :: Equal => Equal | |||||
procedure :: Find => Find | |||||
end type Path | |||||
contains | |||||
subroutine DisplayWrite(this) | |||||
implicit none | |||||
class(Path), intent(in) :: this | |||||
character(len=512) :: temp | |||||
integer :: i | |||||
if(allocated(this%valves)) then | |||||
write(temp, '(a1,i0,a3,i0,a4,9999(g0))') '(', this%First(), '<=>', this%Last(), ') : ', (this%Valves(i), ", ",i=1,size(this%Valves)) | |||||
write(*,*) temp | |||||
end if | |||||
end subroutine | |||||
subroutine Display(this) | |||||
implicit none | |||||
class(Path), intent(in) :: this | |||||
character(len=512) :: temp | |||||
integer :: i | |||||
if(allocated(this%valves)) then | |||||
write(temp, '(a1,i0,a3,i0,a4,9999(g0))') '(', this%First(), '<=>', this%Last(), ') : ', (this%Valves(i), ", ",i=1,size(this%Valves)) | |||||
call Log_5(temp) | |||||
end if | |||||
end subroutine | |||||
integer function First(this) | |||||
implicit none | |||||
class(Path), intent(in) :: this | |||||
if(allocated(this%Valves) .and. size(this%Valves) > 0) then | |||||
First = this%Valves(1) | |||||
return | |||||
end if | |||||
First = 0 | |||||
end function | |||||
integer function Last(this) | |||||
implicit none | |||||
class(Path), intent(in) :: this | |||||
if(allocated(this%Valves) .and. size(this%Valves) > 0) then | |||||
Last = this%Valves(size(this%Valves)) | |||||
return | |||||
end if | |||||
Last = 0 | |||||
end function | |||||
integer function Length(this) | |||||
implicit none | |||||
class(Path), intent(in) :: this | |||||
if(allocated(this%Valves)) then | |||||
Length = size(this%Valves) | |||||
return | |||||
end if | |||||
Length = 0 | |||||
end function | |||||
integer function Get(this, index) | |||||
implicit none | |||||
class(Path), intent(in) :: this | |||||
integer, intent(in) :: index | |||||
if(allocated(this%Valves)) then | |||||
if(index < 1 .or. index > size(this%Valves)) then | |||||
Get = -1 | |||||
return | |||||
endif | |||||
Get = this%Valves(index) | |||||
return | |||||
end if | |||||
get = -1 | |||||
end function | |||||
subroutine Add(this, value) | |||||
implicit none | |||||
class(Path), intent(inout) :: this | |||||
integer, allocatable :: tempArr(:) | |||||
integer, intent(in) :: value | |||||
integer :: i, isize | |||||
if(allocated(this%Valves)) then | |||||
isize = size(this%Valves) | |||||
allocate(tempArr(isize+1)) | |||||
do i=1,isize | |||||
tempArr(i) = this%Valves(i) | |||||
end do | |||||
tempArr(isize+1) = value | |||||
deallocate(this%Valves) | |||||
call move_alloc(tempArr, this%Valves) | |||||
else | |||||
allocate(this%Valves(1)) | |||||
this%Valves(1) = value | |||||
end if | |||||
end subroutine | |||||
subroutine Remove(this, index) | |||||
implicit none | |||||
class(Path), intent(inout) :: this | |||||
integer, intent(in) :: index | |||||
integer, allocatable :: tempArr(:) | |||||
integer :: i | |||||
logical :: found | |||||
if(index <= 0 .or. index > size(this%Valves)) return | |||||
if(.not.allocated(this%Valves))return | |||||
allocate(tempArr(size(this%Valves)-1)) | |||||
found = .false. | |||||
do i=1, size(this%Valves) | |||||
if(i==index) then | |||||
found = .true. | |||||
cycle | |||||
end if | |||||
if(found) then | |||||
tempArr(i-1) = this%Valves(i) | |||||
else | |||||
tempArr(i) = this%Valves(i) | |||||
endif | |||||
end do | |||||
deallocate(this%valves) | |||||
call move_alloc(tempArr, this%valves) | |||||
end subroutine | |||||
subroutine Purge(this, min, max) | |||||
implicit none | |||||
class(Path), intent(inout) :: this | |||||
integer, intent(in) :: min | |||||
integer, intent(in) :: max | |||||
integer :: i | |||||
i = 1 | |||||
do | |||||
! | |||||
if(this%Valves(i) >= min .and. this%Valves(i) <= max) then | |||||
call this%Remove(i) | |||||
else | |||||
i = i + 1 | |||||
endif | |||||
if(i > this%Length()) exit | |||||
enddo | |||||
end subroutine | |||||
subroutine Copy(this, from) | |||||
implicit none | |||||
class(Path), intent(inout) :: this | |||||
class(Path), intent(in) :: from | |||||
if(allocated(from%Valves)) then | |||||
if(allocated(this%Valves)) deallocate(this%Valves) | |||||
allocate(this%Valves(size(from%Valves))) | |||||
this%Valves(:) = from%Valves(:) | |||||
end if | |||||
end subroutine | |||||
subroutine MakeNull(this) | |||||
implicit none | |||||
class(Path), intent(inout) :: this | |||||
if(allocated(this%Valves)) deallocate(this%Valves) | |||||
end subroutine | |||||
logical function IsNull(this) | |||||
implicit none | |||||
class(Path), intent(in) :: this | |||||
IsNull = .not.allocated(this%Valves) | |||||
return | |||||
end function | |||||
logical function Equal(this, otherPath) | |||||
implicit none | |||||
class(Path), intent(inout) :: this | |||||
class(Path), intent(in) :: otherPath | |||||
integer :: i, sizeThis, sizeOtherPath | |||||
sizeThis = size(this%Valves) | |||||
sizeOtherPath = size(otherPath%Valves) | |||||
if(sizeThis /= sizeOtherPath) then | |||||
Equal = .false. | |||||
return | |||||
end if | |||||
do i = 1, sizeThis | |||||
if(this%Valves(i) /= otherPath%Valves(i)) then | |||||
Equal = .false. | |||||
return | |||||
end if | |||||
end do | |||||
Equal = .true. | |||||
return | |||||
end function | |||||
logical function Find(this, value) | |||||
implicit none | |||||
class(Path), intent(in) :: this | |||||
integer, intent(in) :: value | |||||
if(allocated(this%Valves)) then | |||||
Find = any(this%Valves == value) | |||||
return | |||||
end if | |||||
Find = .false. | |||||
end function | |||||
end module CPath |
@@ -0,0 +1,12 @@ | |||||
module CPathChangeEvents | |||||
use CIntegerArrayEventHandlerCollection | |||||
use CVoidEventHandlerCollection | |||||
implicit none | |||||
public | |||||
type(VoidEventHandlerCollection) :: BeforeTraverse | |||||
type(VoidEventHandlerCollection) :: AfterTraverse | |||||
type(IntegerArrayEventHandlerCollection) :: OnPathOpen | |||||
contains | |||||
end module CPathChangeEvents |
@@ -0,0 +1,42 @@ | |||||
module CStack | |||||
use CPath | |||||
implicit none | |||||
public | |||||
type, public :: Stack | |||||
type(Path) :: List | |||||
contains | |||||
procedure :: Clear => Clear | |||||
procedure :: Push => Push | |||||
procedure :: Pop => Pop | |||||
procedure :: DoesHave => DoesHave | |||||
end type Stack | |||||
contains | |||||
subroutine Clear(this) | |||||
implicit none | |||||
class(Stack), intent(inout) :: this | |||||
call this%List%MakeNull() | |||||
end subroutine | |||||
subroutine Push(this, value) | |||||
implicit none | |||||
class(Stack), intent(inout) :: this | |||||
integer, intent(in) :: value | |||||
call this%List%Add(value) | |||||
end subroutine | |||||
subroutine Pop(this) | |||||
implicit none | |||||
class(Stack), intent(inout) :: this | |||||
call this%List%Remove(this%List%Length()) | |||||
end subroutine | |||||
logical function DoesHave(this, value) | |||||
implicit none | |||||
class(Stack), intent(in) :: this | |||||
integer, intent(in) :: value | |||||
DoesHave = this%List%Find(value) | |||||
end function | |||||
end module CStack |
@@ -0,0 +1,252 @@ | |||||
module CTanks | |||||
use CTanksVariables | |||||
use CSimulationVariables | |||||
use CManifolds | |||||
implicit none | |||||
public | |||||
contains | |||||
! Input routines | |||||
subroutine SetWaterRate(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetWaterRate | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetWaterRate' :: SetWaterRate | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
WaterRate = v | |||||
#ifdef deb | |||||
print*, 'WaterRate=', WaterRate | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCementTankVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementTankVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementTankVolume' :: SetCementTankVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementTankVolume = v | |||||
#ifdef deb | |||||
print*, 'CementTankVolume=', CementTankVolume | |||||
#endif | |||||
end subroutine | |||||
subroutine SetCementTankDensity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetCementTankDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetCementTankDensity' :: SetCementTankDensity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
CementTankDensity = v | |||||
#ifdef deb | |||||
print*, 'CementTankDensity=', CementTankDensity | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTripTankVolume(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripTankVolume | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripTankVolume' :: SetTripTankVolume | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TripTankVolume = v | |||||
#ifdef deb | |||||
print*, 'TripTankVolume=', TripTankVolume | |||||
#endif | |||||
end subroutine | |||||
subroutine SetTripTankDensity(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetTripTankDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetTripTankDensity' :: SetTripTankDensity | |||||
implicit none | |||||
real*8, intent(in) :: v | |||||
TripTankDensity = v | |||||
#ifdef deb | |||||
print*, 'TripTankDensity=', TripTankDensity | |||||
#endif | |||||
end subroutine | |||||
! subroutine SetManualPumpPowerT(v) | |||||
! !DEC$ ATTRIBUTES DLLEXPORT :: SetManualPumpPowerT | |||||
! !DEC$ ATTRIBUTES ALIAS: 'SetManualPumpPowerT' :: SetManualPumpPowerT | |||||
! implicit none | |||||
! logical, intent(in) :: v | |||||
! ManualPumpPower = v | |||||
! call ChangeValve(43, v) | |||||
!#ifdef deb | |||||
! print*, 'ManualPumpPowerT=', ManualPumpPower | |||||
!#endif | |||||
! end subroutine | |||||
subroutine SetValve1T(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve1T | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve1T' :: SetValve1T | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve1 = v | |||||
call ChangeValve(40, v) | |||||
#ifdef deb | |||||
print*, 'Valve1T=', Valve1 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve2T(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve2T | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve2T' :: SetValve2T | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve2 = v | |||||
call ChangeValve(41, v) | |||||
#ifdef deb | |||||
print*, 'Valve2T=', Valve2 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve3T(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve3T | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve3T' :: SetValve3T | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve3 = v | |||||
call ChangeValve(45, v) | |||||
#ifdef deb | |||||
print*, 'Valve3T=', Valve3 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve4T(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve4T | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve4T' :: SetValve4T | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve4 = v | |||||
call ChangeValve(58, v) | |||||
#ifdef deb | |||||
print*, 'Valve4T=', Valve4 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve5T(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve5T | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve5T' :: SetValve5T | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve5 = v | |||||
call ChangeValve(42, v) | |||||
#ifdef deb | |||||
print*, 'Valve5T=', Valve5 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve6(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve6 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve6' :: SetValve6 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve6 = v | |||||
call ChangeValve(38, v) | |||||
!WRITE (*,*) ' valve 38 ', v | |||||
#ifdef deb | |||||
print*, 'Valve6=', Valve6 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve7(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve7 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve7' :: SetValve7 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve7 = v | |||||
call ChangeValve(59, v) | |||||
#ifdef deb | |||||
print*, 'Valve7=', Valve7 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve8(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve8 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve8' :: SetValve8 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve8 = v | |||||
call ChangeValve(39, v) | |||||
#ifdef deb | |||||
print*, 'Valve8=', Valve8 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve9(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve9 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve9' :: SetValve9 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve9 = v | |||||
call ChangeValve(36, v) | |||||
!WRITE (*,*) ' valve 36 ', v | |||||
#ifdef deb | |||||
print*, 'Valve9=', Valve9 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve10(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve10 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve10' :: SetValve10 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve10 = v | |||||
call ChangeValve(37, v) | |||||
#ifdef deb | |||||
print*, 'Valve10=', Valve10 | |||||
#endif | |||||
end subroutine | |||||
subroutine SetValve11(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetValve11 | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetValve11' :: SetValve11 | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
Valve11 = v | |||||
call ChangeValve(44, v) | |||||
#ifdef deb | |||||
print*, 'Valve11=', Valve11 | |||||
#endif | |||||
end subroutine | |||||
! Output routines | |||||
real(8) function GetTripTankVolumeT() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTripTankVolumeT | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTripTankVolumeT' :: GetTripTankVolumeT | |||||
implicit none | |||||
GetTripTankVolumeT = TripTankVolume | |||||
!GetTripTankVolumeT = 50.0 + SimulationTime | |||||
end function | |||||
real(8) function GetTripTankDensity() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetTripTankDensity | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetTripTankDensity' :: GetTripTankDensity | |||||
implicit none | |||||
GetTripTankDensity = TripTankDensity | |||||
!GetTripTankDensity = 13.0 + SimulationTime | |||||
end function | |||||
logical function GetManualPumpPowerT() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: GetManualPumpPowerT | |||||
!DEC$ ATTRIBUTES ALIAS: 'GetManualPumpPowerT' :: GetManualPumpPowerT | |||||
implicit none | |||||
GetManualPumpPowerT = ManualPumpPower | |||||
!GetManualPumpPowerT = .true. | |||||
end function | |||||
end module CTanks |
@@ -0,0 +1,41 @@ | |||||
module CTanksVariables | |||||
implicit none | |||||
public | |||||
! Input vars | |||||
real(8) :: WaterRate | |||||
real(8) :: CementTankVolume | |||||
real(8) :: CementTankDensity | |||||
real(8) :: TripTankVolume | |||||
real(8) :: TripTankDensity | |||||
logical :: ManualPumpPower | |||||
logical :: Valve1 | |||||
logical :: Valve2 | |||||
logical :: Valve3 | |||||
logical :: Valve4 | |||||
logical :: Valve5 | |||||
logical :: Valve6 | |||||
logical :: Valve7 | |||||
logical :: Valve8 | |||||
logical :: Valve9 | |||||
logical :: Valve10 | |||||
logical :: Valve11 | |||||
! Output vars | |||||
contains | |||||
subroutine Set_ManualPumpPower(v) | |||||
use CManifolds, only:ChangeValve | |||||
implicit none | |||||
logical, intent(in) :: v | |||||
ManualPumpPower = v | |||||
call ChangeValve(43, v) | |||||
#ifdef deb | |||||
print*, 'ManualPumpPower=', ManualPumpPower | |||||
#endif | |||||
end subroutine | |||||
end module CTanksVariables |
@@ -0,0 +1,303 @@ | |||||
module CError | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
interface Error | |||||
module procedure :: Error1, Error2, Error3, Error4, Error5 | |||||
end interface | |||||
interface ErrorStop | |||||
module procedure :: ErrorStop1, ErrorStop2, ErrorStop3, ErrorStop4, ErrorStop5 | |||||
end interface | |||||
procedure (ActionString), pointer :: ErrorMessagePtr | |||||
procedure (ActionStringInt), pointer :: ErrorMessageIntPtr | |||||
procedure (ActionStringFloat), pointer :: ErrorMessageFloatPtr | |||||
procedure (ActionStringDouble), pointer :: ErrorMessageDoublePtr | |||||
procedure (ActionStringBool), pointer :: ErrorMessageBoolPtr | |||||
procedure (ActionString), pointer :: ErrorStopPtr | |||||
procedure (ActionStringInt), pointer :: ErrorStopIntPtr | |||||
procedure (ActionStringFloat), pointer :: ErrorStopFloatPtr | |||||
procedure (ActionStringDouble), pointer :: ErrorStopDoublePtr | |||||
procedure (ActionStringBool), pointer :: ErrorStopBoolPtr | |||||
contains | |||||
subroutine Error1(message) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
if(associated(ErrorMessagePtr)) call ErrorMessagePtr(message) | |||||
end subroutine | |||||
subroutine Error2(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
integer, intent(in) :: value | |||||
!character(len=256) :: temp | |||||
!temp(:)=' ' | |||||
!write(temp,*) value | |||||
!if(associated(ErrorMessagePtr)) call ErrorMessagePtr(trim(message//' '//adjustl(temp))) | |||||
if(associated(ErrorMessageIntPtr)) call ErrorMessageIntPtr(message, value) | |||||
end subroutine | |||||
subroutine Error3(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real, intent(in) :: value | |||||
!character(len=256) :: temp | |||||
!temp(:)=' ' | |||||
!write(temp,*) value | |||||
!if(associated(ErrorMessagePtr)) call ErrorMessagePtr(trim(message//' '//adjustl(temp))) | |||||
if(associated(ErrorMessageFloatPtr)) call ErrorMessageFloatPtr(message, value) | |||||
end subroutine | |||||
subroutine Error4(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real(8), intent(in) :: value | |||||
!character(len=256) :: temp | |||||
!temp(:)=' ' | |||||
!write(temp,*) value | |||||
!if(associated(ErrorMessagePtr)) call ErrorMessagePtr(trim(message//' '//adjustl(temp))) | |||||
if(associated(ErrorMessageDoublePtr)) call ErrorMessageDoublePtr(message, value) | |||||
end subroutine | |||||
subroutine Error5(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
logical, intent(in) :: value | |||||
!if(value) then | |||||
! if(associated(ErrorMessagePtr)) call ErrorMessagePtr(message//' '//'TRUE') | |||||
!else | |||||
! if(associated(ErrorMessagePtr)) call ErrorMessagePtr(message//' '//'FALSE') | |||||
!endif | |||||
if(associated(ErrorMessageBoolPtr)) call ErrorMessageBoolPtr(message, value) | |||||
end subroutine | |||||
subroutine ErrorStop1(message) | |||||
!use ifmt | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
if(associated(ErrorStopPtr)) then | |||||
call ErrorStopPtr(message) | |||||
! call ExitThread(0) | |||||
end if | |||||
end subroutine | |||||
subroutine ErrorStop2(message, value) | |||||
!use ifmt | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
integer, intent(in) :: value | |||||
!character(len=256) :: temp | |||||
!temp(:)=' ' | |||||
!write(temp,*) value | |||||
!if(associated(ErrorStopPtr)) then | |||||
! call ErrorStopPtr(trim(message//' '//adjustl(temp))) | |||||
! ! call ExitThread(0) | |||||
!end if | |||||
if(associated(ErrorStopIntPtr)) then | |||||
call ErrorStopIntPtr(message, value) | |||||
! call ExitThread(0) | |||||
end if | |||||
end subroutine | |||||
subroutine ErrorStop3(message, value) | |||||
!use ifmt | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real, intent(in) :: value | |||||
!character(len=256) :: temp | |||||
!temp(:)=' ' | |||||
!write(temp,*) value | |||||
!if(associated(ErrorStopPtr)) then | |||||
! call ErrorStopPtr(trim(message//' '//adjustl(temp))) | |||||
! ! call ExitThread(0) | |||||
!end if | |||||
if(associated(ErrorStopFloatPtr)) then | |||||
call ErrorStopFloatPtr(message, value) | |||||
! ! call ExitThread(0) | |||||
end if | |||||
end subroutine | |||||
subroutine ErrorStop4(message, value) | |||||
! use ifmt | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real(8), intent(in) :: value | |||||
!character(len=256) :: temp | |||||
!temp(:)=' ' | |||||
!write(temp,*) value | |||||
!if(associated(ErrorStopPtr)) then | |||||
! call ErrorStopPtr(trim(message//' '//adjustl(temp))) | |||||
! ! call ExitThread(0) | |||||
!end if | |||||
if(associated(ErrorStopDoublePtr)) then | |||||
call ErrorStopDoublePtr(message, value) | |||||
! ! call ExitThread(0) | |||||
end if | |||||
end subroutine | |||||
subroutine ErrorStop5(message, value) | |||||
!use ifmt | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
logical, intent(in) :: value | |||||
!if(value) then | |||||
! if(associated(ErrorStopPtr)) then | |||||
! call ErrorStopPtr(message//' '//'TRUE') | |||||
! ! ! call ExitThread(0) | |||||
! end if | |||||
!else | |||||
! if(associated(ErrorStopPtr)) then | |||||
! call ErrorStopPtr(message//' '//'FALSE') | |||||
! ! ! call ExitThread(0) | |||||
! end if | |||||
!endif | |||||
if(associated(ErrorStopBoolPtr)) then | |||||
call ErrorStopBoolPtr(message, value) | |||||
! call ExitThread(0) | |||||
end if | |||||
end subroutine | |||||
subroutine SubscribeErrorMessage(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorMessage | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorMessage' :: SubscribeErrorMessage | |||||
implicit none | |||||
procedure (ActionString) :: a | |||||
ErrorMessagePtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorMessageInt(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorMessageInt | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorMessageInt' :: SubscribeErrorMessageInt | |||||
implicit none | |||||
procedure (ActionStringInt) :: a | |||||
ErrorMessageIntPtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorMessageFloat(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorMessageFloat | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorMessageFloat' :: SubscribeErrorMessageFloat | |||||
implicit none | |||||
procedure (ActionStringFloat) :: a | |||||
ErrorMessageFloatPtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorMessageDouble(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorMessageDouble | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorMessageDouble' :: SubscribeErrorMessageDouble | |||||
implicit none | |||||
procedure (ActionStringDouble) :: a | |||||
ErrorMessageDoublePtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorMessageBool(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorMessageBool | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorMessageBool' :: SubscribeErrorMessageBool | |||||
implicit none | |||||
procedure (ActionStringBool) :: a | |||||
ErrorMessageBoolPtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorStop(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorStop | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorStop' :: SubscribeErrorStop | |||||
implicit none | |||||
procedure (ActionString) :: a | |||||
ErrorStopPtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorStopInt(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorStopInt | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorStopInt' :: SubscribeErrorStopInt | |||||
implicit none | |||||
procedure (ActionStringInt) :: a | |||||
ErrorStopIntPtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorStopFloat(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorStopFloat | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorStopFloat' :: SubscribeErrorStopFloat | |||||
implicit none | |||||
procedure (ActionStringFloat) :: a | |||||
ErrorStopFloatPtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorStopDouble(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorStopDouble | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorStopDouble' :: SubscribeErrorStopDouble | |||||
implicit none | |||||
procedure (ActionStringDouble) :: a | |||||
ErrorStopDoublePtr => a | |||||
end subroutine | |||||
subroutine SubscribeErrorStopBool(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeErrorStopBool | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeErrorStopBool' :: SubscribeErrorStopBool | |||||
implicit none | |||||
procedure (ActionStringBool) :: a | |||||
ErrorStopBoolPtr => a | |||||
end subroutine | |||||
end module CError |
@@ -0,0 +1,113 @@ | |||||
module CLog1 | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
interface Log_1 | |||||
module procedure :: Log1Log1, Log1Log2, Log1Log3, Log1Log4, Log1Log5 | |||||
end interface | |||||
procedure (ActionString), pointer :: Log1MsgPtr | |||||
procedure (ActionStringInt), pointer :: Log1MsgIntPtr | |||||
procedure (ActionStringFloat), pointer :: Log1MsgFloatPtr | |||||
procedure (ActionStringDouble), pointer :: Log1MsgDoublePtr | |||||
procedure (ActionStringBool), pointer :: Log1MsgBoolPtr | |||||
contains | |||||
subroutine Log1Log1(message) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
#ifdef Log1 | |||||
if(associated(Log1MsgPtr)) call Log1MsgPtr(message) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log1Log2(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
integer, intent(in) :: value | |||||
#ifdef Log1 | |||||
if(associated(Log1MsgIntPtr)) call Log1MsgIntPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log1Log3(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real, intent(in) :: value | |||||
#ifdef Log1 | |||||
if(associated(Log1MsgFloatPtr)) call Log1MsgFloatPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log1Log4(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real(8), intent(in) :: value | |||||
#ifdef Log1 | |||||
if(associated(Log1MsgDoublePtr)) call Log1MsgDoublePtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log1Log5(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
logical, intent(in) :: value | |||||
#ifdef Log1 | |||||
if(associated(Log1MsgBoolPtr)) call Log1MsgBoolPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine SubscribeLog1Message(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1Message | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1Message' :: SubscribeLog1Message | |||||
implicit none | |||||
procedure (ActionString) :: a | |||||
Log1MsgPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog1MsgInt(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1MsgInt | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1MsgInt' :: SubscribeLog1MsgInt | |||||
implicit none | |||||
procedure (ActionStringInt) :: a | |||||
Log1MsgIntPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog1MsgFloat(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1MsgFloat | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1MsgFloat' :: SubscribeLog1MsgFloat | |||||
implicit none | |||||
procedure (ActionStringFloat) :: a | |||||
Log1MsgFloatPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog1MsgDouble(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1MsgDouble | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1MsgDouble' :: SubscribeLog1MsgDouble | |||||
implicit none | |||||
procedure (ActionStringDouble) :: a | |||||
Log1MsgDoublePtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog1MsgBool(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog1MsgBool | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog1MsgBool' :: SubscribeLog1MsgBool | |||||
implicit none | |||||
procedure (ActionStringBool) :: a | |||||
Log1MsgBoolPtr => a | |||||
end subroutine | |||||
end module CLog1 |
@@ -0,0 +1,113 @@ | |||||
module CLog2 | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
interface Log_2 | |||||
module procedure :: Log2Log1, Log2Log2, Log2Log3, Log2Log4, Log2Log5 | |||||
end interface | |||||
procedure (ActionString), pointer :: Log2MsgPtr | |||||
procedure (ActionStringInt), pointer :: Log2MsgIntPtr | |||||
procedure (ActionStringFloat), pointer :: Log2MsgFloatPtr | |||||
procedure (ActionStringDouble), pointer :: Log2MsgDoublePtr | |||||
procedure (ActionStringBool), pointer :: Log2MsgBoolPtr | |||||
contains | |||||
subroutine Log2Log1(message) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
#ifdef Log2 | |||||
if(associated(Log2MsgPtr)) call Log2MsgPtr(message) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log2Log2(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
integer, intent(in) :: value | |||||
#ifdef Log2 | |||||
if(associated(Log2MsgIntPtr)) call Log2MsgIntPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log2Log3(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real, intent(in) :: value | |||||
#ifdef Log2 | |||||
if(associated(Log2MsgFloatPtr)) call Log2MsgFloatPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log2Log4(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real(8), intent(in) :: value | |||||
#ifdef Log2 | |||||
if(associated(Log2MsgDoublePtr)) call Log2MsgDoublePtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log2Log5(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
logical, intent(in) :: value | |||||
#ifdef Log2 | |||||
if(associated(Log2MsgBoolPtr)) call Log2MsgBoolPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine SubscribeLog2Message(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog2Message | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog2Message' :: SubscribeLog2Message | |||||
implicit none | |||||
procedure (ActionString) :: a | |||||
Log2MsgPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog2MsgInt(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog2MsgInt | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog2MsgInt' :: SubscribeLog2MsgInt | |||||
implicit none | |||||
procedure (ActionStringInt) :: a | |||||
Log2MsgIntPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog2MsgFloat(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog2MsgFloat | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog2MsgFloat' :: SubscribeLog2MsgFloat | |||||
implicit none | |||||
procedure (ActionStringFloat) :: a | |||||
Log2MsgFloatPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog2MsgDouble(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog2MsgDouble | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog2MsgDouble' :: SubscribeLog2MsgDouble | |||||
implicit none | |||||
procedure (ActionStringDouble) :: a | |||||
Log2MsgDoublePtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog2MsgBool(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog2MsgBool | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog2MsgBool' :: SubscribeLog2MsgBool | |||||
implicit none | |||||
procedure (ActionStringBool) :: a | |||||
Log2MsgBoolPtr => a | |||||
end subroutine | |||||
end module CLog2 |
@@ -0,0 +1,113 @@ | |||||
module CLog3 | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
interface Log_3 | |||||
module procedure :: Log3Log1, Log3Log2, Log3Log3, Log3Log4, Log3Log5 | |||||
end interface | |||||
procedure (ActionString), pointer :: Log3MsgPtr | |||||
procedure (ActionStringInt), pointer :: Log3MsgIntPtr | |||||
procedure (ActionStringFloat), pointer :: Log3MsgFloatPtr | |||||
procedure (ActionStringDouble), pointer :: Log3MsgDoublePtr | |||||
procedure (ActionStringBool), pointer :: Log3MsgBoolPtr | |||||
contains | |||||
subroutine Log3Log1(message) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
#ifdef Log3 | |||||
if(associated(Log3MsgPtr)) call Log3MsgPtr(message) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log3Log2(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
integer, intent(in) :: value | |||||
#ifdef Log3 | |||||
if(associated(Log3MsgIntPtr)) call Log3MsgIntPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log3Log3(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real, intent(in) :: value | |||||
#ifdef Log3 | |||||
if(associated(Log3MsgFloatPtr)) call Log3MsgFloatPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log3Log4(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real(8), intent(in) :: value | |||||
#ifdef Log3 | |||||
if(associated(Log3MsgDoublePtr)) call Log3MsgDoublePtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log3Log5(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
logical, intent(in) :: value | |||||
#ifdef Log3 | |||||
if(associated(Log3MsgBoolPtr)) call Log3MsgBoolPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine SubscribeLog3Message(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3Message | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3Message' :: SubscribeLog3Message | |||||
implicit none | |||||
procedure (ActionString) :: a | |||||
Log3MsgPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog3MsgInt(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3MsgInt | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3MsgInt' :: SubscribeLog3MsgInt | |||||
implicit none | |||||
procedure (ActionStringInt) :: a | |||||
Log3MsgIntPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog3MsgFloat(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3MsgFloat | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3MsgFloat' :: SubscribeLog3MsgFloat | |||||
implicit none | |||||
procedure (ActionStringFloat) :: a | |||||
Log3MsgFloatPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog3MsgDouble(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3MsgDouble | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3MsgDouble' :: SubscribeLog3MsgDouble | |||||
implicit none | |||||
procedure (ActionStringDouble) :: a | |||||
Log3MsgDoublePtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog3MsgBool(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog3MsgBool | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog3MsgBool' :: SubscribeLog3MsgBool | |||||
implicit none | |||||
procedure (ActionStringBool) :: a | |||||
Log3MsgBoolPtr => a | |||||
end subroutine | |||||
end module CLog3 |
@@ -0,0 +1,113 @@ | |||||
module CLog4 | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
interface Log_4 | |||||
module procedure :: Log4Log1, Log4Log2, Log4Log3, Log4Log4, Log4Log5 | |||||
end interface | |||||
procedure (ActionString), pointer :: Log4MsgPtr | |||||
procedure (ActionStringInt), pointer :: Log4MsgIntPtr | |||||
procedure (ActionStringFloat), pointer :: Log4MsgFloatPtr | |||||
procedure (ActionStringDouble), pointer :: Log4MsgDoublePtr | |||||
procedure (ActionStringBool), pointer :: Log4MsgBoolPtr | |||||
contains | |||||
subroutine Log4Log1(message) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
#ifdef Log4 | |||||
if(associated(Log4MsgPtr)) call Log4MsgPtr(message) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log4Log2(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
integer, intent(in) :: value | |||||
#ifdef Log4 | |||||
if(associated(Log4MsgIntPtr)) call Log4MsgIntPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log4Log3(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real, intent(in) :: value | |||||
#ifdef Log4 | |||||
if(associated(Log4MsgFloatPtr)) call Log4MsgFloatPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log4Log4(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real(8), intent(in) :: value | |||||
#ifdef Log4 | |||||
if(associated(Log4MsgDoublePtr)) call Log4MsgDoublePtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log4Log5(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
logical, intent(in) :: value | |||||
#ifdef Log4 | |||||
if(associated(Log4MsgBoolPtr)) call Log4MsgBoolPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine SubscribeLog4Message(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4Message | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4Message' :: SubscribeLog4Message | |||||
implicit none | |||||
procedure (ActionString) :: a | |||||
Log4MsgPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog4MsgInt(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4MsgInt | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4MsgInt' :: SubscribeLog4MsgInt | |||||
implicit none | |||||
procedure (ActionStringInt) :: a | |||||
Log4MsgIntPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog4MsgFloat(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4MsgFloat | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4MsgFloat' :: SubscribeLog4MsgFloat | |||||
implicit none | |||||
procedure (ActionStringFloat) :: a | |||||
Log4MsgFloatPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog4MsgDouble(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4MsgDouble | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4MsgDouble' :: SubscribeLog4MsgDouble | |||||
implicit none | |||||
procedure (ActionStringDouble) :: a | |||||
Log4MsgDoublePtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog4MsgBool(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog4MsgBool | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog4MsgBool' :: SubscribeLog4MsgBool | |||||
implicit none | |||||
procedure (ActionStringBool) :: a | |||||
Log4MsgBoolPtr => a | |||||
end subroutine | |||||
end module CLog4 |
@@ -0,0 +1,113 @@ | |||||
module CLog5 | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
interface Log_5 | |||||
module procedure :: Log5Log1, Log5Log2, Log5Log3, Log5Log4, Log5Log5 | |||||
end interface | |||||
procedure (ActionString), pointer :: Log5MsgPtr | |||||
procedure (ActionStringInt), pointer :: Log5MsgIntPtr | |||||
procedure (ActionStringFloat), pointer :: Log5MsgFloatPtr | |||||
procedure (ActionStringDouble), pointer :: Log5MsgDoublePtr | |||||
procedure (ActionStringBool), pointer :: Log5MsgBoolPtr | |||||
contains | |||||
subroutine Log5Log1(message) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
#ifdef Log5 | |||||
if(associated(Log5MsgPtr)) call Log5MsgPtr(message) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log5Log2(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
integer, intent(in) :: value | |||||
#ifdef Log5 | |||||
if(associated(Log5MsgIntPtr)) call Log5MsgIntPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log5Log3(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real, intent(in) :: value | |||||
#ifdef Log5 | |||||
if(associated(Log5MsgFloatPtr)) call Log5MsgFloatPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log5Log4(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
real(8), intent(in) :: value | |||||
#ifdef Log5 | |||||
if(associated(Log5MsgDoublePtr)) call Log5MsgDoublePtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine Log5Log5(message, value) | |||||
implicit none | |||||
character(len=*), intent(in) :: message | |||||
logical, intent(in) :: value | |||||
#ifdef Log5 | |||||
if(associated(Log5MsgBoolPtr)) call Log5MsgBoolPtr(message, value) | |||||
#endif | |||||
end subroutine | |||||
subroutine SubscribeLog5Message(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5Message | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5Message' :: SubscribeLog5Message | |||||
implicit none | |||||
procedure (ActionString) :: a | |||||
Log5MsgPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog5MsgInt(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5MsgInt | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5MsgInt' :: SubscribeLog5MsgInt | |||||
implicit none | |||||
procedure (ActionStringInt) :: a | |||||
Log5MsgIntPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog5MsgFloat(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5MsgFloat | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5MsgFloat' :: SubscribeLog5MsgFloat | |||||
implicit none | |||||
procedure (ActionStringFloat) :: a | |||||
Log5MsgFloatPtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog5MsgDouble(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5MsgDouble | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5MsgDouble' :: SubscribeLog5MsgDouble | |||||
implicit none | |||||
procedure (ActionStringDouble) :: a | |||||
Log5MsgDoublePtr => a | |||||
end subroutine | |||||
subroutine SubscribeLog5MsgBool(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeLog5MsgBool | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeLog5MsgBool' :: SubscribeLog5MsgBool | |||||
implicit none | |||||
procedure (ActionStringBool) :: a | |||||
Log5MsgBoolPtr => a | |||||
end subroutine | |||||
end module CLog5 |
@@ -0,0 +1,716 @@ | |||||
module COperationScenariosMain | |||||
use CIActionReference | |||||
implicit none | |||||
public | |||||
procedure (ActionVoid), pointer :: UpdateUnityPtr | |||||
contains | |||||
! subroutine OperationScenarios_Setup() | |||||
! use CSimulationVariables | |||||
! implicit none | |||||
! call OnSimulationInitialization%Add(OperationScenarios_Init) | |||||
! call OnSimulationStop%Add(OperationScenarios_Init) | |||||
! !call OnOperationScenariosStep%Add(OperationScenarios_Step) | |||||
! !call OnOperationScenariosOutput%Add(OperationScenarios_Output) | |||||
! call OnOperationScenariosMain%Add(OperationScenariosMainBody) | |||||
! end subroutine | |||||
! subroutine OperationScenarios_Init | |||||
! use COperationScenariosSettings, OperationScenariosInitialization => Initialization | |||||
! implicit none | |||||
! call OperationScenariosInitialization() | |||||
! end subroutine OperationScenarios_Init | |||||
subroutine OperationScenarios_Step | |||||
use CSimulationVariables | |||||
use CKellyConnectionEnum | |||||
use CElevatorConnectionEnum | |||||
use CCloseKellyCockLedNotification | |||||
use CCloseSafetyValveLedNotification | |||||
use CFillMouseHoleLedNotification | |||||
use CIrIBopLedNotification | |||||
use CIrSafetyValveLedNotification | |||||
use CLatchLedNotification | |||||
use COpenKellyCockLedNotification | |||||
use COpenSafetyValveLedNotification | |||||
use CSlipsNotification | |||||
use CSwingLedNotification | |||||
use CTongNotification | |||||
use CUnlatchLedNotification | |||||
use CInstallFillupHeadPermission | |||||
use CInstallMudBucketPermission | |||||
use CIrIbopPermission | |||||
use CIrSafetyValvePermission | |||||
use CRemoveFillupHeadPermission | |||||
use CRemoveMudBucketPermission | |||||
use CHookHeight | |||||
use CIbopHeight | |||||
use CNearFloorConnection | |||||
use CSafetyValveHeight | |||||
use CSlackOff | |||||
use CStandRack | |||||
use CStringPressure | |||||
use CZeroStringSpeed | |||||
use CUnityInputs, only: & | |||||
Get_ElevatorConnectionPossible, & | |||||
Get_JointConnectionPossible, & | |||||
Get_ElevatorPickup, & | |||||
Get_NearFloorPosition, & | |||||
Get_SingleSetInMouseHole | |||||
use CBucketEnum | |||||
use CElevatorEnum | |||||
use CHeadEnum | |||||
use CIbopEnum | |||||
use CKellyEnum | |||||
use CMouseHoleEnum | |||||
use COperationConditionEnum | |||||
use CSafetyValveEnum | |||||
use CSlipsEnum | |||||
use CSwingEnum | |||||
use CTongEnum | |||||
use CStringUpdate | |||||
use CFlowPipeDisconnectEnum | |||||
use CFlowKellyDisconnectEnum | |||||
use CFillupHeadPermission | |||||
use CSwingDrillPermission | |||||
use CSwingOffPermission | |||||
use CSwingTiltPermission | |||||
use CTdsStemJointHeight | |||||
use CTdsConnectionModesEnum | |||||
use CTdsElevatorModesEnum | |||||
use CTdsSpineEnum | |||||
use CTdsSwingEnum | |||||
use CTdsTongEnum | |||||
use CTdsBackupClamp | |||||
use CTdsIbopLedNotification | |||||
use CTdsPowerLedNotification | |||||
use CTdsTorqueWrenchLedNotification | |||||
implicit none | |||||
call Evaluate_KellyConnection() | |||||
call Evaluate_ElevatorConnection() | |||||
call Evaluate_CloseKellyCockLed() | |||||
call Evaluate_CloseSafetyValveLed() | |||||
call Evaluate_FillMouseHoleLed() | |||||
call Evaluate_IrIBopLed() | |||||
call Evaluate_IrSafetyValveLed() | |||||
call Evaluate_LatchLed() | |||||
call Evaluate_OpenKellyCockLed() | |||||
call Evaluate_OpenSafetyValveLed() | |||||
call Evaluate_SlipsNotification() | |||||
call Evaluate_SwingLed() | |||||
call Evaluate_TongNotification() | |||||
call Evaluate_UnlatchLed() | |||||
call Evaluate_InstallFillupHeadPermission() | |||||
call Evaluate_InstallMudBucketPermission() | |||||
call Evaluate_IrIbopPermission() | |||||
call Evaluate_IrSafetyValvePermission() | |||||
call Evaluate_RemoveFillupHeadPermission() | |||||
call Evaluate_RemoveMudBucketPermission() | |||||
call Evaluate_MudBucket() | |||||
call Evaluate_Elevator() | |||||
call Evaluate_FillupHead() | |||||
call Evaluate_Ibop() | |||||
call Evaluate_Kelly() | |||||
call Evaluate_MouseHole() | |||||
call Evaluate_MouseHole() | |||||
call Evaluate_OperationCondition() | |||||
call Evaluate_SafetyValve() | |||||
call Evaluate_Slips() | |||||
call Evaluate_Swing() | |||||
call Evaluate_Tong() | |||||
call Evaluate_StringUpdate() | |||||
call Evaluate_FlowKellyDisconnect() | |||||
call Evaluate_FlowPipeDisconnect() | |||||
!if(Get_FillMouseHoleLed()) then | |||||
! call Set_MouseHole(MOUSE_HOLE_FILL) | |||||
!else | |||||
! if((Get_KellyConnection() == KELLY_CONNECTION_SINGLE .or.& | |||||
! Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE) .and.& | |||||
! Get_HookHeight() >= 95.0 ) then | |||||
! call Set_MouseHole(MOUSE_HOLE_NEUTRAL) | |||||
! else | |||||
! call Set_MouseHole(MOUSE_HOLE_EMPTY) | |||||
! endif | |||||
!endif | |||||
!topdrive | |||||
call Evaluate_TdsElevatorModes() | |||||
call Evaluate_TdsConnectionModes() | |||||
call Evaluate_SwingTiltPermission() | |||||
call Evaluate_SwingOffPermission() | |||||
call Evaluate_SwingDrillPermission() | |||||
call Evaluate_FillupHeadPermission() | |||||
call Evaluate_TdsTong() | |||||
call Evaluate_TdsBackupClamp() | |||||
call Evaluate_TdsSwing() | |||||
call Evaluate_TdsSpine() | |||||
call Evaluate_PowerLed() | |||||
call Evaluate_IbopLed() | |||||
call Evaluate_TorqueWrenchLed() | |||||
end subroutine OperationScenarios_Step | |||||
subroutine OperationScenarios_Output | |||||
implicit none | |||||
end subroutine OperationScenarios_Output | |||||
subroutine OperationScenariosMainBody | |||||
use CSimulationVariables | |||||
use CKellyConnectionEnum | |||||
use CElevatorConnectionEnum | |||||
use CCloseKellyCockLedNotification | |||||
use CCloseSafetyValveLedNotification | |||||
use CFillMouseHoleLedNotification | |||||
use CIrIBopLedNotification | |||||
use CIrSafetyValveLedNotification | |||||
use CLatchLedNotification | |||||
use COpenKellyCockLedNotification | |||||
use COpenSafetyValveLedNotification | |||||
use CSlipsNotification | |||||
use CSwingLedNotification | |||||
use CTongNotification | |||||
use CUnlatchLedNotification | |||||
use CInstallFillupHeadPermission | |||||
use CInstallMudBucketPermission | |||||
use CIrIbopPermission | |||||
use CIrSafetyValvePermission | |||||
use CRemoveFillupHeadPermission | |||||
use CRemoveMudBucketPermission | |||||
use CHookHeight | |||||
use CIbopHeight | |||||
use CNearFloorConnection | |||||
use CSafetyValveHeight | |||||
use CSlackOff | |||||
use CStandRack | |||||
use CStringPressure | |||||
use CZeroStringSpeed | |||||
use CUnityInputs, only: & | |||||
Get_ElevatorConnectionPossible, & | |||||
Get_JointConnectionPossible, & | |||||
Get_ElevatorPickup, & | |||||
Get_NearFloorPosition, & | |||||
Get_SingleSetInMouseHole | |||||
use CBucketEnum | |||||
use CElevatorEnum | |||||
use CHeadEnum | |||||
use CIbopEnum | |||||
use CKellyEnum | |||||
use CMouseHoleEnum | |||||
use COperationConditionEnum | |||||
use CSafetyValveEnum | |||||
use CSlipsEnum | |||||
use CSwingEnum | |||||
use CTongEnum | |||||
use CStringUpdate | |||||
use CFlowPipeDisconnectEnum | |||||
use CFlowKellyDisconnectEnum | |||||
use CFillupHeadPermission | |||||
use CSwingDrillPermission | |||||
use CSwingOffPermission | |||||
use CSwingTiltPermission | |||||
use CTdsStemJointHeight | |||||
use CTdsConnectionModesEnum | |||||
use CTdsElevatorModesEnum | |||||
use CTdsSpineEnum | |||||
use CTdsSwingEnum | |||||
use CTdsTongEnum | |||||
use CTdsBackupClamp | |||||
use CTdsIbopLedNotification | |||||
use CTdsPowerLedNotification | |||||
use CTdsTorqueWrenchLedNotification | |||||
implicit none | |||||
loop1: do | |||||
call Evaluate_KellyConnection() | |||||
call Evaluate_ElevatorConnection() | |||||
call Evaluate_CloseKellyCockLed() | |||||
call Evaluate_CloseSafetyValveLed() | |||||
call Evaluate_FillMouseHoleLed() | |||||
call Evaluate_IrIBopLed() | |||||
call Evaluate_IrSafetyValveLed() | |||||
call Evaluate_LatchLed() | |||||
call Evaluate_OpenKellyCockLed() | |||||
call Evaluate_OpenSafetyValveLed() | |||||
call Evaluate_SlipsNotification() | |||||
call Evaluate_SwingLed() | |||||
call Evaluate_TongNotification() | |||||
call Evaluate_UnlatchLed() | |||||
call Evaluate_InstallFillupHeadPermission() | |||||
call Evaluate_InstallMudBucketPermission() | |||||
call Evaluate_IrIbopPermission() | |||||
call Evaluate_IrSafetyValvePermission() | |||||
call Evaluate_RemoveFillupHeadPermission() | |||||
call Evaluate_RemoveMudBucketPermission() | |||||
call Evaluate_MudBucket() | |||||
call Evaluate_Elevator() | |||||
call Evaluate_FillupHead() | |||||
call Evaluate_Ibop() | |||||
call Evaluate_Kelly() | |||||
call Evaluate_MouseHole() | |||||
call Evaluate_MouseHole() | |||||
call Evaluate_OperationCondition() | |||||
call Evaluate_SafetyValve() | |||||
call Evaluate_Slips() | |||||
call Evaluate_Swing() | |||||
call Evaluate_Tong() | |||||
call Evaluate_StringUpdate() | |||||
call Evaluate_FlowKellyDisconnect() | |||||
call Evaluate_FlowPipeDisconnect() | |||||
!if(Get_FillMouseHoleLed()) then | |||||
! call Set_MouseHole(MOUSE_HOLE_FILL) | |||||
!else | |||||
! if((Get_KellyConnection() == KELLY_CONNECTION_SINGLE .or.& | |||||
! Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE) .and.& | |||||
! Get_HookHeight() >= 95.0 ) then | |||||
! call Set_MouseHole(MOUSE_HOLE_NEUTRAL) | |||||
! else | |||||
! call Set_MouseHole(MOUSE_HOLE_EMPTY) | |||||
! endif | |||||
!endif | |||||
!topdrive | |||||
call Evaluate_TdsElevatorModes() | |||||
call Evaluate_TdsConnectionModes() | |||||
call Evaluate_SwingTiltPermission() | |||||
call Evaluate_SwingOffPermission() | |||||
call Evaluate_SwingDrillPermission() | |||||
call Evaluate_FillupHeadPermission() | |||||
call Evaluate_TdsTong() | |||||
call Evaluate_TdsBackupClamp() | |||||
call Evaluate_TdsSwing() | |||||
call Evaluate_TdsSpine() | |||||
call Evaluate_PowerLed() | |||||
call Evaluate_IbopLed() | |||||
call Evaluate_TorqueWrenchLed() | |||||
!if (IsStopped==.true.) exit loop1 | |||||
if(IsStopped) call Quit() | |||||
call sleepqq(100) | |||||
enddo loop1 | |||||
end subroutine OperationScenariosMainBody | |||||
subroutine SubscribeUpdateUnity(a) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SubscribeUpdateUnity | |||||
!DEC$ ATTRIBUTES ALIAS: 'SubscribeUpdateUnity' :: SubscribeUpdateUnity | |||||
implicit none | |||||
procedure (ActionVoid) :: a | |||||
UpdateUnityPtr => a | |||||
end subroutine | |||||
subroutine UpdateUnity() | |||||
implicit none | |||||
if(associated(UpdateUnityPtr)) call UpdateUnityPtr() | |||||
end subroutine | |||||
subroutine PreProcessingSnapshot | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: PreProcessingSnapshot | |||||
!DEC$ ATTRIBUTES ALIAS: 'PreProcessingSnapshot' :: PreProcessingSnapshot | |||||
use CSwingEnumVariables | |||||
use CSlipsEnumVariables | |||||
use CHookVariables | |||||
use CTongEnumVariables | |||||
use CHoistingVariables | |||||
use CKellyConnectionEnumVariables | |||||
use CElevatorConnectionEnumVariables | |||||
use COperationConditionEnumVariables | |||||
use CMouseHoleEnumVariables | |||||
implicit none | |||||
if(DriveType == Kelly_DriveType) then ! kelly mode | |||||
if(Get_OperationCondition() == OPERATION_DRILL) then | |||||
if(Get_KellyConnection() == KELLY_CONNECTION_NOTHING) then | |||||
call Kelly_ConnectionNothing() | |||||
elseif (Get_KellyConnection() == KELLY_CONNECTION_STRING) then | |||||
call Kelly_ConnectionString() | |||||
elseif (Get_KellyConnection() == KELLY_CONNECTION_SINGLE) then | |||||
call Kelly_ConnectionSingle() | |||||
endif | |||||
elseif (Get_OperationCondition() == OPERATION_TRIP) then | |||||
if(Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING) then | |||||
call Elevator_ConnectionNothing() | |||||
elseif (Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING) then | |||||
call Elevator_ConnectionString() | |||||
elseif (Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND) then | |||||
call Elevator_ConnectionStand() | |||||
elseif (Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE) then | |||||
call Elevator_ConnectionSingle() | |||||
endif | |||||
endif | |||||
else ! Topdrive mode | |||||
! | |||||
endif | |||||
! final adjustments | |||||
call Update_MouseHole_From_Snapshot() | |||||
end subroutine PreProcessingSnapshot | |||||
subroutine Kelly_ConnectionNothing | |||||
use CSwingEnumVariables | |||||
use CSlipsEnumVariables | |||||
use CHookVariables | |||||
implicit none | |||||
call Set_HookHeight(75.0) | |||||
call sleep(1) | |||||
! first wait for unity to get to starting point | |||||
loop1: do | |||||
if(Get_Swing() == SWING_WELL_END .and. Get_Slips() == SLIPS_SET_END) exit loop1 | |||||
call sleepqq(100) | |||||
enddo loop1 | |||||
call sleep(1) | |||||
!TODO: possibly goto a position to activate swing | |||||
! goto preferred swing position | |||||
if(Swing_S == SWING_MOUSE_HOLE_END) then | |||||
call Set_Swing(SWING_MOUSE_HOLE_BEGIN) | |||||
call UpdateUnity() | |||||
loop2: do | |||||
if(Get_Swing() == SWING_MOUSE_HOLE_END) exit loop2 | |||||
call sleepqq(100) | |||||
enddo loop2 | |||||
elseif (Swing_S == SWING_RAT_HOLE_END) then | |||||
call Set_Swing(SWING_RAT_HOLE_BEGIN) | |||||
call UpdateUnity() | |||||
loop3: do | |||||
if(Get_Swing() == SWING_RAT_HOLE_END) exit loop3 | |||||
call sleepqq(100) | |||||
enddo loop3 | |||||
!elseif (Swing_S == SWING_WELL_END) then | |||||
! call Set_Swing(SWING_WELL_BEGIN) | |||||
! call UpdateUnity() | |||||
! loop4: do | |||||
! if(Get_Swing() == SWING_WELL_END) exit loop4 | |||||
! call sleepqq(100) | |||||
! enddo loop4 | |||||
endif | |||||
call sleep(3) | |||||
! move to final hook height | |||||
call Update_HookHeight_From_Snapshot() | |||||
call sleep(3) | |||||
end subroutine Kelly_ConnectionNothing | |||||
subroutine Kelly_ConnectionString | |||||
use CSwingEnumVariables | |||||
use CSlipsEnumVariables | |||||
use CHookVariables | |||||
use CTongEnumVariables | |||||
implicit none | |||||
call Set_HookHeight(75.0) | |||||
call sleep(1) | |||||
! first wait for unity to get to starting point | |||||
loop1: do | |||||
if(Get_Swing() == SWING_WELL_END .and. Get_Slips() == SLIPS_SET_END) exit loop1 | |||||
call sleepqq(100) | |||||
enddo loop1 | |||||
call sleep(1) | |||||
! goto connection to string position | |||||
call Set_HookHeight_S(66.7) | |||||
call sleep(1) | |||||
! start tong makeup | |||||
call Set_Tong(TONG_MAKEUP_BEGIN) | |||||
call UpdateUnity() | |||||
loop2: do | |||||
if(Get_Tong() == TONG_MAKEUP_END) exit loop2 | |||||
call sleepqq(100) | |||||
enddo loop2 | |||||
call sleepqq(100) | |||||
! release slips | |||||
call Set_Slips(SLIPS_UNSET_BEGIN) | |||||
call UpdateUnity() | |||||
loop3: do | |||||
if(Get_Slips() == SLIPS_UNSET_END) exit loop3 | |||||
call sleepqq(100) | |||||
enddo loop3 | |||||
call sleepqq(100) | |||||
! move to final hook height | |||||
call Update_HookHeight_From_Snapshot() | |||||
call sleep(3) | |||||
! put slips to saved position | |||||
if(Slips_S == SLIPS_SET_END) then | |||||
call Set_Slips(SLIPS_SET_BEGIN) | |||||
call UpdateUnity() | |||||
loop4: do | |||||
if(Get_Slips() == SLIPS_SET_END) exit loop4 | |||||
call sleepqq(100) | |||||
enddo loop4 | |||||
call sleep(1) | |||||
endif | |||||
end subroutine Kelly_ConnectionString | |||||
subroutine Kelly_ConnectionSingle | |||||
use CSwingEnumVariables | |||||
use CSlipsEnumVariables | |||||
use CTongEnumVariables | |||||
use CHookVariables | |||||
implicit none | |||||
call Set_HookHeight(75.0) | |||||
call sleep(1) | |||||
! first wait for unity to get to starting point | |||||
loop1: do | |||||
if(Get_Swing() == SWING_WELL_END .and. Get_Slips() == SLIPS_SET_END) exit loop1 | |||||
call sleepqq(100) | |||||
enddo loop1 | |||||
call sleep(1) | |||||
! goto swing mouse hole position | |||||
call Set_HookHeight_S(70.0) | |||||
call sleep(1) | |||||
! swing mouse hole | |||||
call Set_Swing(SWING_MOUSE_HOLE_BEGIN) | |||||
call UpdateUnity() | |||||
loop2: do | |||||
if(Get_Swing() == SWING_MOUSE_HOLE_END) exit loop2 | |||||
call sleepqq(100) | |||||
enddo loop2 | |||||
call sleepqq(100) | |||||
! goto makeup pipe location | |||||
call Set_HookHeight_S(65.0) | |||||
call sleep(1) | |||||
! start tong makeup | |||||
call Set_Tong(TONG_MAKEUP_BEGIN) | |||||
call UpdateUnity() | |||||
loop3: do | |||||
if(Get_Tong() == TONG_MAKEUP_END) exit loop3 | |||||
call sleepqq(100) | |||||
enddo loop3 | |||||
call sleepqq(100) | |||||
if (Swing_S == SWING_WELL_END) then ! already in mouse hole | |||||
! goto swing location | |||||
call Set_HookHeight_S(98.0) | |||||
call sleep(1) | |||||
! goto preferred swing position | |||||
call Set_Swing(SWING_WELL_BEGIN) | |||||
call UpdateUnity() | |||||
loop4: do | |||||
if(Get_Swing() == SWING_WELL_END) exit loop4 | |||||
call sleepqq(100) | |||||
enddo loop4 | |||||
call sleep(2) | |||||
endif | |||||
! move to final hook height | |||||
call Update_HookHeight_From_Snapshot() | |||||
call sleep(3) | |||||
end subroutine Kelly_ConnectionSingle | |||||
subroutine Elevator_ConnectionNothing | |||||
use CSwingEnumVariables | |||||
use CSlipsEnumVariables | |||||
use CHookVariables | |||||
use CKellyEnumVariables | |||||
implicit none | |||||
call Set_HookHeight(75.0) | |||||
call sleep(1) | |||||
! first wait for unity to get to starting point | |||||
loop1: do | |||||
if(Get_Swing() == SWING_WELL_END .and. Get_Slips() == SLIPS_SET_END) exit loop1 | |||||
call sleepqq(100) | |||||
enddo loop1 | |||||
call sleep(1) | |||||
!TODO: possibly goto a position to activate swing | |||||
!! first goto mouse hole | |||||
!call Set_Swing(SWING_MOUSE_HOLE_BEGIN) | |||||
!call UpdateUnity() | |||||
!loop2: do | |||||
! if(Get_Swing() == SWING_MOUSE_HOLE_END) exit loop2 | |||||
! call sleepqq(100) | |||||
!enddo loop2 | |||||
!call sleep(1) | |||||
! | |||||
!! then goto rat hole | |||||
!call Set_Swing(SWING_RAT_HOLE_BEGIN) | |||||
!call UpdateUnity() | |||||
!loop3: do | |||||
! if(Get_Swing() == SWING_RAT_HOLE_END) exit loop3 | |||||
! call sleepqq(100) | |||||
!enddo loop3 | |||||
!call sleep(1) | |||||
! kelly back | |||||
call Set_Kelly(KELLY_REMOVE) | |||||
call sleepqq(100) | |||||
! goto preferred swing position | |||||
if(Swing_S == SWING_MOUSE_HOLE_END) then | |||||
call Set_Swing(SWING_MOUSE_HOLE_BEGIN) | |||||
call UpdateUnity() | |||||
loop4: do | |||||
if(Get_Swing() == SWING_MOUSE_HOLE_END) exit loop4 | |||||
call sleepqq(100) | |||||
enddo loop4 | |||||
elseif (Swing_S == SWING_RAT_HOLE_END) then | |||||
call Set_Swing(SWING_RAT_HOLE_BEGIN) | |||||
call UpdateUnity() | |||||
loop5: do | |||||
if(Get_Swing() == SWING_RAT_HOLE_END) exit loop5 | |||||
call sleepqq(100) | |||||
enddo loop5 | |||||
elseif (Swing_S == SWING_WELL_END) then | |||||
call Set_Swing(SWING_WELL_BEGIN) | |||||
call UpdateUnity() | |||||
loop6: do | |||||
if(Get_Swing() == SWING_WELL_END) exit loop6 | |||||
call sleepqq(100) | |||||
enddo loop6 | |||||
endif | |||||
call sleepqq(100) | |||||
! move to final hook height | |||||
call Update_HookHeight_From_Snapshot() | |||||
call sleep(3) | |||||
end subroutine Elevator_ConnectionNothing | |||||
subroutine Elevator_ConnectionString | |||||
implicit none | |||||
end subroutine Elevator_ConnectionString | |||||
subroutine Elevator_ConnectionStand | |||||
implicit none | |||||
end subroutine Elevator_ConnectionStand | |||||
subroutine Elevator_ConnectionSingle | |||||
implicit none | |||||
end subroutine Elevator_ConnectionSingle | |||||
end module COperationScenariosMain |
@@ -0,0 +1,488 @@ | |||||
module COperationScenariosSettings | |||||
implicit none | |||||
public | |||||
contains | |||||
!subroutine Initialization() | |||||
! use CSimulationVariables | |||||
! use CUnityOutputs, only: SetupUnityOutputs => Setup | |||||
! | |||||
! use CBucketEnum | |||||
! use CTongEnum | |||||
! use CSwingEnum | |||||
! use CSlipsEnum | |||||
! use CSafetyValveEnum | |||||
! use COperationConditionEnum | |||||
! use CMouseHoleEnum | |||||
! use CKellyEnum | |||||
! use CKellyConnectionEnum | |||||
! use CIbopEnum | |||||
! use CHeadEnum | |||||
! use CElevatorEnum | |||||
! use CElevatorConnectionEnum | |||||
! | |||||
! use CInstallFillupHeadPermission | |||||
! use CInstallMudBucketPermission | |||||
! use CIrIbopPermission | |||||
! use CIrSafetyValvePermission | |||||
! use CRemoveFillupHeadPermission | |||||
! use CRemoveMudBucketPermission | |||||
! | |||||
! use CCloseKellyCockLedNotification | |||||
! use CCloseSafetyValveLedNotification | |||||
! use CFillMouseHoleLedNotification | |||||
! use CIrIBopLedNotification | |||||
! use CIrSafetyValveLedNotification | |||||
! use CLatchLedNotification | |||||
! use COpenKellyCockLedNotification | |||||
! use COpenSafetyValveLedNotification | |||||
! use CSlipsNotification | |||||
! use CSwingLedNotification | |||||
! use CTongNotification | |||||
! use CUnlatchLedNotification | |||||
! | |||||
! use CHookHeight | |||||
! use CIbopHeight | |||||
! use CNearFloorConnection | |||||
! use CSafetyValveHeight | |||||
! use CSlackOff | |||||
! use CStandRack | |||||
! use CStringPressure | |||||
! use CZeroStringSpeed | |||||
! | |||||
! use CStringUpdate | |||||
! | |||||
! use CFlowPipeDisconnectEnum | |||||
! use CFlowKellyDisconnectEnum | |||||
! | |||||
! use CFillupHeadPermission | |||||
! use CSwingDrillPermission | |||||
! use CSwingOffPermission | |||||
! use CSwingTiltPermission | |||||
! use CTdsStemJointHeight | |||||
! use CTdsConnectionModesEnum | |||||
! use CTdsElevatorModesEnum | |||||
! use CTdsSpineEnum | |||||
! use CTdsSwingEnum | |||||
! use CTdsTongEnum | |||||
! use CTdsBackupClamp | |||||
! | |||||
! use CTdsIbopLedNotification | |||||
! use CTdsPowerLedNotification | |||||
! | |||||
! use CTdsTorqueWrenchLedNotification | |||||
! | |||||
! implicit none | |||||
! | |||||
! call SetupUnityOutputs() | |||||
! | |||||
! call Subscribe_Tong() | |||||
! call Subscribe_MudBucket() | |||||
! call Subscribe_ElevatorConnection() | |||||
! call Subscribe_Elevator() | |||||
! call Subscribe_FillupHead() | |||||
! call Subscribe_Ibop() | |||||
! call Subscribe_KellyConnection() | |||||
! call Subscribe_Kelly() | |||||
! call Subscribe_MouseHole() | |||||
! call Subscribe_OperationCondition() | |||||
! call Subscribe_SafetyValve() | |||||
! call Subscribe_Slips() | |||||
! call Subscribe_Swing() | |||||
! | |||||
! | |||||
! call Subscribe_InstallFillupHeadPermission() | |||||
! call Subscribe_InstallMudBucketPermission() | |||||
! call Subscribe_IrIbopPermission() | |||||
! call Subscribe_IrSafetyValvePermission() | |||||
! call Subscribe_RemoveFillupHeadPermission() | |||||
! call Subscribe_RemoveMudBucketPermission() | |||||
! | |||||
! call Subscribe_CloseKellyCockLed() | |||||
! call Subscribe_CloseSafetyValveLed() | |||||
! call Subscribe_FillMouseHoleLed() | |||||
! call Subscribe_IrIBopLed() | |||||
! call Subscribe_IrSafetyValveLed() | |||||
! call Subscribe_LatchLed() | |||||
! call Subscribe_OpenKellyCockLed() | |||||
! call Subscribe_OpenSafetyValveLed() | |||||
! call Subscribe_SlipsNotification() | |||||
! call Subscribe_SwingLed() | |||||
! call Subscribe_UnlatchLed() | |||||
! | |||||
! call Subscribe_HookHeight() | |||||
! call Subscribe_IbopHeight() | |||||
! call Subscribe_NearFloorConnection() | |||||
! call Subscribe_SafetyValveHeight() | |||||
! call Subscribe_SlackOff() | |||||
! call Subscribe_StringPressure() | |||||
! call Subscribe_ZeroStringSpeed() | |||||
! call Subscribe_StandRack() | |||||
! | |||||
! call Subscribe_StringUpdate() | |||||
! | |||||
! call Subscribe_TongNotification() | |||||
! | |||||
! call Subscribe_FlowKellyDisconnect() | |||||
! call Subscribe_FlowPipeDisconnect() | |||||
! | |||||
! | |||||
! | |||||
! | |||||
! | |||||
! !top drive | |||||
! call Subscribe_TdsConnectionModes() | |||||
! call Subscribe_TdsElevatorModes() | |||||
! call Subscribe_FillupHeadPermission() | |||||
! call Subscribe_SwingDrillPermission() | |||||
! call Subscribe_SwingOffPermission() | |||||
! call Subscribe_SwingTiltPermission() | |||||
! call Subscribe_TdsStemJointHeight() | |||||
! call Subscribe_TdsTong() | |||||
! call Subscribe_TdsBackupClamp() | |||||
! call Subscribe_TdsSwing() | |||||
! call Subscribe_TdsSpine() | |||||
! call Subscribe_PowerLed() | |||||
! call Subscribe_IbopLed() | |||||
! | |||||
! call Subscribe_TorqueWrenchLed() | |||||
! | |||||
! | |||||
! call OnSimulationStart%Add(SetDefaultValues) | |||||
! | |||||
!end subroutine | |||||
subroutine SetDefaultValues() | |||||
use COperationScenariosVariables | |||||
use CHoistingVariables, only: DriveType, TopDrive_DriveType | |||||
use CManifolds, only: RemoveSafetyValve_TripMode, RemoveSafetyValve_KellyMode | |||||
implicit none | |||||
call Set_KellyConnection(KELLY_CONNECTION_NOTHING) | |||||
!Get_KellyConnection() | |||||
!KELLY_CONNECTION_NOTHING | |||||
!KELLY_CONNECTION_STRING | |||||
!KELLY_CONNECTION_SINGLE | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_NOTHING) | |||||
!Get_ElevatorConnection() | |||||
!ELEVATOR_CONNECTION_NOTHING | |||||
!ELEVATOR_CONNECTION_STRING | |||||
!ELEVATOR_CONNECTION_STAND | |||||
!ELEVATOR_CONNECTION_SINGLE | |||||
!ELEVATOR_LATCH_STRING | |||||
!ELEVATOR_LATCH_SINGLE | |||||
!ELEVATOR_LATCH_STAND | |||||
call Set_CloseKellyCockLed(.false.) !Get_CloseKellyCockLed() | |||||
call Set_CloseSafetyValveLed(.false.) !Get_CloseSafetyValveLed() | |||||
call Set_FillMouseHoleLed(.true.) !Get_FillMouseHoleLed() | |||||
call Set_IrIBopLed(.false.) !Get_IrIBopLed() | |||||
!call Set_IrSafetyValveLed(.true.) !Get_IrSafetyValveLed() | |||||
if(DriveType == TopDrive_DriveType) then | |||||
call RemoveSafetyValve_TripMode() | |||||
call RemoveSafetyValve_KellyMode() | |||||
call Set_IrSafetyValveLed(.false.) | |||||
else | |||||
call Set_IrSafetyValveLed(.true.) | |||||
endif | |||||
call Set_LatchLed(.false.) !Get_LatchLed() | |||||
call Set_OpenKellyCockLed(.true.) !Get_OpenKellyCockLed() | |||||
call Set_OpenSafetyValveLed(.true.) !Get_OpenSafetyValveLed() | |||||
call Set_SlipsNotification(.false.) !Get_SlipsNotification() | |||||
call Set_SwingLed(.false.) !Get_SwingLed() | |||||
call Set_TongNotification(.false.) !Get_TongNotification() | |||||
call Set_UnlatchLed(.false.) !Get_UnlatchLed() | |||||
call Set_InstallFillupHeadPermission(.false.) !Get_InstallFillupHeadPermission() | |||||
call Set_InstallMudBucketPermission(.false.) !Get_InstallMudBucketPermission() | |||||
call Set_IrIbopPermission(.false.) !Get_IrIbopPermission() | |||||
call Set_IrSafetyValvePermission(.false.) !Get_IrSafetyValvePermission() | |||||
call Set_RemoveFillupHeadPermission(.false.) !Get_RemoveFillupHeadPermission() | |||||
call Set_RemoveMudBucketPermission(.false.) !Get_RemoveMudBucketPermission() | |||||
!call Set_HookHeight(REAL(70.0, 8)) !Get_HookHeight() | |||||
call Set_IbopHeight(3.0) !Get_IbopHeight() | |||||
!call Set_NearFloorConnection(3.0) !Get_NearFloorConnection() | |||||
call Set_SafetyValveHeight(3.0) !Get_SafetyValveHeight() | |||||
call Set_SlackOff(.true.) !Get_SlackOff() | |||||
!call Set_StandRack(0.0) !Get_StandRack() | |||||
!call Set_StringPressure(0.0) !Get_StringPressure() | |||||
!call Set_ZeroStringSpeed(.true.) !Get_ZeroStringSpeed() | |||||
!Get_ElevatorConnected() | |||||
!Get_JointConnection() | |||||
!Get_NearMonkeyBoardPosition() | |||||
!Get_NearFloorPosition() | |||||
!Get_SingleSetInMouseHole() | |||||
!Get_SwingCenter() | |||||
call Set_MudBucket(MUD_BUCKET_REMOVE) | |||||
!Get_MudBucket() | |||||
!MUD_BUCKET_INSTALL | |||||
!MUD_BUCKET_REMOVE | |||||
call Set_Elevator(ELEVATOR_NEUTRAL) | |||||
! Get_Elevator() | |||||
!ELEVATOR_NEUTRAL | |||||
!ELEVATOR_LATCH_STRING_BEGIN | |||||
!ELEVATOR_LATCH_STRING_END | |||||
!ELEVATOR_UNLATCH_STRING_BEGIN | |||||
!ELEVATOR_UNLATCH_STRING_END | |||||
!ELEVATOR_LATCH_STAND_BEGIN | |||||
!ELEVATOR_LATCH_STAND_END | |||||
!ELEVATOR_UNLATCH_STAND_BEGIN | |||||
!ELEVATOR_UNLATCH_STAND_END | |||||
!ELEVATOR_LATCH_SINGLE_BEGIN | |||||
!ELEVATOR_LATCH_SINGLE_END | |||||
!ELEVATOR_UNLATCH_SINGLE_BEGIN | |||||
!ELEVATOR_UNLATCH_SINGLE_END | |||||
call Set_FillupHead(FILLUP_HEAD_REMOVE) | |||||
!Get_FillupHead() | |||||
!FILLUP_HEAD_INSTALL | |||||
!FILLUP_HEAD_REMOVE | |||||
call Set_Ibop(IBOP_REMOVE) | |||||
!Get_Ibop() | |||||
!IBOP_INSTALL | |||||
!IBOP_REMOVE | |||||
call Set_Kelly(KELLY_INSTALL) | |||||
!Get_Kelly() | |||||
!KELLY_NEUTRAL | |||||
!KELLY_INSTALL | |||||
!KELLY_REMOVE | |||||
call Set_MouseHole(MOUSE_HOLE_FILL) | |||||
!Get_MouseHole() | |||||
!MOUSE_HOLE_NEUTRAL | |||||
!MOUSE_HOLE_FILL | |||||
!MOUSE_HOLE_EMPTY | |||||
call Set_OperationCondition(OPERATION_DRILL) | |||||
!Get_OperationCondition() | |||||
!OPERATION_DRILL | |||||
!OPERATION_TRIP | |||||
call Set_SafetyValve(SAFETY_VALVE_INSTALL) | |||||
!Get_SafetyValve() | |||||
!SAFETY_VALVE_INSTALL | |||||
!SAFETY_VALVE_REMOVE | |||||
if(DriveType == TopDrive_DriveType) call Set_SafetyValve(SAFETY_VALVE_REMOVE) | |||||
call Set_Slips(SLIPS_SET_BEGIN) | |||||
!Get_Slips() | |||||
!SLIPS_NEUTRAL | |||||
!SLIPS_SET_BEGIN | |||||
!SLIPS_SET_END | |||||
!SLIPS_UNSET_BEGIN | |||||
!SLIPS_UNSET_END | |||||
call Set_Swing(SWING_WELL_BEGIN) | |||||
!Get_Swing() | |||||
!SWING_NEUTRAL | |||||
!SWING_MOUSE_HOLE_BEGIN | |||||
!SWING_MOUSE_HOLE_END | |||||
!SWING_RAT_HOLE_BEGIN | |||||
!SWING_RAT_HOLE_END | |||||
!SWING_WELL_BEGIN | |||||
!SWING_WELL_END | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
!Get_Tong() | |||||
!TONG_NEUTRAL | |||||
!TONG_BREAKOUT_BEGIN | |||||
!TONG_BREAKOUT_END | |||||
!TONG_MAKEUP_BEGIN | |||||
!TONG_MAKEUP_END | |||||
call Set_StringUpdate(STRING_UPDATE_NEUTRAL) | |||||
!Get_StringUpdate() | |||||
!STRING_UPDATE_NEUTRAL | |||||
!STRING_UPDATE_ADD_SINGLE | |||||
!STRING_UPDATE_ADD_STAND | |||||
!STRING_UPDATE_REMOVE_SINGLE | |||||
!STRING_UPDATE_REMOVE_STAND | |||||
call Set_TdsElevatorModes(TDS_ELEVATOR_CONNECTION_NOTHING) | |||||
!Get_TdsElevatorModes() | |||||
!TDS_ELEVATOR_CONNECTION_NOTHING | |||||
!TDS_ELEVATOR_CONNECTION_STRING | |||||
!TDS_ELEVATOR_CONNECTION_SINGLE | |||||
!TDS_ELEVATOR_CONNECTION_STAND | |||||
!TDS_ELEVATOR_LATCH_STRING | |||||
!TDS_ELEVATOR_LATCH_SINGLE | |||||
!TDS_ELEVATOR_LATCH_STAND | |||||
call Set_TdsConnectionModes(TDS_CONNECTION_NOTHING) | |||||
!Get_TdsConnectionModes() | |||||
!TDS_CONNECTION_NOTHING | |||||
!TDS_CONNECTION_STRING | |||||
!TDS_CONNECTION_SPINE | |||||
call Set_SwingTiltPermission(.false.) !Get_SwingTiltPermission() | |||||
call Set_SwingOffPermission(.false.) !Get_SwingOffPermission() | |||||
call Set_SwingDrillPermission(.false.) !Get_SwingDrillPermission() | |||||
call Set_FillupHeadPermission(.false.) !Get_FillupHeadPermission() | |||||
call Set_PowerLed(.false.) | |||||
call Set_IbopLed(.false.) | |||||
call Set_TorqueWrenchLed(0) !Get_TorqueWrenchLed() | |||||
!TdsPower_REV = 1 | |||||
!TdsPower_OFF = 0 | |||||
!TdsPower_FWD = -1 | |||||
! | |||||
!TdsMu_TORQ = 1 | |||||
!TdsMu_SPINE = 0 | |||||
!TdsMu_DRILL = -1 | |||||
! | |||||
!TdsLinkTilt_TILT = 1 | |||||
!TdsLinkTilt_OFF = 0 | |||||
!TdsLinkTilt_DRILL = -1 | |||||
!TDS IBOP TopDriveIbop | |||||
!TDS LinkTilt TopDriveLinkTiltState | |||||
!TDS MU TopDriveDrillTorqueState | |||||
!TDS Power TopDriveTdsPowerState | |||||
!TopDriveTorqueWrench PRESSED=True or UNPRESSED=Falses | |||||
!Get_TdsConnectionPossible() | |||||
!Get_TdsStemIn() | |||||
!call Set_TdsStemJointHeight(v) !Get_TdsStemJointHeight() | |||||
!Get_SwingDrillPermission() | |||||
!Get_SwingOffPermission() | |||||
!Get_SwingTiltPermission() | |||||
!Get_FillupHeadPermission() | |||||
call Set_TdsTong(TDS_TONG_BREAKOUT_END) | |||||
!Get_TdsTong() | |||||
!TDS_TONG_BREAKOUT_BEGIN | |||||
!TDS_TONG_BREAKOUT_END | |||||
!TDS_TONG_MAKEUP_BEGIN | |||||
!TDS_TONG_MAKEUP_END | |||||
call Set_TdsBackupClamp(BACKUP_CLAMP_OFF_END) | |||||
!Get_TdsBackupClamp() | |||||
!BACKUP_CLAMP_OFF_END | |||||
!BACKUP_CLAMP_OFF_BEGIN | |||||
!BACKUP_CLAMP_FW_BEGIN | |||||
!BACKUP_CLAMP_FW_END | |||||
call Set_TdsSwing(TDS_SWING_OFF_END) | |||||
!Get_TdsSwing() | |||||
!TDS_SWING_NEUTRAL | |||||
!TDS_SWING_OFF_BEGIN | |||||
!TDS_SWING_OFF_END | |||||
!TDS_SWING_DRILL_BEGIN | |||||
!TDS_SWING_DRILL_END | |||||
!TDS_SWING_TILT_BEGIN | |||||
!TDS_SWING_TILT_END | |||||
call Set_TdsSpine(TDS_SPINE_NEUTRAL) !TDS_SPINE_DISCONNECT_END | |||||
!Get_TdsSpine() | |||||
!TDS_SPINE_NEUTRAL | |||||
!TDS_SPINE_CONNECT_BEGIN | |||||
!TDS_SPINE_CONNECT_END | |||||
!TDS_SPINE_DISCONNECT_BEGIN | |||||
!TDS_SPINE_DISCONNECT_END | |||||
end subroutine | |||||
subroutine SetDefaults_WN() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: SetDefaults_WN | |||||
!DEC$ ATTRIBUTES ALIAS: 'SetDefaults_WN' :: SetDefaults_WN | |||||
implicit none | |||||
call SetDefaultValues() | |||||
end subroutine | |||||
end module COperationScenariosSettings |
@@ -0,0 +1,116 @@ | |||||
module COperationScenariosVariables | |||||
use CKellyConnectionEnumVariables | |||||
use CElevatorConnectionEnumVariables | |||||
use CCloseKellyCockLedNotificationVariables | |||||
use CCloseSafetyValveLedNotificationVariables | |||||
use CFillMouseHoleLedNotificationVariables | |||||
use CIrIBopLedNotificationVariables | |||||
use CIrSafetyValveLedNotificationVariables | |||||
use CLatchLedNotificationVariables | |||||
use COpenKellyCockLedNotificationVariables | |||||
use COpenSafetyValveLedNotificationVariables | |||||
use CSlipsNotificationVariables | |||||
use CSwingLedNotificationVariables | |||||
use CTongNotificationVariables | |||||
use CUnlatchLedNotificationVariables | |||||
use CInstallFillupHeadPermissionVariables | |||||
use CInstallMudBucketPermissionVariables | |||||
use CIrIbopPermissionVariables | |||||
use CIrSafetyValvePermissionVariables | |||||
use CRemoveFillupHeadPermissionVariables | |||||
use CRemoveMudBucketPermissionVariables | |||||
use CHookHeight | |||||
use CIbopHeight | |||||
use CNearFloorConnection | |||||
use CSafetyValveHeight | |||||
use CSlackOff | |||||
use CStandRack | |||||
use CStringPressure | |||||
use CZeroStringSpeed | |||||
use CStringUpdateVariables | |||||
use CUnityInputs | |||||
!, only: Get_OutOfMouseHole,& | |||||
! Get_Unlatch,& | |||||
! Get_Latch,& | |||||
! Get_SlipsUnSet,& | |||||
! Get_SlipsSet,& | |||||
! Get_BreakupTong,& | |||||
! Get_MakeupTong,& | |||||
! Get_NewHookHeight,& | |||||
! Get_ElevatorConnectionPossible,& | |||||
! Get_JointConnectionPossible,& | |||||
! Get_NearMonkeyBoardPosition,& | |||||
! Get_SingleSetInMouseHole,& | |||||
! Get_SwingCenter | |||||
use CUnityOutputs, only: GetRotaryRpm | |||||
use CBucketEnumVariables | |||||
use CElevatorEnumVariables | |||||
use CHeadEnumVariables | |||||
use CIbopEnumVariables | |||||
use CKellyEnumVariables | |||||
use CMouseHoleEnumVariables | |||||
use COperationConditionEnumVariables | |||||
use CSafetyValveEnumVariables | |||||
use CSlipsEnumVariables | |||||
use CSwingEnumVariables | |||||
use CTongEnumVariables | |||||
use CFillupHeadPermissionVariables | |||||
use CSwingDrillPermissionVariables | |||||
use CSwingOffPermissionVariables | |||||
use CSwingTiltPermissionVariables | |||||
use CTdsStemJointHeight | |||||
use CTdsConnectionModesEnumVariables | |||||
use CTdsElevatorModesEnumVariables | |||||
use CTdsSpineEnumVariables | |||||
use CTdsSwingEnumVariables | |||||
use CTdsTongEnumVariables | |||||
use CTdsBackupClampVariables | |||||
use CHoistingVariables | |||||
use CTopDrivePanelVariables | |||||
use CTdsPowerLedNotificationVariables | |||||
use CTdsIbopLedNotificationVariables | |||||
use CTdsTorqueWrenchLedNotificationVariables | |||||
implicit none | |||||
public | |||||
real :: HKL = 63.76 ! Hook And Kelly Length | |||||
real :: HL = 17.81 ! Hook Length | |||||
real :: PL = 30.0 ! Pipe Length | |||||
real :: SL = 90.0 ! Stand Length | |||||
real :: LG = 8.0 ! Limit Gap | |||||
real :: SG = 3.0 ! Slips Gap | |||||
real :: TG = 4.0 ! Tong Gap | |||||
real :: RE = 3.0 ! Release | |||||
real :: ECG = 2.3 ! Elevator Connection Gap | |||||
contains | |||||
real(8) function TJH() | |||||
use TD_DrillStemComponents | |||||
implicit none | |||||
TJH = TD_TopJointHeight | |||||
end function | |||||
real function TL() | |||||
implicit none | |||||
TL = 26.97 | |||||
end function | |||||
real function NFC() | |||||
implicit none | |||||
NFC = Get_NearFloorConnection() | |||||
end function | |||||
end module COperationScenariosVariables |
@@ -0,0 +1,618 @@ | |||||
module CElevatorConnectionEnum | |||||
use COperationScenariosVariables | |||||
use CLog3 | |||||
use CLog4 | |||||
implicit none | |||||
contains | |||||
subroutine Evaluate_ElevatorConnection() | |||||
use CCommon, only: SetStandRack | |||||
implicit none | |||||
if (DriveType == TopDrive_DriveType) then | |||||
#ifdef OST | |||||
print*, 'Evaluate_ElevatorConnection=TopDrive' | |||||
#endif | |||||
endif | |||||
if (DriveType == Kelly_DriveType) then | |||||
#ifdef OST | |||||
print*, 'ElevatorConnection=Kelly' | |||||
#endif | |||||
!!OPERATION-CODE=83 | |||||
!if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
! Get_ElevatorConnection() == ELEVATOR_LATCH_STRING .and.& | |||||
! Get_ElevatorPickup() .and.& | |||||
! Get_Slips() == SLIPS_SET_END) then | |||||
! !call Log_4('OPERATION-CODE=83') | |||||
! call Set_ElevatorConnection(ELEVATOR_CONNECTION_STRING) | |||||
! return | |||||
!end if | |||||
!OPERATION-CODE=78 | |||||
if (Get_ElevatorPickup() == .false. .and.& | |||||
Get_Tong() == TONG_BREAKOUT_END .and.& | |||||
Get_HookHeight() <= (HL + Get_NearFloorConnection() + PL) .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) then | |||||
call Set_ElevatorConnection(ELEVATOR_LATCH_SINGLE) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=79 | |||||
if (Get_ElevatorPickup() == .false. .and.& | |||||
Get_Tong() == TONG_BREAKOUT_END .and.& | |||||
Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - LG) .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) then | |||||
call Set_ElevatorConnection(ELEVATOR_LATCH_STAND) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=83 | |||||
if (Get_ElevatorPickup().and.& | |||||
Get_ElevatorConnection() == ELEVATOR_LATCH_SINGLE) then | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_SINGLE) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=84 | |||||
if (Get_ElevatorPickup().and.& | |||||
Get_ElevatorConnection() == ELEVATOR_LATCH_STAND) then | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_STAND) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=7 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
!GetRotaryRpm() == 0.0d0 .and.& | |||||
!Get_StandRack() > 0 .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||||
!Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_Slips() == SLIPS_SET_END .and.& | |||||
!Get_LatchLed() .and. | |||||
Get_Elevator() == ELEVATOR_LATCH_STAND_END) then | |||||
!call Log_4('OPERATION-CODE=7') | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_STAND) | |||||
!call Set_UnlatchLed(.true.) | |||||
!call Set_LatchLed(.false.) | |||||
call SetStandRack(Get_StandRack() - 1) | |||||
call Set_Elevator(ELEVATOR_NEUTRAL) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=8 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) .and.& | |||||
!GetRotaryRpm() == 0.0d0 .and.& | |||||
!Get_StandRack() < 80 .and.& | |||||
!Get_ElevatorConnectionPossible() .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.& | |||||
!Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_Slips() == SLIPS_SET_END .and.& | |||||
!Get_UnlatchLed() .and.& | |||||
Get_Elevator() == ELEVATOR_UNLATCH_STAND_END) then | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_NOTHING) | |||||
!call Set_UnlatchLed(.false.) | |||||
!call Set_LatchLed(.true.) | |||||
call SetStandRack(Get_StandRack() + 1) | |||||
call Set_Elevator(ELEVATOR_NEUTRAL) | |||||
!call Set_Elevator(ELEVATOR_UNLATCH_STAND_BEGIN) | |||||
call Log_3('OPERATION-CODE=8') | |||||
return | |||||
end if | |||||
!OPERATION-CODE=9 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
!Get_HookHeight() >= 18.0 .and. Get_HookHeight() <= 22.0 .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||||
!Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_Slips() == SLIPS_SET_END .and.& | |||||
!Get_LatchLed() .and.& | |||||
!Get_ElevatorPickup() .and.& | |||||
Get_Elevator() == ELEVATOR_LATCH_STRING_END) then | |||||
!call Log_4('OPERATION-CODE=9') | |||||
call Set_ElevatorConnection(ELEVATOR_LATCH_STRING) | |||||
call Set_Elevator(ELEVATOR_NEUTRAL) | |||||
!call Set_UnlatchLed(.true.) | |||||
!call Set_LatchLed(.false.) | |||||
!call Set_UnlatchLed(.false.) | |||||
!call Set_Elevator(ELEVATOR_LATCH_STRING_BEGIN) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=60 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
!Get_HookHeight() <= (HL + Get_NearFloorConnection() - ECG) .and.& | |||||
Get_ElevatorPickup() == .false. .and.& | |||||
Get_Slips() == SLIPS_SET_END .and.& | |||||
!Get_Tong() /= TONG_MAKEUP_END .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING) then | |||||
call Set_ElevatorConnection(ELEVATOR_LATCH_STRING) | |||||
!call Set_Elevator(ELEVATOR_NEUTRAL) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=49 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_ElevatorPickup() .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) then | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_STRING) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=10 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
!GetRotaryRpm() == 0.0d0 .and.& | |||||
(Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .or. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) .and.& | |||||
!Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_Slips() == SLIPS_SET_END .and.& | |||||
!Get_UnlatchLed() .and.& | |||||
Get_Elevator() == ELEVATOR_UNLATCH_STRING_END) then | |||||
!call Log_4('OPERATION-CODE=10') | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_NOTHING) | |||||
call Set_Elevator(ELEVATOR_NEUTRAL) | |||||
!call Set_UnlatchLed(.false.) | |||||
!call Set_LatchLed(.true.) | |||||
!call Set_Elevator(ELEVATOR_UNLATCH_STRING_BEGIN) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=11 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
!Get_ElevatorConnectionPossible() .and.& | |||||
Get_ElevatorPickup().and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||||
!Get_Swing() == SWING_MOUSE_HOLE_END .and.& | |||||
!Get_LatchLed() .and.& | |||||
!Get_FillMouseHoleLed() .and.& | |||||
Get_Elevator() == ELEVATOR_LATCH_SINGLE_END) then | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_SINGLE) | |||||
!call Set_UnlatchLed(.true.) | |||||
call Set_FillMouseHoleLed(.false.) | |||||
call Set_MouseHole(MOUSE_HOLE_NEUTRAL) | |||||
call Set_Elevator(ELEVATOR_NEUTRAL) | |||||
!call Set_Elevator(ELEVATOR_LATCH_SINGLE_BEGIN) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=12 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.& | |||||
!Get_Swing() == SWING_MOUSE_HOLE_END .and.& | |||||
!Get_UnlatchLed() .and.& | |||||
!Get_FillMouseHoleLed() == .false. .and.& | |||||
Get_Elevator() == ELEVATOR_UNLATCH_SINGLE_END) then | |||||
!call Log_4('OPERATION-CODE=12') | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_NOTHING) | |||||
!call Set_UnlatchLed(.false.) | |||||
!call Set_LatchLed(.true.) | |||||
call Set_FillMouseHoleLed(.true.) | |||||
call Set_MouseHole(MOUSE_HOLE_NEUTRAL) | |||||
call Set_Elevator(ELEVATOR_NEUTRAL) | |||||
!call Set_Elevator(ELEVATOR_UNLATCH_SINGLE_BEGIN) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=13 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_HookHeight() <= (HL + Get_NearFloorConnection() + PL) .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.& | |||||
!Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_ElevatorPickup().and.& | |||||
Get_Tong() == TONG_BREAKOUT_END) then | |||||
!call Log_4('OPERATION-CODE=13') | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_SINGLE) | |||||
call Set_StringUpdate(STRING_UPDATE_REMOVE_SINGLE) | |||||
!call Set_StringUpdate(STRING_UPDATE_ADD_SINGLE) | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=14 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_HookHeight() <= (HL + Get_NearFloorConnection() + PL) .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.& | |||||
!Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_ElevatorPickup().and.& | |||||
Get_Tong() == TONG_MAKEUP_END) then | |||||
!call Log_4('OPERATION-CODE=14') | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_STRING) | |||||
call Set_StringUpdate(STRING_UPDATE_ADD_SINGLE) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=15 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - LG) .and.& | |||||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.& | |||||
!Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_ElevatorPickup().and.& | |||||
Get_Tong() == TONG_BREAKOUT_END) then | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_STAND) | |||||
call Set_StringUpdate(STRING_UPDATE_REMOVE_STAND) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=16 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL - RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) .and.& | |||||
!Get_JointConnectionPossible() .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.& | |||||
!Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_ElevatorPickup().and.& | |||||
Get_Tong() == TONG_MAKEUP_END) then | |||||
!call Log_4('OPERATION-CODE=16') | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_ElevatorConnection(ELEVATOR_CONNECTION_STRING) | |||||
call Set_StringUpdate(STRING_UPDATE_ADD_STAND) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=75 | |||||
if (Get_ElevatorPickup() == .false. .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE) then | |||||
call Set_ElevatorConnection(ELEVATOR_LATCH_SINGLE) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=76 | |||||
if (Get_ElevatorPickup() == .false. .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND) then | |||||
call Set_ElevatorConnection(ELEVATOR_LATCH_STAND) | |||||
return | |||||
end if | |||||
endif | |||||
end subroutine | |||||
! subroutine Subscribe_ElevatorConnection() | |||||
! use CDrillingConsoleVariables | |||||
! implicit none | |||||
! call OnLatchPipePress%Add(ButtonPress_Latch_ElevatorConnection) | |||||
! call OnUnlatchPipePress%Add(ButtonPress_Unlatch_ElevatorConnection) | |||||
! call OnBreakoutLeverPress%Add(ButtonPress_Breakout_ElevatorConnection) | |||||
! call OnMakeupLeverPress%Add(ButtonPress_Makeup_ElevatorConnection) | |||||
! end subroutine | |||||
subroutine ButtonPress_Latch_ElevatorConnection() | |||||
use CCommon, only: SetStandRack | |||||
implicit none | |||||
if (DriveType == TopDrive_DriveType) then | |||||
#ifdef OST | |||||
print*, 'ButtonPress_Latch_ElevatorConnection=TopDrive' | |||||
#endif | |||||
!TOPDRIVE-CODE=73 | |||||
if ((Get_HookHeight() >= (TL() + SL - ECG + NFC()) .and. Get_HookHeight() <= (TL() + SL - ECG + NFC() + TG)) .and.& | |||||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | |||||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | |||||
Get_LatchLed()) then | |||||
call Set_Elevator(ELEVATOR_LATCH_STAND_BEGIN) | |||||
call Set_LatchLed(.false.) | |||||
return | |||||
end if | |||||
!TOPDRIVE-CODE=74 | |||||
if (Get_HookHeight() <= (TL() + NFC() - ECG) .and.& | |||||
GetRotaryRpm() == 0.0d0 .and.& | |||||
Get_ElevatorConnectionPossible() .and.& | |||||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | |||||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | |||||
Get_LatchLed()) then | |||||
call Set_Elevator(ELEVATOR_LATCH_STRING_BEGIN) | |||||
call Set_LatchLed(.false.) | |||||
return | |||||
end if | |||||
!TOPDRIVE-CODE=75 | |||||
if (Get_ElevatorConnectionPossible() .and.& | |||||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_NOTHING .and.& | |||||
Get_TdsSwing() == TDS_SWING_TILT_END .and.& | |||||
Get_LatchLed() .and.& | |||||
Get_FillMouseHoleLed()) then | |||||
call Set_Elevator(ELEVATOR_LATCH_SINGLE_BEGIN) | |||||
call Set_LatchLed(.false.) | |||||
return | |||||
end if | |||||
endif | |||||
if (DriveType == Kelly_DriveType) then | |||||
#ifdef OST | |||||
print*, 'ButtonPress_Latch_ElevatorConnection=Kelly' | |||||
#endif | |||||
!OPERATION-CODE=86 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_HookHeight() <= (HL + Get_NearFloorConnection() - ECG) .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||||
Get_LatchLed() .and.& | |||||
GetRotaryRpm() == 0.0d0 .and.& | |||||
Get_Swing() == SWING_WELL_END .and.& | |||||
Get_ElevatorConnectionPossible() .and.& | |||||
Get_HookHeight() <= (HL + Get_NearFloorConnection())) then | |||||
!call Log_4("OPERATION-CODE=ELEVATOR_LATCH_STRING_BEGIN") | |||||
call Set_Elevator(ELEVATOR_LATCH_STRING_BEGIN) | |||||
call Set_LatchLed(.false.) | |||||
return | |||||
endif | |||||
!OPERATION-CODE=85 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_HookHeight() >= (HL + SL - ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (HL + SL - ECG + Get_NearFloorConnection() + LG) .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||||
Get_LatchLed() .and.& | |||||
Get_Swing() == SWING_WELL_END) then | |||||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL + RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) | |||||
call Set_Elevator(ELEVATOR_LATCH_STAND_BEGIN) | |||||
call Set_LatchLed(.false.) | |||||
return | |||||
endif | |||||
!OPERATION-CODE=87 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING .and.& | |||||
Get_LatchLed() .and.& | |||||
Get_FillMouseHoleLed() .and.& | |||||
Get_ElevatorConnectionPossible() .and.& | |||||
Get_Swing() == SWING_MOUSE_HOLE_END) then | |||||
call Set_Elevator(ELEVATOR_LATCH_SINGLE_BEGIN) | |||||
call Set_LatchLed(.false.) | |||||
return | |||||
endif | |||||
endif | |||||
end subroutine | |||||
subroutine ButtonPress_Unlatch_ElevatorConnection() | |||||
use CCommon, only: SetStandRack | |||||
implicit none | |||||
if (DriveType == TopDrive_DriveType) then | |||||
#ifdef OST | |||||
print*, 'ButtonPress_Unlatch_ElevatorConnection=TopDrive' | |||||
#endif | |||||
!TOPDRIVE-CODE=76 | |||||
if ((Get_HookHeight() >= (TL() + SL - ECG + NFC()) .and. Get_HookHeight() <= (TL() + SL - ECG + NFC() + TG)) .and.& | |||||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STAND .and.& | |||||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | |||||
Get_UnlatchLed()) then | |||||
call Set_Elevator(ELEVATOR_UNLATCH_STAND_BEGIN) | |||||
call Set_UnlatchLed(.false.) | |||||
return | |||||
end if | |||||
!TOPDRIVE-CODE=77 | |||||
if (Get_HookHeight() <= (TL() + NFC() - ECG) .and.& | |||||
GetRotaryRpm() == 0.0d0 .and.& | |||||
Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0 .and.& | |||||
(Get_TdsElevatorModes() == TDS_ELEVATOR_LATCH_STRING .or. Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING) .and.& | |||||
Get_TdsSwing() == TDS_SWING_OFF_END .and.& | |||||
Get_UnlatchLed()) then | |||||
call Set_Elevator(ELEVATOR_UNLATCH_STRING_BEGIN) | |||||
call Set_UnlatchLed(.false.) | |||||
return | |||||
end if | |||||
!TOPDRIVE-CODE=78 | |||||
if ((Get_HookHeight() > TL() .and. Get_HookHeight() < (TL() + NFC() + SG)) .and.& | |||||
Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_SINGLE .and.& | |||||
Get_TdsSwing() == TDS_SWING_TILT_END .and.& | |||||
Get_UnlatchLed() .and.& | |||||
Get_FillMouseHoleLed() == .false.) then | |||||
call Set_Elevator(ELEVATOR_UNLATCH_SINGLE_BEGIN) | |||||
call Set_UnlatchLed(.false.) | |||||
return | |||||
end if | |||||
endif | |||||
if (DriveType == Kelly_DriveType) then | |||||
#ifdef OST | |||||
print*, 'ButtonPress_Unlatch_ElevatorConnection=Kelly' | |||||
#endif | |||||
!OPERATION-CODE=89 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_HookHeight() <= (HL + Get_NearFloorConnection() - ECG) .and.& | |||||
(Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .or. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING) .and.& | |||||
Get_HookHeight() <= (HL + Get_NearFloorConnection()) .and.& | |||||
Get_UnlatchLed() .and.& | |||||
GetRotaryRpm() == 0.0d0 .and.& | |||||
Get_Swing() == SWING_WELL_END .and.& | |||||
Get_NearFloorConnection() >= 3.0 .and. Get_NearFloorConnection() <= 6.0) then | |||||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() - 4.0) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() - 2.0)) then | |||||
call Set_Elevator(ELEVATOR_UNLATCH_STRING_BEGIN) | |||||
call Set_UnlatchLed(.false.) | |||||
return | |||||
endif | |||||
!OPERATION-CODE=88 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_HookHeight() >= (HL + SL - ECG + Get_NearFloorConnection()) .and. Get_HookHeight() <= (HL + SL - ECG + Get_NearFloorConnection() + LG) .and.& | |||||
!Get_HookHeight() >= (HL + Get_NearFloorConnection() + SL + RE) .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SL + LG) | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND .and.& | |||||
Get_UnlatchLed() .and.& | |||||
Get_Swing() == SWING_WELL_END) then | |||||
call Set_Elevator(ELEVATOR_UNLATCH_STAND_BEGIN) | |||||
call Set_UnlatchLed(.false.) | |||||
return | |||||
endif | |||||
!OPERATION-CODE=90 | |||||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||||
Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE .and.& | |||||
Get_UnlatchLed() .and.& | |||||
Get_HookHeight() >= HL .and. Get_HookHeight() <= (HL + Get_NearFloorConnection() + SG) .and.& | |||||
!Get_JointConnectionPossible() .and.& | |||||
Get_Swing() == SWING_MOUSE_HOLE_END) then | |||||
call Set_Elevator(ELEVATOR_UNLATCH_SINGLE_BEGIN) | |||||
call Set_UnlatchLed(.false.) | |||||
return | |||||
endif | |||||
endif | |||||
end subroutine | |||||
subroutine ButtonPress_Breakout_ElevatorConnection() | |||||
implicit none | |||||
end subroutine | |||||
subroutine ButtonPress_Makeup_ElevatorConnection() | |||||
implicit none | |||||
end subroutine | |||||
end module CElevatorConnectionEnum |
@@ -0,0 +1,64 @@ | |||||
module CElevatorConnectionEnumVariables | |||||
use CVoidEventHandlerCollection | |||||
implicit none | |||||
integer :: ElevatorConnection = 0 | |||||
public | |||||
type(VoidEventHandlerCollection) :: OnElevatorConnectionChange | |||||
enum, bind(c) | |||||
enumerator ELEVATOR_CONNECTION_NOTHING | |||||
enumerator ELEVATOR_CONNECTION_STRING | |||||
enumerator ELEVATOR_CONNECTION_STAND | |||||
enumerator ELEVATOR_CONNECTION_SINGLE | |||||
enumerator ELEVATOR_LATCH_STRING | |||||
enumerator ELEVATOR_LATCH_SINGLE | |||||
enumerator ELEVATOR_LATCH_STAND | |||||
end enum | |||||
private :: ElevatorConnection | |||||
contains | |||||
subroutine Set_ElevatorConnection(v) | |||||
implicit none | |||||
integer , intent(in) :: v | |||||
#ifdef ExcludeExtraChanges | |||||
if(ElevatorConnection == v) return | |||||
#endif | |||||
ElevatorConnection = v | |||||
#ifdef deb | |||||
print*, 'ElevatorConnection=', ElevatorConnection | |||||
#endif | |||||
call OnElevatorConnectionChange%RunAll() | |||||
end subroutine | |||||
integer function Get_ElevatorConnection() | |||||
implicit none | |||||
Get_ElevatorConnection = ElevatorConnection | |||||
end function | |||||
subroutine Set_ElevatorConnection_WN(v) | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: Set_ElevatorConnection_WN | |||||
!DEC$ ATTRIBUTES ALIAS: 'Set_ElevatorConnection_WN' :: Set_ElevatorConnection_WN | |||||
implicit none | |||||
integer , intent(in) :: v | |||||
call Set_ElevatorConnection(v) | |||||
end subroutine | |||||
integer function Get_ElevatorConnection_WN() | |||||
!DEC$ ATTRIBUTES DLLEXPORT :: Get_ElevatorConnection_WN | |||||
!DEC$ ATTRIBUTES ALIAS: 'Get_ElevatorConnection_WN' :: Get_ElevatorConnection_WN | |||||
implicit none | |||||
Get_ElevatorConnection_WN = ElevatorConnection | |||||
end function | |||||
end module CElevatorConnectionEnumVariables |
@@ -0,0 +1,175 @@ | |||||
module CKellyConnectionEnum | |||||
use COperationScenariosVariables | |||||
use CLog4 | |||||
implicit none | |||||
contains | |||||
subroutine Evaluate_KellyConnection() | |||||
implicit none | |||||
if (DriveType == TopDrive_DriveType) then | |||||
#ifdef OST | |||||
print*, 'Evaluate_KellyConnection=TopDrive' | |||||
#endif | |||||
endif | |||||
if (DriveType == Kelly_DriveType) then | |||||
#ifdef OST | |||||
print*, 'Evaluate_KellyConnection=Kelly' | |||||
#endif | |||||
!!OPERATION-CODE=4 | |||||
!if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||||
! Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.& | |||||
! Get_Swing() == SWING_MOUSE_HOLE_END .and.& | |||||
! Get_TongNotification() .and.& | |||||
! Get_FillMouseHoleLed() == .false. .and.& | |||||
! Get_Tong() == TONG_BREAKOUT_END) then | |||||
! | |||||
! call Set_FillMouseHoleLed(.true.) | |||||
! return | |||||
!end if | |||||
!OPERATION-CODE=1 | |||||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||||
!Get_JointConnectionPossible() .and.& | |||||
Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.& | |||||
Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_Tong() == TONG_MAKEUP_END) then | |||||
!call Log_4('KELLY_CONNECTION_STRING') | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_KellyConnection(KELLY_CONNECTION_STRING) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=2 | |||||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||||
Get_StringPressure() == 0 .and.& | |||||
Get_HookHeight() <= (HKL + Get_NearFloorConnection()) .and.& | |||||
Get_KellyConnection() == KELLY_CONNECTION_STRING .and.& | |||||
Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_Tong() == TONG_BREAKOUT_END) then | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_KellyConnection(KELLY_CONNECTION_NOTHING) | |||||
call Set_SwingLed(.true.) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=3 | |||||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||||
!Get_JointConnectionPossible() .and.& | |||||
Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.& | |||||
Get_Swing() == SWING_MOUSE_HOLE_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_FillMouseHoleLed() .and.& | |||||
Get_Tong() == TONG_MAKEUP_END) then | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_KellyConnection(KELLY_CONNECTION_SINGLE) | |||||
call Set_SwingLed(.false.) | |||||
call Set_FillMouseHoleLed(.false.) | |||||
call Set_MouseHole(MOUSE_HOLE_NEUTRAL) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=4 | |||||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||||
Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.& | |||||
Get_Swing() == SWING_MOUSE_HOLE_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_FillMouseHoleLed() == .false. .and.& | |||||
Get_Tong() == TONG_BREAKOUT_END) then | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_KellyConnection(KELLY_CONNECTION_NOTHING) | |||||
call Set_FillMouseHoleLed(.true.) | |||||
call Set_MouseHole(MOUSE_HOLE_NEUTRAL) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=5 | |||||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||||
!Get_JointConnectionPossible() .and.& | |||||
Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.& | |||||
Get_Swing() == SWING_WELL_END .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_Tong() == TONG_MAKEUP_END) then | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_KellyConnection(KELLY_CONNECTION_STRING) | |||||
call Set_StringUpdate(STRING_UPDATE_ADD_SINGLE) | |||||
call Set_SwingLed(.false.) | |||||
return | |||||
end if | |||||
!OPERATION-CODE=6 | |||||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||||
Get_StringPressure() == 0 .and.& | |||||
Get_HookHeight() > 70.0 .and.& | |||||
Get_KellyConnection() == KELLY_CONNECTION_STRING .and.& | |||||
!Get_TongNotification() .and.& | |||||
Get_Swing() == SWING_WELL_END .and.& | |||||
Get_Tong() == TONG_BREAKOUT_END) then | |||||
call Set_Tong(TONG_NEUTRAL) | |||||
call Set_KellyConnection(KELLY_CONNECTION_SINGLE) | |||||
call Set_StringUpdate(STRING_UPDATE_REMOVE_SINGLE) | |||||
return | |||||
end if | |||||
endif | |||||
end subroutine | |||||
! subroutine Subscribe_KellyConnection() | |||||
! use CDrillingConsoleVariables | |||||
! implicit none | |||||
! call OnBreakoutLeverPress%Add(ButtonPress_Breakout) | |||||
! call OnMakeupLeverPress%Add(ButtonPress_Makeup) | |||||
! end subroutine | |||||
subroutine ButtonPress_Breakout() | |||||
implicit none | |||||
#ifdef deb | |||||
print*, 'ButtonPress_Breakout on ======> CKellyConnectionEnum' | |||||
#endif | |||||
end subroutine | |||||
subroutine ButtonPress_Makeup() | |||||
implicit none | |||||
#ifdef deb | |||||
print*, 'ButtonPress_Makeup on ======> CKellyConnectionEnum' | |||||
#endif | |||||
end subroutine | |||||
end module CKellyConnectionEnum |