module CBitProblemsVariables
    use CProblemDifinition
    use CLog3
	implicit none    
	public 
    
    ! Input vars
    type:: BitProblemsType
        type(CProblem) :: PlugJets
        type(CProblem) :: JetWashout
        integer :: PlugJetsCount
        integer :: JetWashoutCount
        
        ! procedure (ActionInteger), pointer :: PlugJetsPtr
        ! procedure (ActionInteger), pointer :: JetWashoutPtr
    end type BitProblemsType
    type(BitProblemsType)::BitProblems

    contains   

    subroutine ProcessBitProblemsDueTime(time)
        implicit none
        integer :: time
        if(BitProblems%PlugJets%ProblemType == Time_ProblemType) call ProcessDueTime(BitProblems%PlugJets, ChangePlugJets, time)
        if(BitProblems%JetWashout%ProblemType == Time_ProblemType) call ProcessDueTime(BitProblems%JetWashout, ChangeJetWashout, time)
        
    end subroutine
    
    subroutine ProcessBitProblemsDuePumpStrokes(strokes)
        implicit none
        integer :: strokes
        
        if(BitProblems%PlugJets%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BitProblems%PlugJets, ChangePlugJets, strokes)
        if(BitProblems%JetWashout%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(BitProblems%JetWashout, ChangeJetWashout, strokes)
        
    end subroutine
    
    subroutine ProcessBitProblemsDueVolumePumped(volume)
        implicit none
        real(8) :: volume
        
        if(BitProblems%PlugJets%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BitProblems%PlugJets, ChangePlugJets, volume)
        if(BitProblems%JetWashout%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(BitProblems%JetWashout, ChangeJetWashout, volume)
        
    end subroutine
    
    subroutine ProcessBitProblemsDueDistanceDrilled(distance)
        implicit none
        real(8) :: distance
        
        if(BitProblems%PlugJets%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BitProblems%PlugJets, ChangePlugJets, distance)
        if(BitProblems%JetWashout%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(BitProblems%JetWashout, ChangeJetWashout, distance)
        
    end subroutine
    
    subroutine ChangePlugJets(status)
        USE FricPressDropVars
        implicit none
        integer, intent (in) :: status
        ! if(associated(BitProblems%PlugJetsPtr)) call BitProblems%PlugJetsPtr(status)
        if(status == Clear_StatusType)          BitJetsPlugged = 0
        if(status == Executed_StatusType)       BitJetsPlugged = 1
    endsubroutine
    
    subroutine ChangeJetWashout(status)
        USE FricPressDropVars
        implicit none
        integer, intent (in) :: status
        ! if(associated(BitProblems%JetWashoutPtr)) call BitProblems%JetWashoutPtr(status)
        if(status == Clear_StatusType)          BitJetsWashedOut = 0
        if(status == Executed_StatusType)       BitJetsWashedOut = 1
    endsubroutine
    
    
    
    
    
    
    
    
    
    
    ! subroutine SubscribePlugJets(v)
    ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribePlugJets
    ! !DEC$ ATTRIBUTES ALIAS: 'SubscribePlugJets' :: SubscribePlugJets
	!     implicit none
	!     procedure (ActionInteger) :: v
	!     BitProblems%PlugJetsPtr => v
    ! end subroutine

    ! subroutine SubscribeJetWashout(v)
    ! !DEC$ ATTRIBUTES DLLEXPORT :: SubscribeJetWashout
    ! !DEC$ ATTRIBUTES ALIAS: 'SubscribeJetWashout' :: SubscribeJetWashout
	!     implicit none
	!     procedure (ActionInteger) :: v
	!     BitProblems%JetWashoutPtr => v
    ! end subroutine
    
end module CBitProblemsVariables