LCOV - code coverage report
Current view: top level - MPR - mo_prepare_gridded_lai.f90 (source / functions) Hit Total Coverage
Test: mHM coverage Lines: 18 60 30.0 %
Date: 2024-04-15 17:48:09 Functions: 1 2 50.0 %

          Line data    Source code
       1             : !> \file mo_prepare_gridded_lai.f90
       2             : !> \brief \copybrief mo_prepare_gridded_lai
       3             : !> \details \copydetails mo_prepare_gridded_lai
       4             : 
       5             : !> \brief Prepare daily LAI fields (e.g., MODIS data) for mHM
       6             : !> \details Prepare daily LAI fields(e.g., MODIS data) for mHM
       7             : !> \authors John Craven & Rohini Kumar
       8             : !> \date Aug 2013
       9             : !> \copyright Copyright 2005-\today, the mHM Developers, Luis Samaniego, Sabine Attinger: All rights reserved.
      10             : !! mHM is released under the LGPLv3+ license \license_note
      11             : !> \ingroup f_mpr
      12             : MODULE mo_prepare_gridded_LAI
      13             : 
      14             :   ! This module provides routines to read daily gridded LAI data.
      15             : 
      16             :   ! Written  John Craven & Rohini Kumar, August 2013
      17             :   ! Modified from mo_meteo_forcings
      18             : 
      19             :   USE mo_kind, ONLY : i4, dp
      20             :   use mo_message, only: error_message
      21             : 
      22             :   IMPLICIT NONE
      23             : 
      24             :   PRIVATE
      25             : 
      26             :   PUBLIC :: prepare_gridded_daily_LAI_data
      27             :   PUBLIC :: prepare_gridded_mean_monthly_LAI_data
      28             : 
      29             :   ! ------------------------------------------------------------------
      30             : 
      31             : CONTAINS
      32             : 
      33             :   ! ------------------------------------------------------------------
      34             : 
      35             :   !    NAME
      36             :   !        prepare_gridded_daily_LAI_data
      37             : 
      38             :   !    PURPOSE
      39             :   !>       \brief Prepare gridded daily LAI data
      40             : 
      41             :   !>       \details Prepare gridded daily LAI data at Level-0 (e.g., using MODIS datasets)
      42             : 
      43             :   !    INTENT(IN)
      44             :   !>       \param[in] "integer(i4) :: iDomain, nrows, ncols" domain Id
      45             :   !>       \param[in] "integer(i4) :: iDomain, nrows, ncols" domain Id
      46             :   !>       \param[in] "integer(i4) :: iDomain, nrows, ncols" domain Id
      47             :   !>       \param[in] "logical, dimension(:, :) :: mask"
      48             : 
      49             :   !    INTENT(IN), OPTIONAL
      50             :   !>       \param[in] "type(period), optional :: LAIPer_iDomain"
      51             : 
      52             :   !    HISTORY
      53             :   !>       \authors John Craven & Rohini Kumar
      54             : 
      55             :   !>       \date Aug 2013
      56             : 
      57             :   ! Modifications:
      58             :   ! Matthias Cuntz & Juliane Mai Nov 2014 - use meteo reading routines
      59             :   ! Robert Schweppe Jun 2018 - refactoring and reformatting
      60             : 
      61           1 :   subroutine prepare_gridded_daily_LAI_data(iDomain, nrows, ncols, mask, LAIPer_iDomain)
      62             : 
      63             :     use mo_append, only : append
      64             :     use mo_common_types, only: period
      65             :     use mo_mpr_global_variables, only : L0_gridded_LAI, dirgridded_LAI, inputFormat_gridded_LAI, &
      66             :             nLAI, LAIBoundaries, timeStep_LAI_input
      67             :     use mo_read_nc, only : read_nc
      68             : 
      69             :     implicit none
      70             : 
      71             :     ! domain Id
      72             :     integer(i4), intent(in) :: iDomain, nrows, ncols
      73             : 
      74             :     logical, dimension(:, :), intent(in) :: mask
      75             : 
      76             :     type(period), intent(in), optional :: LAIPer_iDomain
      77             : 
      78             :     integer(i4) :: ncells, iLAI
      79             : 
      80             :     ! data at level-0 [nRow X nCols X nTimeSteps]
      81           1 :     real(dp), dimension(:, :, :), allocatable :: LAI0_3D
      82             : 
      83             :     ! data at level-0 [nCells X nTimeSteps]
      84           1 :     real(dp), dimension(:, :), allocatable :: LAI0_2D
      85             : 
      86             : 
      87             :     ! select case depending on input data format
      88           2 :     SELECT CASE(trim(inputFormat_gridded_LAI))
      89             : 
      90             :     ! netcdf file input option
      91             :     CASE('nc')
      92           0 :       CALL read_nc(dirgridded_LAI(iDomain), nRows, nCols, &
      93             :               'lai', mask, LAI0_3D, target_period = LAIPer_iDomain, &
      94           1 :               lower = 1.00E-10_dp, upper = 30.0_dp, nctimestep = timeStep_LAI_input)
      95             :     CASE DEFAULT
      96           2 :       call error_message('***ERROR: No recognized input format')
      97             : 
      98             :     END SELECT
      99             : 
     100             :     ! pack variables
     101      124849 :     nCells = count(mask)
     102             :     ! only set if not yet allocated (e.g. domain 1)
     103           1 :     if (.not. allocated(LAIBoundaries)) then
     104           1 :       nLAI = size(LAI0_3D, 3)
     105           3 :       allocate(LAIBoundaries(nLAI+1))
     106          59 :       LAIBoundaries = [(iLAI, iLAI=1, nLAI+1)]
     107             :     end if
     108           4 :     allocate(LAI0_2D(nCells, nLAI))
     109             : 
     110          19 :     do iLAI = 1, nLAI
     111          19 :       LAI0_2D(:, iLAI) = pack(LAI0_3D(:, :, iLAI), MASK = mask(:, :))
     112             :     end do
     113             : 
     114             :     ! append to Global variable
     115           1 :     call append(L0_gridded_LAI, LAI0_2D(:, :))
     116             : 
     117             :     !free space
     118           1 :     deallocate(LAI0_2D, LAI0_3D)
     119             : 
     120           1 :   end subroutine prepare_gridded_daily_LAI_data
     121             : 
     122             :   ! ------------------------------------------------------------------
     123             : 
     124             :   !    NAME
     125             :   !        prepare_gridded_mean_monthly_LAI_data
     126             : 
     127             :   !    PURPOSE
     128             :   !>       \brief prepare_gridded_mean_monthly_LAI_data
     129             : 
     130             :   !>       \details Long term mean monthly gridded LAI data at Level-0 (e.g., using MODIS datasets)
     131             :   !>       The netcdf file should contain 12 (calender months) gridded fields of climatological
     132             :   !>       LAI data at the input L0 data resolution.
     133             : 
     134             :   !    INTENT(IN)
     135             :   !>       \param[in] "integer(i4) :: iDomain, nrows, ncols" domain Id
     136             :   !>       \param[in] "integer(i4) :: iDomain, nrows, ncols" domain Id
     137             :   !>       \param[in] "integer(i4) :: iDomain, nrows, ncols" domain Id
     138             :   !>       \param[in] "logical, dimension(:, :) :: mask"
     139             : 
     140             :   !    HISTORY
     141             :   !>       \authors Rohini Kumar
     142             : 
     143             :   !>       \date Dec 2016
     144             : 
     145             :   ! Modifications:
     146             :   ! Robert Schweppe Jun 2018 - refactoring and reformatting
     147             : 
     148           0 :   subroutine prepare_gridded_mean_monthly_LAI_data(iDomain, nrows, ncols, mask)
     149             : 
     150           1 :     use mo_append, only : append
     151             :     use mo_mpr_global_variables, only : L0_gridded_LAI, dirgridded_LAI, nLAI, LAIBoundaries
     152             :     use mo_ncread, only : Get_NcDim, Get_NcVar, Get_NcVarAtt
     153             :     use mo_string_utils, only : num2str
     154             :     use mo_utils, only : eq
     155             : 
     156             :     implicit none
     157             : 
     158             :     ! domain Id
     159             :     integer(i4), intent(in) :: iDomain, nrows, ncols
     160             : 
     161             :     logical, dimension(:, :), intent(in) :: mask
     162             : 
     163             :     integer(i4) :: ncells, iLAI
     164             : 
     165             :     ! data at level-0 [nRow X nCols X nTimeSteps]
     166           0 :     real(dp), dimension(:, :, :), allocatable :: LAI0_3D
     167             : 
     168             :     ! data at level-0 [nCells X nTimeSteps]
     169           0 :     real(dp), dimension(:, :), allocatable :: LAI0_2D
     170             : 
     171             :     integer(i4) :: t
     172             : 
     173             :     ! name of NetCDF file
     174             :     character(256) :: fName
     175             : 
     176             :     ! netcdf attribute values
     177             :     character(256) :: AttValues
     178             : 
     179             :     ! datatype of attribute
     180             :     integer(i4) :: datatype
     181             : 
     182             :     ! dimension for NetCDF file
     183             :     integer(i4), dimension(5) :: dimen
     184             : 
     185             :     ! data nodata value
     186           0 :     real(dp) :: nodata_value
     187             : 
     188             : 
     189           0 :     fName = trim(dirgridded_LAI(iDomain)) // trim('lai.nc')
     190             : 
     191             :     ! get dimensions
     192           0 :     dimen = Get_NcDim(trim(fName), 'lai')
     193           0 :     if ((dimen(1) .ne. nRows) .or. (dimen(2) .ne. nCols)) then
     194           0 :        call error_message('***ERROR: read_nc: mHM generated x and y are not matching NetCDF dimensions')
     195             :     end if
     196           0 :     if (dimen(3) .ne. 12) then
     197           0 :        call error_message('***ERROR: read_nc: the time dimenion of LAI NetCDF file under the option-1 is not 12')
     198             :     end if
     199             : 
     200             :     ! determine no data value
     201           0 :     call Get_NcVarAtt(trim(fName), 'lai', '_FillValue', AttValues, dtype = datatype)
     202             :     ! convert to number
     203           0 :     read(AttValues, *) nodata_value
     204             : 
     205           0 :     call Get_NcVar(trim(fName), 'lai', LAI0_3D)
     206             : 
     207             :     ! start checking values
     208           0 :     do t = 1, dimen(3)
     209             :       ! checking for nodata values if optional nocheck is given
     210           0 :       if (any(eq(LAI0_3D(:, :, t), nodata_value) .and. (mask))) then
     211           0 :         call error_message('***ERROR: read_nc: nodata value within domain ', raise=.false.)
     212           0 :         call error_message('          boundary in variable: ', 'lai', raise=.false.)
     213           0 :         call error_message('          at timestep         : ', trim(num2str(t)))
     214             :       end if
     215             :       ! optional check
     216           0 :       if (any((LAI0_3D(:, :, t) .lt. 0.0_dp) .AND. mask(:, :))) then
     217           0 :         call error_message('***ERROR: read_nc: values in variable lai are lower than ', trim(num2str(0, '(F7.2)')), raise=.false.)
     218           0 :         call error_message('          at timestep  : ', trim(num2str(t)), raise=.false.)
     219           0 :         call error_message('File: ', trim(fName), raise=.false.)
     220           0 :         call error_message('Minval at timestep: ', trim(num2str(minval(LAI0_3D(:, :, t)), '(F7.2)')), raise=.false.)
     221           0 :         call error_message('Total minval: ', trim(num2str(minval(LAI0_3D(:, :, :)), '(F7.2)')))
     222             :       end if
     223             : 
     224           0 :       if (any((LAI0_3D(:, :, t) .gt. 30.0_dp) .AND. mask(:, :))) then
     225           0 :         call error_message('***ERROR: read_nc: values in variable lai are greater than ', trim(num2str(30, '(F7.2)')), raise=.false.)
     226           0 :         call error_message('          at timestep  : ', trim(num2str(t)), raise=.false.)
     227           0 :         call error_message('File: ', trim(fName), raise=.false.)
     228           0 :         call error_message('Maxval at timestep: ', trim(num2str(maxval(LAI0_3D(:, :, t)), '(F7.2)')), raise=.false.)
     229           0 :         call error_message('Total maxval: ', trim(num2str(maxval(LAI0_3D(:, :, :)), '(F7.2)')))
     230             :       end if
     231             :     end do
     232             : 
     233             :     ! pack variables
     234           0 :     nCells = count(mask)
     235             :     ! only set if not yet allocated (e.g. domain 1)
     236           0 :     if (.not. allocated(LAIBoundaries)) then
     237           0 :       nLAI = size(LAI0_3D, 3)
     238           0 :       allocate(LAIBoundaries(nLAI+1))
     239           0 :       LAIBoundaries = [(iLAI, iLAI=1, nLAI+1)]
     240             :     end if
     241           0 :     allocate(LAI0_2D(nCells, nLAI))
     242           0 :     do iLAI = 1, nLAI
     243           0 :       LAI0_2D(:, iLAI) = pack(LAI0_3D(:, :, iLAI), MASK = mask(:, :))
     244             :     end do
     245             : 
     246             :     ! append to Global variable
     247           0 :     call append(L0_gridded_LAI, LAI0_2D(:, :))
     248             : 
     249             :     !free space
     250           0 :     deallocate(LAI0_2D, LAI0_3D)
     251             : 
     252           0 :   end subroutine prepare_gridded_mean_monthly_LAI_data
     253             : 
     254             : 
     255             : END MODULE mo_prepare_gridded_LAI

Generated by: LCOV version 1.16