landuse.f95 Source File


This file depends on

sourcefile~~landuse.f95~~EfferentGraph sourcefile~landuse.f95 landuse.f95 sourcefile~input.f95 input.f95 sourcefile~landuse.f95->sourcefile~input.f95 sourcefile~utilities.f95 utilities.f95 sourcefile~landuse.f95->sourcefile~utilities.f95 sourcefile~input.f95->sourcefile~utilities.f95

Files dependent on this one

sourcefile~~landuse.f95~~AfferentGraph sourcefile~landuse.f95 landuse.f95 sourcefile~vegetation.f95 vegetation.f95 sourcefile~vegetation.f95->sourcefile~landuse.f95 sourcefile~subbasin.f95 subbasin.f95 sourcefile~subbasin.f95->sourcefile~landuse.f95 sourcefile~subbasin.f95->sourcefile~vegetation.f95 sourcefile~hydrotope.f95 hydrotope.f95 sourcefile~subbasin.f95->sourcefile~hydrotope.f95 sourcefile~crop.f95 crop.f95 sourcefile~subbasin.f95->sourcefile~crop.f95 sourcefile~reservoir.f95 reservoir.f95 sourcefile~subbasin.f95->sourcefile~reservoir.f95 sourcefile~swim.f95 swim.f95 sourcefile~swim.f95->sourcefile~landuse.f95 sourcefile~swim.f95->sourcefile~vegetation.f95 sourcefile~swim.f95->sourcefile~subbasin.f95 sourcefile~swim.f95->sourcefile~hydrotope.f95 sourcefile~swim.f95->sourcefile~crop.f95 sourcefile~swim.f95->sourcefile~reservoir.f95 sourcefile~catchment.f95 catchment.f95 sourcefile~swim.f95->sourcefile~catchment.f95 sourcefile~time.f95 time.f95 sourcefile~swim.f95->sourcefile~time.f95 sourcefile~hydrotope.f95->sourcefile~landuse.f95 sourcefile~hydrotope.f95->sourcefile~vegetation.f95 sourcefile~hydrotope.f95->sourcefile~crop.f95 sourcefile~crop.f95->sourcefile~vegetation.f95 sourcefile~reservoir.f95->sourcefile~hydrotope.f95 sourcefile~catchment.f95->sourcefile~subbasin.f95 sourcefile~time.f95->sourcefile~vegetation.f95 sourcefile~time.f95->sourcefile~subbasin.f95 sourcefile~time.f95->sourcefile~hydrotope.f95 sourcefile~time.f95->sourcefile~crop.f95 sourcefile~time.f95->sourcefile~reservoir.f95 sourcefile~time.f95->sourcefile~catchment.f95

Contents

Source Code


Source Code

module landuse

  use utilities, only : dp, path_max_length, log_error, log_debug

  implicit none

  character(len=path_max_length) :: landuse_input_file = "landuse.csv"
  integer :: landuse_input_file_id

  ! switch for including interception module, 0 - no, 1 - yes
  integer, save :: iicep = 1
  ! max number of land use types (formerly mc)
  integer, save :: nlut = 0

  !******************************************************************************
  !**** DATATYPE LULC
  !**** Land use / land cover IDs (from LULC map), vegetation code, land use type,
  !**** max. canopy storage for interception, and ETpot correction on LULC type
  !**** Curve Numbers for 4 soil classes A, B, C, D & 15
  !**** Read in subroutine: readlut.f90
  TYPE :: TLULC
    real(dp), dimension(:), pointer :: cn2a
    real(dp), dimension(:), pointer :: cn2b
    real(dp), dimension(:), pointer :: cn2c
    real(dp), dimension(:), pointer :: cn2d
    ! maximum canopy storage for interception [mm] for land use type
    real(dp), dimension(:), pointer :: canmx
    ! vegetation code (crop.dat) for each land use class, read from input file
    integer, dimension(:), pointer :: veg_code
    ! land use ID in * .lut and land use / cover map
    integer, dimension(:), pointer :: id
    ! land use type:
    integer, dimension(:), pointer :: lutype
                                                            ! 0 = no vegetation, like bare soil, settlements...
                                                            ! 1 = crops (managed)
                                                            ! 2 = natrual vegetation, like grasslands, savanna, wetlands
                                                            ! 3 = water
                                                            ! 4 = forests, like mixed, deciduous, evergreen, forested wetlands
    ! vegetation - specific correction on ETp;
    real(dp), dimension(:), pointer :: ETcor
                                                            ! this is a little bit a relict of an older SWIM version where it is assumed that land cover influences ETpot
                                                            ! if you don't want to correct ETp on land cover, apply 1.0 to all LULC types
  END TYPE TLULC
  ! This is how the variables can be accessed:
  !   - The "%" symbol connects the datatype LULC with its variables.
  !   - To access the variables with LULC id = n, use function 'get_lu_index(n)'
  !     to get the position (line) of the respective LU type in the *.lut input file.
  !   - LULC%ETcor(get_lu_index(n)) --> returns the ETcor value of the land use type "n"
  ! Below in this file you find following helper functions:
  ! - get_lu_index(n)
  ! - landuse_is_cropland(n)
  ! - landuse_is_natural_vegetation(n)
  ! - landuse_is_forest(n)
  ! with "n" = land use / land cover id from LULC map
  TYPE (TLULC) LULC
  !*****************************************************************************

  namelist / landuse_parameters / &
    landuse_input_file, &
    iicep

