LCOV - code coverage report
Current view: top level - MPR - mo_read_lut.f90 (source / functions) Hit Total Coverage
Test: mHM coverage Lines: 29 29 100.0 %
Date: 2024-04-15 17:48:09 Functions: 2 2 100.0 %

          Line data    Source code
       1             : !> \file mo_read_lut.f90
       2             : !> \brief \copybrief mo_read_lut
       3             : !> \details \copydetails mo_read_lut
       4             : 
       5             : !> \brief Routines reading lookup tables (lut).
       6             : !> \details This module contains routines reading various lookup tables (lut).
       7             : !! 1. LUT containing gauge information.
       8             : !! 2. LUT containing geological formation information.
       9             : !! 3. LUT containing LAI class information.
      10             : !> \authors Juliane Mai, Matthias Zink
      11             : !> \date Jan 2013
      12             : !> \copyright Copyright 2005-\today, the mHM Developers, Luis Samaniego, Sabine Attinger: All rights reserved.
      13             : !! mHM is released under the LGPLv3+ license \license_note
      14             : !> \ingroup f_mpr
      15             : MODULE mo_read_lut
      16             : 
      17             :   ! Written    Juliane Mai,    Jan 2013
      18             :   ! Modified   Matthias Zink,  Jan 2013 - add read_gauge_lut
      19             : 
      20             :   USE mo_kind, ONLY : i4, dp
      21             :   USE mo_os, ONLY: check_path_isfile
      22             :   use mo_string_utils, ONLY: num2str
      23             :   use mo_message, ONLY: error_message
      24             : 
      25             :   IMPLICIT NONE
      26             : 
      27             :   PUBLIC :: read_geoformation_lut  ! Reads LUT containing geological formation information
      28             :   PUBLIC :: read_lai_lut           ! Reads LUT containing LAI class information
      29             : 
      30             : CONTAINS
      31             : 
      32             :   ! ------------------------------------------------------------------
      33             : 
      34             :   !    NAME
      35             :   !        read_geoformation_lut
      36             : 
      37             :   !    PURPOSE
      38             :   !>       \brief Reads LUT containing geological formation information.
      39             : 
      40             :   !>       \details The LUT needs to have the following header:
      41             :   !>       \verbatim
      42             :   !>       nGeo_Formations  < Number of lines containing data >
      43             :   !>       GeoParam(i)   ClassUnit     Karstic      Description
      44             :   !>       \endverbatim
      45             : 
      46             :   !>       The subsequent lines contains the geological formation information:
      47             :   !>       \verbatim
      48             :   !>       <GeoParam(i)>  <ClassUnit_i4>  <Karstic_i4>  <Description_char>
      49             :   !>       \endverbatim
      50             :   !>       All following lines will be discarded while reading.
      51             :   !>       GeoParam is a running index while ClassUnit is the unit of the map containing the geological formations
      52             :   !>       such that it does not neccessarily contains subsequent numbers. The parametrization of this unit is part
      53             :   !>       of the namelist mhm_parameter.nml under <geoparameter>.
      54             : 
      55             :   !    INTENT(IN)
      56             :   !>       \param[in] "character(len = *) :: filename" File name of LUT
      57             :   !>       \param[in] "integer(i4) :: fileunit"        Unit to open file
      58             : 
      59             :   !    INTENT(OUT)
      60             :   !>       \param[out] "integer(i4) :: nGeo"                      Number of geological formations
      61             :   !>       \param[out] "integer(i4), dimension(:) :: geo_unit"    List of id numbers of each geological formations
      62             :   !>       \param[out] "integer(i4), dimension(:) :: geo_karstic" ID of the Karstic formation (0 == does not exist)
      63             : 
      64             :   !    HISTORY
      65             :   !>       \authors Juliane Mai
      66             : 
      67             :   !>       \date Jan 2013
      68             : 
      69             :   ! Modifications:
      70             :   ! Robert Schweppe Jun 2018 - refactoring and reformatting
      71             : 
      72          13 :   subroutine read_geoformation_lut(filename, fileunit, nGeo, geo_unit, geo_karstic)
      73             :     implicit none
      74             : 
      75             :     ! File name of LUT
      76             :     character(len = *), intent(in) :: filename
      77             : 
      78             :     ! Unit to open file
      79             :     integer(i4), intent(in) :: fileunit
      80             : 
      81             :     ! Number of geological formations
      82             :     integer(i4), intent(out) :: nGeo
      83             : 
      84             :     ! List of id numbers of each geological formations
      85             :     integer(i4), dimension(:), allocatable, intent(out) :: geo_unit
      86             : 
      87             :     ! ID of the Karstic formation (0 == does not exist)
      88             :     integer(i4), dimension(:), allocatable, intent(out) :: geo_karstic
      89             : 
      90             :     integer(i4) :: i, ios
      91             : 
      92             :     character(256) :: dummy
      93             : 
      94             :     !checking whether the file exists
      95          13 :     call check_path_isfile(path = filename, raise=.true.)
      96          13 :     open(fileunit, file = filename, action = 'read', status = 'old')
      97             : 
      98             :     ! read header
      99          13 :     read(fileunit, *) dummy, nGeo
     100          13 :     read(fileunit, *) dummy
     101          13 :     dummy = dummy // ''   ! only to avoid warning
     102             : 
     103             :     ! allocation of arrays
     104          39 :     allocate(geo_unit(nGeo))
     105          39 :     allocate(geo_karstic(nGeo))
     106             : 
     107             :     ! read data
     108         143 :     do i = 1, nGeo
     109         130 :       read(fileunit, *, iostat=ios) dummy, geo_unit(i), geo_karstic(i), dummy
     110         130 :       if ( ios /= 0 ) call error_message( &
     111             :         "ERROR: nGeo_Formations (", num2str(nGeo), ") in geology_classdefinition.txt ", &
     112             :         "seems to be higher than available geology classes!" &
     113          13 :       )
     114             :     end do
     115             : 
     116          13 :     close(fileunit)
     117             : 
     118          13 :   end subroutine read_geoformation_lut
     119             : 
     120             :   ! ------------------------------------------------------------------
     121             : 
     122             :   !    NAME
     123             :   !        read_lai_lut
     124             : 
     125             :   !    PURPOSE
     126             :   !>       \brief Reads LUT containing LAI information.
     127             : 
     128             :   !>       \details The LUT needs to have the following header:
     129             :   !>       \verbatim
     130             :   !>       NoLAIclasses  <Number of lines containing data>
     131             :   !>       Id  land-use  Jan.   Feb.    Mar.    Apr.    May    Jun.    Jul.    Aug.    Sep.    Oct.    Nov.    Dec.
     132             :   !>       \endverbatim
     133             :   !>       The subsequent lines contains the lai class information:
     134             :   !>       \verbatim
     135             :   !>       <ID_i4>  <landuse_char>  <val_1_dp>  <val_2_dp>  <val_3_dp>  <val_4_dp> ... <val_12_dp>
     136             :   !>       \endverbatim
     137             :   !>       All following lines will be discarded while reading.
     138             : 
     139             :   !    INTENT(IN)
     140             :   !>       \param[in] "character(len = *) :: filename" File name of LUT
     141             :   !>       \param[in] "integer(i4) :: fileunit"        Unit to open file
     142             : 
     143             :   !    INTENT(OUT)
     144             :   !>       \param[out] "integer(i4) :: nLAI"                    Number of LAI classes
     145             :   !>       \param[out] "integer(i4), dimension(:) :: LAIIDlist" List of ids of LAI classes
     146             :   !>       \param[out] "real(dp), dimension(:, :) :: LAI"       LAI per class (row) and month (col)
     147             : 
     148             :   !    HISTORY
     149             :   !>       \authors Juliane Mai
     150             : 
     151             :   !>       \date Jan 2013
     152             : 
     153             :   ! Modifications:
     154             :   ! Robert Schweppe Jun 2018 - refactoring and reformatting
     155             : 
     156          12 :   subroutine read_lai_lut(filename, fileunit, nLAI, LAIIDlist, LAI)
     157             : 
     158          13 :     use mo_constants, only : YearMonths
     159             : 
     160             :     implicit none
     161             : 
     162             :     ! File name of LUT
     163             :     character(len = *), intent(in) :: filename
     164             : 
     165             :     ! Unit to open file
     166             :     integer(i4), intent(in) :: fileunit
     167             : 
     168             :     ! Number of LAI classes
     169             :     integer(i4), intent(out) :: nLAI
     170             : 
     171             :     ! List of ids of LAI classes
     172             :     integer(i4), dimension(:), allocatable, intent(out) :: LAIIDlist
     173             : 
     174             :     ! LAI per class (row) and month (col)
     175             :     real(dp), dimension(:, :), allocatable, intent(out) :: LAI
     176             : 
     177             :     integer(i4) :: i, j, ios
     178             : 
     179             :     character(256) :: dummy
     180             : 
     181             :     !checking whether the file exists
     182          12 :     call check_path_isfile(path = filename, raise=.true.)
     183          12 :     open(fileunit, file = filename, action = 'read')
     184             : 
     185             :     ! read header
     186          12 :     read(fileunit, *) dummy, nLAI
     187          12 :     read(fileunit, *) dummy
     188          12 :     dummy = dummy // ''   ! only to avoid warning
     189             : 
     190             :     ! allocate arrays
     191          36 :     allocate(LAIIDList(nLAI))
     192          36 :     allocate(LAI(nLAI, int(YearMonths, i4)))
     193             : 
     194             :     ! read data
     195         132 :     do i = 1, nLAI
     196        1560 :       read(fileunit, *, iostat=ios) LAIIDList(i), dummy, (LAI(i, j), j = 1, int(YearMonths, i4))
     197         120 :       if ( ios /= 0 ) call error_message( &
     198             :         "ERROR: NoLAIclasses (", num2str(nLAI), ") in LAI_classdefinition.txt ", &
     199             :         "seems to be higher than available LAI classes!" &
     200          12 :       )
     201             :     end do
     202             : 
     203          12 :     close(fileunit)
     204             : 
     205          12 :   end subroutine read_lai_lut
     206             : 
     207             : END MODULE mo_read_lut

Generated by: LCOV version 1.16