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
        MudProperties%ActiveMudType = v            
    end subroutine
        
    subroutine SetActiveRheologyModel(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActiveRheologyModel
    !DEC$ ATTRIBUTES ALIAS: 'SetActiveRheologyModel' :: SetActiveRheologyModel
        implicit none
        integer, intent(in) :: v
        MudProperties%ActiveRheologyModel = v
#ifdef deb
        call Log_4( '=====ActiveRheologyModel=', MudProperties%ActiveRheologyModel)
#endif
    end subroutine
        
    subroutine SetActiveMudVolume(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActiveMudVolume
    !DEC$ ATTRIBUTES ALIAS: 'SetActiveMudVolume' :: SetActiveMudVolume
        implicit none
        real*8, intent(in) :: v
        MudProperties%ActiveMudVolume = v
        !call Log_5('ActiveDensity=', ActiveDensity)
#ifdef deb
        print*, 'ActiveMudVolume=', MudProperties%ActiveMudVolume
#endif
        MudProperties%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
        MudProperties%ActiveDensity = v   
        !call Log_5('ActiveDensity=', ActiveDensity)
#ifdef deb
        print*, 'ActiveDensity=', MudProperties%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
        MudProperties%ActiveThetaThreeHundred = v            
    end subroutine
        
    subroutine SetActiveThetaSixHundred(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActiveThetaSixHundred
    !DEC$ ATTRIBUTES ALIAS: 'SetActiveThetaSixHundred' :: SetActiveThetaSixHundred
        implicit none
        real*8, intent(in) :: v
        MudProperties%ActiveThetaSixHundred = v            
    end subroutine
    
    
    subroutine SetReserveMudType(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetReserveMudType
    !DEC$ ATTRIBUTES ALIAS: 'SetReserveMudType' :: SetReserveMudType
        implicit none
        integer, intent(in) :: v
        MudProperties%ReserveMudType = v            
    end subroutine
    
    subroutine SetReserveMudVolume(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetReserveMudVolume
    !DEC$ ATTRIBUTES ALIAS: 'SetReserveMudVolume' :: SetReserveMudVolume
        implicit none
        real*8, intent(in) :: v
        MudProperties%ReserveMudVolume = v 
        !call Log_5('ReserveMudVolume=', ReserveMudVolume)
#ifdef deb
        print*, 'ReserveMudVolume=', MudProperties%ReserveMudVolume
#endif

        MudProperties%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
        MudProperties%ReserveDensity = v 
        !call Log_5('ReserveDensity=', ReserveDensity)
#ifdef deb
        print*, 'ReserveDensity=', MudProperties%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
        MudProperties%ReserveThetaThreeHundred = v            
    end subroutine
        
    subroutine SetReserveThetaSixHundred(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetReserveThetaSixHundred
    !DEC$ ATTRIBUTES ALIAS: 'SetReserveThetaSixHundred' :: SetReserveThetaSixHundred
        implicit none
        real*8, intent(in) :: v
        MudProperties%ReserveThetaSixHundred = v            
    end subroutine
    
    
    subroutine SetActiveTotalTankCapacity(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActiveTotalTankCapacity
    !DEC$ ATTRIBUTES ALIAS: 'SetActiveTotalTankCapacity' :: SetActiveTotalTankCapacity
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%ActiveTotalTankCapacity = v
	    MudProperties%ActiveTotalTankCapacityGal = v * 42.0
#ifdef deb
	    print*, 'ActiveTotalTankCapacity=', MudProperties%ActiveTotalTankCapacity
#endif
    end subroutine

    subroutine SetActiveSettledContents(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActiveSettledContents
    !DEC$ ATTRIBUTES ALIAS: 'SetActiveSettledContents' :: SetActiveSettledContents
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%ActiveSettledContents = v
	    MudProperties%ActiveSettledContentsGal = v * 42.0
#ifdef deb
	    print*, 'ActiveSettledContents=', MudProperties%ActiveSettledContents
#endif
    end subroutine

    subroutine SetActiveTotalContents(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActiveTotalContents
    !DEC$ ATTRIBUTES ALIAS: 'SetActiveTotalContents' :: SetActiveTotalContents
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%ActiveTotalContents = v
	    MudProperties%ActiveTotalContentsGal = v * 42.0
#ifdef deb
	    print*, 'ActiveTotalContents=', MudProperties%ActiveTotalContents
#endif
    end subroutine

    subroutine SetActivePlasticViscosity(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActivePlasticViscosity
    !DEC$ ATTRIBUTES ALIAS: 'SetActivePlasticViscosity' :: SetActivePlasticViscosity
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%ActivePlasticViscosity = v
#ifdef deb
	    print*, 'ActivePlasticViscosity=', MudProperties%ActivePlasticViscosity
#endif
    end subroutine

    subroutine SetActiveYieldPoint(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActiveYieldPoint
    !DEC$ ATTRIBUTES ALIAS: 'SetActiveYieldPoint' :: SetActiveYieldPoint
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%ActiveYieldPoint = v
#ifdef deb
	    print*, 'ActiveYieldPoint=', MudProperties%ActiveYieldPoint
#endif
    end subroutine

    subroutine SetActiveAutoDensity(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetActiveAutoDensity
    !DEC$ ATTRIBUTES ALIAS: 'SetActiveAutoDensity' :: SetActiveAutoDensity
	    implicit none
	    logical, intent(in) :: v
	    MudProperties%ActiveAutoDensity = v
#ifdef deb
	    print*, 'ActiveAutoDensity=', MudProperties%ActiveAutoDensity
#endif
    end subroutine

    subroutine SetReservePlasticViscosity(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetReservePlasticViscosity
    !DEC$ ATTRIBUTES ALIAS: 'SetReservePlasticViscosity' :: SetReservePlasticViscosity
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%ReservePlasticViscosity = v
#ifdef deb
	    print*, 'ReservePlasticViscosity=', MudProperties%ReservePlasticViscosity
#endif
    end subroutine

    subroutine SetReserveYieldPoint(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetReserveYieldPoint
    !DEC$ ATTRIBUTES ALIAS: 'SetReserveYieldPoint' :: SetReserveYieldPoint
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%ReserveYieldPoint = v
#ifdef deb
	    print*, 'ReserveYieldPoint=', MudProperties%ReserveYieldPoint
#endif
    end subroutine

    subroutine SetInitialTripTankMudVolume(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetInitialTripTankMudVolume
    !DEC$ ATTRIBUTES ALIAS: 'SetInitialTripTankMudVolume' :: SetInitialTripTankMudVolume
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%InitialTripTankMudVolume = v
	    MudProperties%InitialTripTankMudVolumeGal = v * 42.0
#ifdef deb
	    print*, 'InitialTripTankMudVolume=', MudProperties%InitialTripTankMudVolume
#endif
    end subroutine

    subroutine SetPedalFlowMeter(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: SetPedalFlowMeter
    !DEC$ ATTRIBUTES ALIAS: 'SetPedalFlowMeter' :: SetPedalFlowMeter
	    implicit none
	    real*8, intent(in) :: v
	    MudProperties%PedalFlowMeter = v
#ifdef deb
	    print*, 'PedalFlowMeter=', MudProperties%PedalFlowMeter
#endif
    end subroutine
        
end module CMudProperties