MeteoInit Subroutine

public subroutine MeteoInit(inifile, tstart, mask, dem, dem_loaded, albedo_loaded)

Initialize meteorological forcings

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inifile

name of configuration file

type(DateTime), intent(in) :: tstart

initial time

type(grid_integer), intent(in) :: mask

defines interpolation extent

type(grid_real), intent(in) :: dem

digital elevation model to be used to modify interpolated data

logical, intent(in) :: dem_loaded

true if dem has been loaded

logical, intent(in) :: albedo_loaded

true if dem has been loaded


Source Code

SUBROUTINE MeteoInit &
!
( inifile, tstart, mask, dem, dem_loaded, albedo_loaded )

IMPLICIT NONE


CHARACTER (LEN = *), INTENT(IN) :: inifile  !!name of configuration file
TYPE (DateTime),     INTENT(IN) :: tstart !!initial time
TYPE (grid_integer), INTENT(IN) :: mask  !!defines interpolation extent
!INTEGER (KIND = short), INTENT(IN) :: dtMeteo !! deltat of meteo data reading
TYPE(grid_real), INTENT(in) :: dem !!digital elevation model to be used to modify interpolated data
LOGICAL , INTENT (in) :: dem_loaded !! true if dem has been loaded
LOGICAL , INTENT (in) :: albedo_loaded !! true if dem has been loaded

!-------------------------end of declarations----------------------------------

!open and load configuration file
CALL IniOpen (inifile, meteoini)

!configure precipitation
IF (SectionIsPresent (section = "precipitation", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize precipitation ')
   CALL PrecipitationInit (meteoini, mask, dtMeteo, tstart, dem_loaded)
ELSE 
    CALL Catch ('warning', 'Meteo', 'precipitation is turned off')
END IF

!configure daily precipitation
IF (SectionIsPresent (section = "precipitation-daily", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize daily precipitation ')
   CALL PrecipitationDailyInit (meteoini, mask, dtMeteo, tstart, dem_loaded)
ELSE 
    CALL Catch ('warning', 'Meteo', 'daily precipitation is turned off')
END IF

!configure air temperature
IF (SectionIsPresent (section = "temperature", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize air temperature ')
   CALL AirTemperatureInit (meteoini, mask, dtMeteo, tstart, dem_loaded)
ELSE 
    CALL Catch ('warning', 'Meteo', 'air temperature is turned off')
END IF

!configure mean daily air temperature
IF (SectionIsPresent (section = "temperature-daily-mean", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize daily mean air temperature ')
   CALL AirTemperatureDailyMeanInit (meteoini, mask, dtMeteo, tstart, dem_loaded)
ELSE 
    CALL Catch ('warning', 'Meteo', 'daily mean air temperature is turned off')
END IF

!configure maximum daily air temperature
IF (SectionIsPresent (section = "temperature-daily-max", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize daily max air temperature ')
   CALL AirTemperatureDailyMaxInit (meteoini, mask, dtMeteo, tstart, dem_loaded)
ELSE 
    CALL Catch ('warning', 'Meteo', 'daily max air temperature is turned off')
END IF

!configure minimum daily air temperature
IF (SectionIsPresent (section = "temperature-daily-min", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize daily min air temperature ')
   CALL AirTemperatureDailyMinInit (meteoini, mask, dtMeteo, tstart, dem_loaded)
ELSE 
    CALL Catch ('warning', 'Meteo', 'daily min air temperature is turned off')
END IF

!configure relative humidity
IF (SectionIsPresent (section = "relative-humidity", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize relative humidity ')
   CALL AirRelativeHumidityInit (meteoini, mask, dtMeteo, tstart)
ELSE 
    CALL Catch ('warning', 'Meteo', 'relative humidity is turned off')
END IF

!configure solar radiation
IF (SectionIsPresent (section = "solar-radiation", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize solar radiation ')
   CALL SolarRadiationInit (meteoini, mask, dtMeteo, tstart, dem, dem_loaded, &
                            albedo_loaded, dtTemperature, dtRelHumidity )
ELSE 
    CALL Catch ('warning', 'Meteo', 'solar radiation is turned off')
END IF

!configure wind speed
IF (SectionIsPresent (section = "wind-speed", iniDB = meteoini))  THEN
   CALL Catch ('info', 'Meteo', 'initialize wind flux ')
   CALL WindFluxInit (meteoini, mask, dtMeteo, tstart, dem, dem_loaded)
ELSE 
    CALL Catch ('warning', 'Meteo', 'wind speed is turned off')
END IF

!close ini
CALL IniClose (meteoini)

RETURN
END SUBROUTINE MeteoInit