module CPumpProblems
    use SimulationVariables
	implicit none    
	public 
    contains
    subroutine PumpProblemsFromJson(parent)
        type(json_value),pointer :: parent
        type(json_core) :: json
        type(json_value),pointer :: p

        call json%get(parent,'PumpProblems',p)
        call ProblemFromJson(p,"Pump1PowerFail",data%problems%PumpProblems%Pump1PowerFail)
        call ProblemFromJson(p,"Pump1BlowPopOffValve",data%problems%PumpProblems%Pump1BlowPopOffValve)
        call ProblemFromJson(p,"Pump2PowerFail",data%problems%PumpProblems%Pump2PowerFail)
        call ProblemFromJson(p,"Pump2BlowPopOffValve",data%problems%PumpProblems%Pump2BlowPopOffValve)
        call ProblemFromJson(p,"CementPumpPowerFail",data%problems%PumpProblems%CementPumpPowerFail)
        call ProblemFromJson(p,"CementPumpBlowPopOffValve",data%problems%PumpProblems%CementPumpBlowPopOffValve)
    end subroutine
    
    subroutine PumpProblemsToJson(parent)

        type(json_value),pointer :: parent
        type(json_core) :: json
        type(json_value),pointer :: p

        ! 1. create new node
        call json%create_object(p,'PumpProblems')
        
        ! 2. add member of data type to new node
        call ProblemToJson(p,"Pump1PowerFail",data%problems%PumpProblems%Pump1PowerFail)
        call ProblemToJson(p,"Pump1BlowPopOffValve",data%problems%PumpProblems%Pump1BlowPopOffValve)
        call ProblemToJson(p,"Pump2PowerFail",data%problems%PumpProblems%Pump2PowerFail)
        call ProblemToJson(p,"Pump2BlowPopOffValve",data%problems%PumpProblems%Pump2BlowPopOffValve)
        call ProblemToJson(p,"CementPumpPowerFail",data%problems%PumpProblems%CementPumpPowerFail)
        call ProblemToJson(p,"CementPumpBlowPopOffValve",data%problems%PumpProblems%CementPumpBlowPopOffValve)
        
        ! 3. add new node to parent
        call json%add(parent,p)
    end subroutine

    subroutine ProcessPumpProblemsDueTime(time)
        implicit none
        integer :: time
        
        if(data%problems%PumpProblems%Pump1PowerFail%ProblemType == Time_ProblemType) call ProcessDueTime(data%problems%PumpProblems%Pump1PowerFail, ChangePump1PowerFail, time)
        if(data%problems%PumpProblems%Pump1BlowPopOffValve%ProblemType == Time_ProblemType) call ProcessDueTime(data%problems%PumpProblems%Pump1BlowPopOffValve, ChangePump1BlowPopOffValve, time)
        if(data%problems%PumpProblems%Pump2PowerFail%ProblemType == Time_ProblemType) call ProcessDueTime(data%problems%PumpProblems%Pump2PowerFail, ChangePump2PowerFail, time)
        if(data%problems%PumpProblems%Pump2BlowPopOffValve%ProblemType == Time_ProblemType) call ProcessDueTime(data%problems%PumpProblems%Pump2BlowPopOffValve, ChangePump2BlowPopOffValve, time)
        if(data%problems%PumpProblems%CementPumpPowerFail%ProblemType == Time_ProblemType) call ProcessDueTime(data%problems%PumpProblems%CementPumpPowerFail, ChangeCementPumpPowerFail, time)
        if(data%problems%PumpProblems%CementPumpBlowPopOffValve%ProblemType == Time_ProblemType) call ProcessDueTime(data%problems%PumpProblems%CementPumpBlowPopOffValve, ChangeCementPumpBlowPopOffValve, time)
        
    end subroutine
	
	subroutine ProcessPumpProblemsDuePumpStrokes(strokes)
        implicit none
        integer :: strokes
        
        if(data%problems%PumpProblems%Pump1PowerFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(data%problems%PumpProblems%Pump1PowerFail, ChangePump1PowerFail, strokes)
        if(data%problems%PumpProblems%Pump1BlowPopOffValve%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(data%problems%PumpProblems%Pump1BlowPopOffValve, ChangePump1BlowPopOffValve, strokes)
        if(data%problems%PumpProblems%Pump2PowerFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(data%problems%PumpProblems%Pump2PowerFail, ChangePump2PowerFail, strokes)
        if(data%problems%PumpProblems%Pump2BlowPopOffValve%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(data%problems%PumpProblems%Pump2BlowPopOffValve, ChangePump2BlowPopOffValve, strokes)
        if(data%problems%PumpProblems%CementPumpPowerFail%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(data%problems%PumpProblems%CementPumpPowerFail, ChangeCementPumpPowerFail, strokes)
        if(data%problems%PumpProblems%CementPumpBlowPopOffValve%ProblemType == PumpStrokes_ProblemType) call ProcessDuePumpStrokes(data%problems%PumpProblems%CementPumpBlowPopOffValve, ChangeCementPumpBlowPopOffValve, strokes)
        
    end subroutine
	
	subroutine ProcessPumpProblemsDueVolumePumped(volume)
        implicit none
        real(8) :: volume
        
        if(data%problems%PumpProblems%Pump1PowerFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(data%problems%PumpProblems%Pump1PowerFail, ChangePump1PowerFail, volume)
        if(data%problems%PumpProblems%Pump1BlowPopOffValve%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(data%problems%PumpProblems%Pump1BlowPopOffValve, ChangePump1BlowPopOffValve, volume)
        if(data%problems%PumpProblems%Pump2PowerFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(data%problems%PumpProblems%Pump2PowerFail, ChangePump2PowerFail, volume)
        if(data%problems%PumpProblems%Pump2BlowPopOffValve%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(data%problems%PumpProblems%Pump2BlowPopOffValve, ChangePump2BlowPopOffValve, volume)
        if(data%problems%PumpProblems%CementPumpPowerFail%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(data%problems%PumpProblems%CementPumpPowerFail, ChangeCementPumpPowerFail, volume)
        if(data%problems%PumpProblems%CementPumpBlowPopOffValve%ProblemType == VolumePumped_ProblemType) call ProcessDueVolumePumped(data%problems%PumpProblems%CementPumpBlowPopOffValve, ChangeCementPumpBlowPopOffValve, volume)
        
    end subroutine
	
	subroutine ProcessPumpProblemsDueDistanceDrilled(distance)
        implicit none
        real(8) :: distance
        
        if(data%problems%PumpProblems%Pump1PowerFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(data%problems%PumpProblems%Pump1PowerFail, ChangePump1PowerFail, distance)
        if(data%problems%PumpProblems%Pump1BlowPopOffValve%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(data%problems%PumpProblems%Pump1BlowPopOffValve, ChangePump1BlowPopOffValve, distance)
        if(data%problems%PumpProblems%Pump2PowerFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(data%problems%PumpProblems%Pump2PowerFail, ChangePump2PowerFail, distance)
        if(data%problems%PumpProblems%Pump2BlowPopOffValve%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(data%problems%PumpProblems%Pump2BlowPopOffValve, ChangePump2BlowPopOffValve, distance)
        if(data%problems%PumpProblems%CementPumpPowerFail%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(data%problems%PumpProblems%CementPumpPowerFail, ChangeCementPumpPowerFail, distance)
        if(data%problems%PumpProblems%CementPumpBlowPopOffValve%ProblemType == DistanceDrilled_ProblemType) call ProcessDueDistanceDrilled(data%problems%PumpProblems%CementPumpBlowPopOffValve, ChangeCementPumpBlowPopOffValve, distance)
        
    end subroutine
	
	
	
	
	
	
	
	
	
	
    
    subroutine ChangePump1PowerFail(status)
        use SimulationVariables
        implicit none
        integer, intent (in) :: status
        !if(associated(Pump1PowerFailPtr)) call Pump1PowerFailPtr(status)
        if(status == Clear_StatusType)     data%State%Pump(1)%PowerFailMalf=0
        if(status == Executed_StatusType)  data%State%Pump(1)%PowerFailMalf=1
    endsubroutine
    
    subroutine ChangePump1BlowPopOffValve(status)
        use SimulationVariables
        implicit none
        integer, intent (in) :: status
        !if(associated(Pump1BlowPopOffValvePtr)) call Pump1BlowPopOffValvePtr(status)
        if(status == Clear_StatusType)     data%State%Pump(1)%BlowPopOffMalf=0
        if(status == Executed_StatusType)  data%State%Pump(1)%BlowPopOffMalf=1
    endsubroutine
    
    subroutine ChangePump2PowerFail(status)
        use SimulationVariables
        implicit none
        integer, intent (in) :: status
        !if(associated(Pump2PowerFailPtr)) call Pump2PowerFailPtr(status)
        if(status == Clear_StatusType)     data%State%Pump(2)%PowerFailMalf=0
        if(status == Executed_StatusType)  data%State%Pump(2)%PowerFailMalf=1
    endsubroutine
    
    subroutine ChangePump2BlowPopOffValve(status)
        use SimulationVariables
        implicit none
        integer, intent (in) :: status
        !if(associated(Pump2BlowPopOffValvePtr)) call Pump2BlowPopOffValvePtr(status)
        if(status == Clear_StatusType)     data%State%Pump(2)%BlowPopOffMalf=0
        if(status == Executed_StatusType)  data%State%Pump(2)%BlowPopOffMalf=1
    endsubroutine
    
    subroutine ChangeCementPumpPowerFail(status)
        use SimulationVariables
        implicit none
        integer, intent (in) :: status
        !if(associated(CementPumpPowerFailPtr)) call CementPumpPowerFailPtr(status)
        if(status == Clear_StatusType)    data%State%Pump(3)%PowerFailMalf=0
        if(status == Executed_StatusType) data%State%Pump(3)%PowerFailMalf=1
    endsubroutine
    
    subroutine ChangeCementPumpBlowPopOffValve(status)
        use SimulationVariables
        implicit none
        integer, intent (in) :: status
        !if(associated(CementPumpBlowPopOffValvePtr)) call CementPumpBlowPopOffValvePtr(status)
        if(status == Clear_StatusType)    data%State%Pump(3)%BlowPopOffMalf=0
        if(status == Executed_StatusType) data%State%Pump(3)%BlowPopOffMalf=1
    endsubroutine
    

end module CPumpProblems