contains

  subroutine landuse_initialise
    use input, only : input_open_file, input_count_rows, get_config_fid

    read(get_config_fid(), nml=landuse_parameters)

    landuse_input_file_id = input_open_file(landuse_input_file)
    ! **** count number of land use types in *.lut
    nlut = input_count_rows(landuse_input_file_id, .true.)

    !**** Begin: Arrays allocated with: nlut (formerly 'mc') = number of land use types
    allocate(LULC % cn2a(nlut))
    LULC % cn2a = 0.
    allocate(LULC % cn2b(nlut))
    LULC % cn2b = 0.
    allocate(LULC % cn2c(nlut))
    LULC % cn2c = 0.
    allocate(LULC % cn2d(nlut))
    LULC % cn2d = 0.
    allocate(LULC % canmx(nlut))
    LULC % canmx = 0.
    allocate(LULC % id(nlut)) ! land use ID in * .lut
    LULC % id = 0
    allocate(LULC % lutype(nlut)) ! land use type: 0 = no vegetation; 1 = crops (managed); 2 = natrual vegetation, water
    LULC % id = 0
    allocate(LULC%veg_code(nlut)) ! vegetation code (crop.dat(nlut)) for each land use class, read from input file
    LULC % veg_code = 0
    allocate(LULC % ETcor(nlut)) ! vegetation - specific correction on ETp

    call landuse_read_input

    call log_debug('hydrotope_initialise', 'Interception iicep =', int=iicep)
    if (iicep == 0) LULC % canmx = 0.

  end subroutine landuse_initialise

  !#############################################################################
  !!! FUNCTIONS FOR DATATYPE LULC
  !#############################################################################

  !-----------------------------------------------------------------------------
  integer function landuse_index(id) ! get land / cover use index
    ! Return the position/line number/index of the land use cover entry in
    ! the *.lut file

    ! land use/cover ID from land use map, or variable 'n' as used in the rest of the SWIM code
    integer, intent(in) :: id
    integer :: i

    landuse_index = 0
    do i = 1, nlut
      if (LULC % id(i) == id ) then
        landuse_index = i
        EXIT
      end if
    end do
    if (landuse_index == 0) then
      call log_error("landuse_index", "Land use ID does not exist:", int=id)
    end if

  end function landuse_index
  !-----------------------------------------------------------------------------


  !-----------------------------------------------------------------------------
  logical function landuse_is_cropland(id)
  ! Return true if land use type is cropland

    ! land use / cover ID from land use map
    integer, intent(in) :: id

    landuse_is_cropland = .false.
    if (LULC % lutype(landuse_index(id)) == 1 ) landuse_is_cropland = .true.

  end function landuse_is_cropland
  !-----------------------------------------------------------------------------

  !-----------------------------------------------------------------------------
  logical function landuse_is_natural_vegetation(id)
    ! Return true if land use type is natural vegetation, except forest

    ! land use / cover ID from land use map
    integer, intent(in) :: id

    landuse_is_natural_vegetation = .false.
    if (LULC % lutype(landuse_index(id)) == 2 ) landuse_is_natural_vegetation = .true.

  end function landuse_is_natural_vegetation
  !-----------------------------------------------------------------------------

  !-----------------------------------------------------------------------------
  logical function landuse_is_forest(id)
    ! Return true if land use type is forest

    ! land use / cover ID from land use map
    integer, intent(in) :: id

    landuse_is_forest = .false.
    if (LULC % lutype(landuse_index(id)) == 4 ) landuse_is_forest = .true.

  end function landuse_is_forest

  !######################################################################
  ! Read *.lut file
  ! land use/cover information:
  !   - id : land use/cover id
  !   - veg_code : vegetation code (crop.dat)
  !   - lutype : land use type
  !   - canmx : canopy storage [mm]
  !   - cnxx : curve number values
  !   - ETcor : land use specific correction on ETpot
  !######################################################################
  subroutine landuse_read_input
    use input, only : read_integer_column, read_real_column

    call read_integer_column(landuse_input_file_id, "landuse_id", LULC%id, 0)
    call read_integer_column(landuse_input_file_id, "icnum", LULC%veg_code, 0)
    call read_integer_column(landuse_input_file_id, "type", LULC%lutype, 0)
    call read_real_column(landuse_input_file_id, "canmx", LULC%canmx, 0.0_dp)
    call read_real_column(landuse_input_file_id, "cn2a", LULC%cn2a, 0.0_dp)
    call read_real_column(landuse_input_file_id, "cn2b", LULC%cn2b, 0.0_dp)
    call read_real_column(landuse_input_file_id, "cn2c", LULC%cn2c, 0.0_dp)
    call read_real_column(landuse_input_file_id, "cn2d", LULC%cn2d, 0.0_dp)
    call read_real_column(landuse_input_file_id, "lu_ETcor", LULC%ETcor, 0.0_dp)

    close(landuse_input_file_id)

  end subroutine landuse_read_input

  !&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&

end module landuse