module CWarningsVariables
    use CWarningsActions    	
    implicit none    
    public    
    
    logical :: PumpWithKellyDisconnected
    logical :: PumpWithTopdriveDisconnected
    logical :: Pump1PopOffValveBlown
    logical :: Pump1Failure
    logical :: Pump2PopOffValveBlown
    logical :: Pump2Failure
    logical :: Pump3PopOffValveBlown
    logical :: Pump3Failure
    logical :: DrawworksGearsAbuse
    logical :: RotaryGearsAbuse
    logical :: HoistLineBreak
    logical :: PartedDrillString
    logical :: ActiveTankOverflow
    logical :: ActiveTankUnderVolume
    logical :: TripTankOverflow
    logical :: DrillPipeTwistOff
    logical :: DrillPipeParted
    logical :: TripWithSlipsSet
    logical :: Blowout
    logical :: UndergroundBlowout
    logical :: MaximumWellDepthExceeded
    logical :: CrownCollision
    logical :: FloorCollision
    logical :: TopdriveRotaryTableConfilict
 
    contains  
    
    subroutine Activate_PumpWithKellyDisconnected()
        implicit none
        if(PumpWithKellyDisconnected) return
        PumpWithKellyDisconnected = .true.
        call RunPumpWithKellyDisconnected()            
    end subroutine
    
    subroutine Activate_PumpWithTopdriveDisconnected()
        implicit none
        if(PumpWithTopdriveDisconnected) return
        PumpWithTopdriveDisconnected = .true.
        call RunPumpWithTopdriveDisconnected()
    end subroutine
    
    subroutine Activate_Pump1PopOffValveBlown()
        implicit none
        if(Pump1PopOffValveBlown) return
        Pump1PopOffValveBlown = .true.
        call RunPump1PopOffValveBlown()
    end subroutine
    
    subroutine Activate_Pump1Failure()
        implicit none
        if(Pump1Failure) return
        Pump1Failure = .true.
        call RunPump1Failure()
    end subroutine
    
    subroutine Activate_Pump2PopOffValveBlown()
        implicit none
        if(Pump2PopOffValveBlown) return
        Pump2PopOffValveBlown = .true.
        call RunPump2PopOffValveBlown()
    end subroutine
    
    subroutine Activate_Pump2Failure()
        implicit none
        if(Pump2Failure) return
        Pump2Failure = .true.
        call RunPump2Failure()
    end subroutine
    
    subroutine Activate_Pump3PopOffValveBlown()
        implicit none
        if(Pump3PopOffValveBlown) return
        Pump3PopOffValveBlown = .true.
        call RunPump3PopOffValveBlown()
    end subroutine
    
    subroutine Activate_Pump3Failure()
        implicit none
        if(Pump3Failure) return
        Pump3Failure = .true.
        call RunPump3Failure()
    end subroutine
    
    subroutine Activate_DrawworksGearsAbuse()
        implicit none
        if(DrawworksGearsAbuse) return
        DrawworksGearsAbuse = .true.
        call RunDrawworksGearsAbuse()
    end subroutine
    
    subroutine Activate_RotaryGearsAbuse()
        implicit none
        if(RotaryGearsAbuse) return
        RotaryGearsAbuse = .true.
        call RunRotaryGearsAbuse()
    end subroutine
    
    subroutine Activate_HoistLineBreak()
        implicit none
        if(HoistLineBreak) return
        HoistLineBreak = .true.
        call RunHoistLineBreak()
    end subroutine
    
    subroutine Activate_PartedDrillString()
        implicit none
        if(PartedDrillString) return
        PartedDrillString = .true.
        call RunPartedDrillString()
    end subroutine
    
    subroutine Activate_ActiveTankOverflow()
        implicit none
        if(ActiveTankOverflow) return
        ActiveTankOverflow = .true.
        call RunActiveTankOverflow()
    end subroutine
    
    subroutine Activate_ActiveTankUnderVolume()
        implicit none
        if(ActiveTankUnderVolume) return
        ActiveTankUnderVolume = .true.
        call RunActiveTankUnderVolume()
    end subroutine
    
    subroutine Activate_TripTankOverflow()
        implicit none
        if(TripTankOverflow) return
        TripTankOverflow = .true.
        call RunTripTankOverflow()
    end subroutine
    
    subroutine Activate_DrillPipeTwistOff()
        implicit none
        if(DrillPipeTwistOff) return
        DrillPipeTwistOff = .true.
        call RunDrillPipeTwistOff()
    end subroutine
    
    subroutine Activate_DrillPipeParted()
        implicit none
        if(DrillPipeParted) return
        DrillPipeParted = .true.
        call RunDrillPipeParted()
    end subroutine
    
    subroutine Activate_TripWithSlipsSet()
        implicit none
        if(TripWithSlipsSet) return
        TripWithSlipsSet = .true.
        call RunTripWithSlipsSet()
    end subroutine
    
    subroutine Activate_Blowout()
        implicit none
        if(Blowout) return
        Blowout = .true.
        call RunBlowout()
    end subroutine
    
    subroutine Activate_UndergroundBlowout()
        implicit none
        if(UndergroundBlowout) return
        UndergroundBlowout = .true.
        call RunUndergroundBlowout()
    end subroutine
    
    subroutine Activate_MaximumWellDepthExceeded()
        implicit none
        if(MaximumWellDepthExceeded) return
        MaximumWellDepthExceeded = .true.
        call RunMaximumWellDepthExceeded()
    end subroutine
    
    subroutine Activate_CrownCollision()
        implicit none
        if(CrownCollision) return
        CrownCollision = .true.
        call RunCrownCollision()
    end subroutine
    
    subroutine Activate_FloorCollision()
        implicit none
        if(FloorCollision) return
        FloorCollision = .true.
        call RunFloorCollision()
    end subroutine
    
    subroutine Activate_TopdriveRotaryTableConfilict()
        implicit none
        if(TopdriveRotaryTableConfilict) return
        TopdriveRotaryTableConfilict = .true.
        call RunTopdriveRotaryTableConfilict()
    end subroutine
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    subroutine Deactivate_PumpWithKellyDisconnected()
        implicit none
        if(.not.PumpWithKellyDisconnected) return
        PumpWithKellyDisconnected = .false.
        call RunPumpWithKellyDisconnected()
    end subroutine
    
    subroutine Deactivate_PumpWithTopdriveDisconnected()
        implicit none
        if(.not.PumpWithTopdriveDisconnected) return
        PumpWithTopdriveDisconnected = .false.
        call RunPumpWithTopdriveDisconnected()
    end subroutine
    
    subroutine Deactivate_Pump1PopOffValveBlown()
        use CManifolds
        implicit none
        if(.not.Pump1PopOffValveBlown) return
        Pump1PopOffValveBlown = .false.
        call ChangeValve(65, .false.)
        call RunPump1PopOffValveBlown()
    end subroutine
    
    subroutine Deactivate_Pump1Failure()
        use CManifolds
        implicit none
        if(.not.Pump1Failure) return
        Pump1Failure = .false.
        call RunPump1Failure()
    end subroutine
    
    subroutine Deactivate_Pump2PopOffValveBlown()
        use CManifolds
        implicit none
        if(.not.Pump2PopOffValveBlown) return
        Pump2PopOffValveBlown = .false.
        call ChangeValve(66, .false.)
        call RunPump2PopOffValveBlown()
    end subroutine
    
    subroutine Deactivate_Pump2Failure()
        use CManifolds
        implicit none
        if(.not.Pump2Failure) return
        Pump2Failure = .false.
        call RunPump2Failure()
    end subroutine
    
    subroutine Deactivate_Pump3PopOffValveBlown()
        use CManifolds
        implicit none
        if(.not.Pump3PopOffValveBlown) return
        Pump3PopOffValveBlown = .false.
        call RunPump3PopOffValveBlown()
    end subroutine
    
    subroutine Deactivate_Pump3Failure()
        use CManifolds
        implicit none
        if(.not.Pump3Failure) return
        Pump3Failure = .false.
        call RunPump3Failure()
    end subroutine
    
    subroutine Deactivate_DrawworksGearsAbuse()
        implicit none
        if(.not.DrawworksGearsAbuse) return
        DrawworksGearsAbuse = .false.
        call RunDrawworksGearsAbuse()
    end subroutine
    
    subroutine Deactivate_RotaryGearsAbuse()
        implicit none
        if(.not.RotaryGearsAbuse) return
        RotaryGearsAbuse = .false.
        call RunRotaryGearsAbuse()
    end subroutine
    
    subroutine Deactivate_HoistLineBreak()
        implicit none
        if(.not.HoistLineBreak) return
        HoistLineBreak = .false.
        call RunHoistLineBreak()
    end subroutine
    
    subroutine Deactivate_PartedDrillString()
        implicit none
        if(.not.PartedDrillString) return
        PartedDrillString = .false.
        call RunPartedDrillString()
    end subroutine
    
    subroutine Deactivate_ActiveTankOverflow()
        implicit none
        if(.not.ActiveTankOverflow) return
        ActiveTankOverflow = .false.
        call RunActiveTankOverflow()
    end subroutine
    
    subroutine Deactivate_ActiveTankUnderVolume()
        implicit none
        if(.not.ActiveTankUnderVolume) return
        ActiveTankUnderVolume = .false.
        call RunActiveTankUnderVolume()
    end subroutine
    
    subroutine Deactivate_TripTankOverflow()
        implicit none
        if(.not.TripTankOverflow) return
        TripTankOverflow = .false.
        call RunTripTankOverflow()
    end subroutine
    
    subroutine Deactivate_DrillPipeTwistOff()
        implicit none
        if(.not.DrillPipeTwistOff) return
        DrillPipeTwistOff = .false.
        call RunDrillPipeTwistOff()
    end subroutine
    
    subroutine Deactivate_DrillPipeParted()
        implicit none
        if(.not.DrillPipeParted) return
        DrillPipeParted = .false.
        call RunDrillPipeParted()
    end subroutine
    
    subroutine Deactivate_TripWithSlipsSet()
        implicit none
        if(.not.TripWithSlipsSet) return
        TripWithSlipsSet = .false.
        call RunTripWithSlipsSet()
    end subroutine
    
    subroutine Deactivate_Blowout()
        implicit none
        if(.not.Blowout) return
        Blowout = .false.
        call RunBlowout()
    end subroutine
    
    subroutine Deactivate_UndergroundBlowout()
        implicit none
        if(.not.UndergroundBlowout) return
        UndergroundBlowout = .false.
        call RunUndergroundBlowout()
    end subroutine
    
    subroutine Deactivate_MaximumWellDepthExceeded()
        implicit none
        if(.not.MaximumWellDepthExceeded) return
        MaximumWellDepthExceeded = .false.
        call RunMaximumWellDepthExceeded()
    end subroutine
    
    subroutine Deactivate_CrownCollision()
        implicit none
        if(.not.CrownCollision) return
        CrownCollision = .false.
        call RunCrownCollision()
    end subroutine
    
    subroutine Deactivate_FloorCollision()
        implicit none
        if(.not.FloorCollision) return
        FloorCollision = .false.
        call RunFloorCollision()
    end subroutine
    
    subroutine Deactivate_TopdriveRotaryTableConfilict()
        implicit none
        if(.not.TopdriveRotaryTableConfilict) return
        TopdriveRotaryTableConfilict = .false.
        call RunTopdriveRotaryTableConfilict()
    end subroutine
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    subroutine RunPumpWithKellyDisconnected()
        implicit none
        if(associated(PumpWithKellyDisconnectedPtr)) then 
            call PumpWithKellyDisconnectedPtr(PumpWithKellyDisconnected)          
        end if
    end subroutine
    
    subroutine RunPumpWithTopdriveDisconnected()
		implicit none
		if(associated(PumpWithTopdriveDisconnectedPtr)) then 
			call PumpWithTopdriveDisconnectedPtr(PumpWithTopdriveDisconnected)
		end if
    end subroutine
    
    subroutine RunPump1PopOffValveBlown()
		implicit none
		if(associated(Pump1PopOffValveBlownPtr)) then 
			call Pump1PopOffValveBlownPtr(Pump1PopOffValveBlown)
		end if
    end subroutine
    
    subroutine RunPump1Failure()
		implicit none
		if(associated(Pump1FailurePtr)) then 
			call Pump1FailurePtr(Pump1Failure)
		end if
    end subroutine
    
    subroutine RunPump2PopOffValveBlown()
		implicit none
		if(associated(Pump2PopOffValveBlownPtr)) then 
			call Pump2PopOffValveBlownPtr(Pump2PopOffValveBlown)
		end if
    end subroutine
    
    subroutine RunPump2Failure()
		implicit none
		if(associated(Pump2FailurePtr)) then 
			call Pump2FailurePtr(Pump2Failure)
		end if
    end subroutine
    
    subroutine RunPump3PopOffValveBlown()
		implicit none
		if(associated(Pump3PopOffValveBlownPtr)) then 
			call Pump3PopOffValveBlownPtr(Pump3PopOffValveBlown)
		end if
    end subroutine
    
    subroutine RunPump3Failure()
		implicit none
		if(associated(Pump3FailurePtr)) then 
			call Pump3FailurePtr(Pump3Failure)
		end if
    end subroutine
    
    subroutine RunDrawworksGearsAbuse()
		implicit none
		if(associated(DrawworksGearsAbusePtr)) then 
			call DrawworksGearsAbusePtr(DrawworksGearsAbuse)
		end if
    end subroutine
    
    subroutine RunRotaryGearsAbuse()
		implicit none
		if(associated(RotaryGearsAbusePtr)) then 
			call RotaryGearsAbusePtr(RotaryGearsAbuse)
		end if
    end subroutine
    
    subroutine RunHoistLineBreak()
		implicit none
		if(associated(HoistLineBreakPtr)) then 
			call HoistLineBreakPtr(HoistLineBreak)
		end if
    end subroutine
    
    subroutine RunPartedDrillString()
		implicit none
		if(associated(PartedDrillStringPtr)) then 
			call PartedDrillStringPtr(PartedDrillString)
		end if
    end subroutine
    
    subroutine RunActiveTankOverflow()
		implicit none
		if(associated(ActiveTankOverflowPtr)) then 
			call ActiveTankOverflowPtr(ActiveTankOverflow)
		end if
    end subroutine
    
    subroutine RunActiveTankUnderVolume()
		implicit none
		if(associated(ActiveTankUnderVolumePtr)) then 
			call ActiveTankUnderVolumePtr(ActiveTankUnderVolume)
		end if
    end subroutine
    
    subroutine RunTripTankOverflow()
		implicit none
		if(associated(TripTankOverflowPtr)) then 
			call TripTankOverflowPtr(TripTankOverflow)
		end if
    end subroutine
    
    subroutine RunDrillPipeTwistOff()
		implicit none
		if(associated(DrillPipeTwistOffPtr)) then 
			call DrillPipeTwistOffPtr(DrillPipeTwistOff)
		end if
    end subroutine
    
    subroutine RunDrillPipeParted()
		implicit none
		if(associated(DrillPipePartedPtr)) then 
			call DrillPipePartedPtr(DrillPipeParted)
		end if
    end subroutine
    
    subroutine RunTripWithSlipsSet()
		implicit none
		if(associated(TripWithSlipsSetPtr)) then 
			call TripWithSlipsSetPtr(TripWithSlipsSet)
		end if
    end subroutine
    
    subroutine RunBlowout()
		implicit none
		if(associated(BlowoutPtr)) then 
			call BlowoutPtr(Blowout)
		end if
    end subroutine
    
    subroutine RunUndergroundBlowout()
		implicit none
		if(associated(UndergroundBlowoutPtr)) then 
			call UndergroundBlowoutPtr(UndergroundBlowout)
		end if
    end subroutine
    
    subroutine RunMaximumWellDepthExceeded()
		implicit none
		if(associated(MaximumWellDepthExceededPtr)) then 
			call MaximumWellDepthExceededPtr(MaximumWellDepthExceeded)
		end if
    end subroutine
    
    subroutine RunCrownCollision()
		implicit none
		if(associated(CrownCollisionPtr)) then 
			call CrownCollisionPtr(CrownCollision)
		end if
    end subroutine
    
    subroutine RunFloorCollision()
		implicit none
		if(associated(FloorCollisionPtr)) then 
			call FloorCollisionPtr(FloorCollision)
		end if
    end subroutine
    
    subroutine RunTopdriveRotaryTableConfilict()
		implicit none
		if(associated(TopdriveRotaryTableConfilictPtr)) then 
			call TopdriveRotaryTableConfilictPtr(TopdriveRotaryTableConfilict)
		end if
    end subroutine
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    subroutine Activate_PumpWithKellyDisconnected_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_PumpWithKellyDisconnected_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_PumpWithKellyDisconnected_WN' :: Activate_PumpWithKellyDisconnected_WN
        implicit none
        call Activate_PumpWithKellyDisconnected()
    end subroutine
    
    subroutine Activate_PumpWithTopdriveDisconnected_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_PumpWithTopdriveDisconnected_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_PumpWithTopdriveDisconnected_WN' :: Activate_PumpWithTopdriveDisconnected_WN
        implicit none
        call Activate_PumpWithTopdriveDisconnected()
    end subroutine
    
    subroutine Activate_Pump1PopOffValveBlown_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_Pump1PopOffValveBlown_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_Pump1PopOffValveBlown_WN' :: Activate_Pump1PopOffValveBlown_WN
        implicit none
        call Activate_Pump1PopOffValveBlown()
    end subroutine
    
    subroutine Activate_Pump1Failure_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_Pump1Failure_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_Pump1Failure_WN' :: Activate_Pump1Failure_WN
        implicit none
        call Activate_Pump1Failure()
    end subroutine
    
    subroutine Activate_Pump2PopOffValveBlown_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_Pump2PopOffValveBlown_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_Pump2PopOffValveBlown_WN' :: Activate_Pump2PopOffValveBlown_WN
        implicit none
        call Activate_Pump2PopOffValveBlown()
    end subroutine
    
    subroutine Activate_Pump2Failure_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_Pump2Failure_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_Pump2Failure_WN' :: Activate_Pump2Failure_WN
        implicit none
        call Activate_Pump2Failure()
    end subroutine
    
    subroutine Activate_Pump3PopOffValveBlown_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_Pump3PopOffValveBlown_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_Pump3PopOffValveBlown_WN' :: Activate_Pump3PopOffValveBlown_WN
        implicit none
        call Activate_Pump3PopOffValveBlown()
    end subroutine
    
    subroutine Activate_Pump3Failure_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_Pump3Failure_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_Pump3Failure_WN' :: Activate_Pump3Failure_WN
        implicit none
        call Activate_Pump3Failure()
    end subroutine
    
    subroutine Activate_DrawworksGearsAbuse_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_DrawworksGearsAbuse_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_DrawworksGearsAbuse_WN' :: Activate_DrawworksGearsAbuse_WN
        implicit none
        call Activate_DrawworksGearsAbuse()
    end subroutine
    
    subroutine Activate_RotaryGearsAbuse_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_RotaryGearsAbuse_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_RotaryGearsAbuse_WN' :: Activate_RotaryGearsAbuse_WN
        implicit none
        call Activate_RotaryGearsAbuse()
    end subroutine
    
    subroutine Activate_HoistLineBreak_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_HoistLineBreak_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_HoistLineBreak_WN' :: Activate_HoistLineBreak_WN
        implicit none
        call Activate_HoistLineBreak()
    end subroutine
    
    subroutine Activate_PartedDrillString_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_PartedDrillString_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_PartedDrillString_WN' :: Activate_PartedDrillString_WN
        implicit none
        call Activate_PartedDrillString()
    end subroutine
    
    subroutine Activate_ActiveTankOverflow_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_ActiveTankOverflow_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_ActiveTankOverflow_WN' :: Activate_ActiveTankOverflow_WN
        implicit none
        call Activate_ActiveTankOverflow()
    end subroutine
    
    subroutine Activate_ActiveTankUnderVolume_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_ActiveTankUnderVolume_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_ActiveTankUnderVolume_WN' :: Activate_ActiveTankUnderVolume_WN
        implicit none
        call Activate_ActiveTankUnderVolume()
    end subroutine
    
    subroutine Activate_TripTankOverflow_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_TripTankOverflow_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_TripTankOverflow_WN' :: Activate_TripTankOverflow_WN
        implicit none
        call Activate_TripTankOverflow()
    end subroutine
    
    subroutine Activate_DrillPipeTwistOff_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_DrillPipeTwistOff_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_DrillPipeTwistOff_WN' :: Activate_DrillPipeTwistOff_WN
        implicit none
        call Activate_DrillPipeTwistOff()
    end subroutine
    
    subroutine Activate_DrillPipeParted_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_DrillPipeParted_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_DrillPipeParted_WN' :: Activate_DrillPipeParted_WN
        implicit none
        call Activate_DrillPipeParted()
    end subroutine
    
    subroutine Activate_TripWithSlipsSet_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_TripWithSlipsSet_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_TripWithSlipsSet_WN' :: Activate_TripWithSlipsSet_WN
        implicit none
        call Activate_TripWithSlipsSet()
    end subroutine
    
    subroutine Activate_Blowout_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_Blowout_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_Blowout_WN' :: Activate_Blowout_WN
        implicit none
        call Activate_Blowout()
    end subroutine
    
    subroutine Activate_UndergroundBlowout_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_UndergroundBlowout_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_UndergroundBlowout_WN' :: Activate_UndergroundBlowout_WN
        implicit none
        call Activate_UndergroundBlowout()
    end subroutine
    
    subroutine Activate_MaximumWellDepthExceeded_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_MaximumWellDepthExceeded_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_MaximumWellDepthExceeded_WN' :: Activate_MaximumWellDepthExceeded_WN
        implicit none
        call Activate_MaximumWellDepthExceeded()
    end subroutine
    
    subroutine Activate_CrownCollision_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_CrownCollision_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_CrownCollision_WN' :: Activate_CrownCollision_WN
        implicit none
        call Activate_CrownCollision()
    end subroutine
    
    subroutine Activate_FloorCollision_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_FloorCollision_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_FloorCollision_WN' :: Activate_FloorCollision_WN
        implicit none
        call Activate_FloorCollision()
    end subroutine
    
    subroutine Activate_TopdriveRotaryTableConfilict_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Activate_TopdriveRotaryTableConfilict_WN
    !DEC$ ATTRIBUTES ALIAS: 'Activate_TopdriveRotaryTableConfilict_WN' :: Activate_TopdriveRotaryTableConfilict_WN
        implicit none
        call Activate_TopdriveRotaryTableConfilict()
    end subroutine
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    subroutine Deactivate_PumpWithKellyDisconnected_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_PumpWithKellyDisconnected_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_PumpWithKellyDisconnected_WN' :: Deactivate_PumpWithKellyDisconnected_WN
        implicit none
        call Deactivate_PumpWithKellyDisconnected()
    end subroutine
    
    subroutine Deactivate_PumpWithTopdriveDisconnected_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_PumpWithTopdriveDisconnected_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_PumpWithTopdriveDisconnected_WN' :: Deactivate_PumpWithTopdriveDisconnected_WN
        implicit none
        call Deactivate_PumpWithTopdriveDisconnected()
    end subroutine
    
    subroutine Deactivate_Pump1PopOffValveBlown_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_Pump1PopOffValveBlown_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_Pump1PopOffValveBlown_WN' :: Deactivate_Pump1PopOffValveBlown_WN
        implicit none
        call Deactivate_Pump1PopOffValveBlown()
    end subroutine
    
    subroutine Deactivate_Pump1Failure_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_Pump1Failure_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_Pump1Failure_WN' :: Deactivate_Pump1Failure_WN
        implicit none
        call Deactivate_Pump1Failure()
    end subroutine
    
    subroutine Deactivate_Pump2PopOffValveBlown_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_Pump2PopOffValveBlown_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_Pump2PopOffValveBlown_WN' :: Deactivate_Pump2PopOffValveBlown_WN
        implicit none
        call Deactivate_Pump2PopOffValveBlown()
    end subroutine
    
    subroutine Deactivate_Pump2Failure_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_Pump2Failure_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_Pump2Failure_WN' :: Deactivate_Pump2Failure_WN
        implicit none
        call Deactivate_Pump2Failure()
    end subroutine
    
    subroutine Deactivate_Pump3PopOffValveBlown_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_Pump3PopOffValveBlown_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_Pump3PopOffValveBlown_WN' :: Deactivate_Pump3PopOffValveBlown_WN
        implicit none
        call Deactivate_Pump3PopOffValveBlown()
    end subroutine
    
    subroutine Deactivate_Pump3Failure_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_Pump3Failure_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_Pump3Failure_WN' :: Deactivate_Pump3Failure_WN
        implicit none
        call Deactivate_Pump3Failure()
    end subroutine
    
    subroutine Deactivate_DrawworksGearsAbuse_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_DrawworksGearsAbuse_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_DrawworksGearsAbuse_WN' :: Deactivate_DrawworksGearsAbuse_WN
        implicit none
        call Deactivate_DrawworksGearsAbuse()
    end subroutine
    
    subroutine Deactivate_RotaryGearsAbuse_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_RotaryGearsAbuse_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_RotaryGearsAbuse_WN' :: Deactivate_RotaryGearsAbuse_WN
        implicit none
        call Deactivate_RotaryGearsAbuse()
    end subroutine
    
    subroutine Deactivate_HoistLineBreak_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_HoistLineBreak_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_HoistLineBreak_WN' :: Deactivate_HoistLineBreak_WN
        implicit none
        call Deactivate_HoistLineBreak()
    end subroutine
    
    subroutine Deactivate_PartedDrillString_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_PartedDrillString_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_PartedDrillString_WN' :: Deactivate_PartedDrillString_WN
        implicit none
        call Deactivate_PartedDrillString()
    end subroutine
    
    subroutine Deactivate_ActiveTankOverflow_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_ActiveTankOverflow_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_ActiveTankOverflow_WN' :: Deactivate_ActiveTankOverflow_WN
        implicit none
        call Deactivate_ActiveTankOverflow()
    end subroutine
    
    subroutine Deactivate_ActiveTankUnderVolume_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_ActiveTankUnderVolume_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_ActiveTankUnderVolume_WN' :: Deactivate_ActiveTankUnderVolume_WN
        implicit none
        call Deactivate_ActiveTankUnderVolume()
    end subroutine
    
    subroutine Deactivate_TripTankOverflow_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_TripTankOverflow_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_TripTankOverflow_WN' :: Deactivate_TripTankOverflow_WN
        implicit none
        call Deactivate_TripTankOverflow()
    end subroutine
    
    subroutine Deactivate_DrillPipeTwistOff_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_DrillPipeTwistOff_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_DrillPipeTwistOff_WN' :: Deactivate_DrillPipeTwistOff_WN
        implicit none
        call Deactivate_DrillPipeTwistOff()
    end subroutine
    
    subroutine Deactivate_DrillPipeParted_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_DrillPipeParted_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_DrillPipeParted_WN' :: Deactivate_DrillPipeParted_WN
        implicit none
        call Deactivate_DrillPipeParted()
    end subroutine
    
    subroutine Deactivate_TripWithSlipsSet_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_TripWithSlipsSet_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_TripWithSlipsSet_WN' :: Deactivate_TripWithSlipsSet_WN
        implicit none
        call Deactivate_TripWithSlipsSet()
    end subroutine
    
    subroutine Deactivate_Blowout_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_Blowout_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_Blowout_WN' :: Deactivate_Blowout_WN
        implicit none
        call Deactivate_Blowout()
    end subroutine
    
    subroutine Deactivate_UndergroundBlowout_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_UndergroundBlowout_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_UndergroundBlowout_WN' :: Deactivate_UndergroundBlowout_WN
        implicit none
        call Deactivate_UndergroundBlowout()
    end subroutine
    
    subroutine Deactivate_MaximumWellDepthExceeded_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_MaximumWellDepthExceeded_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_MaximumWellDepthExceeded_WN' :: Deactivate_MaximumWellDepthExceeded_WN
        implicit none
        call Deactivate_MaximumWellDepthExceeded()
    end subroutine
    
    subroutine Deactivate_CrownCollision_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_CrownCollision_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_CrownCollision_WN' :: Deactivate_CrownCollision_WN
        implicit none
        call Deactivate_CrownCollision()
    end subroutine
    
    subroutine Deactivate_FloorCollision_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_FloorCollision_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_FloorCollision_WN' :: Deactivate_FloorCollision_WN
        implicit none
        call Deactivate_FloorCollision()
    end subroutine
    
    subroutine Deactivate_TopdriveRotaryTableConfilict_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Deactivate_TopdriveRotaryTableConfilict_WN
    !DEC$ ATTRIBUTES ALIAS: 'Deactivate_TopdriveRotaryTableConfilict_WN' :: Deactivate_TopdriveRotaryTableConfilict_WN
        implicit none
        call Deactivate_TopdriveRotaryTableConfilict()
    end subroutine
    
    
    
    
    
    
end module CWarningsVariables