GridOperations Module

History

current version 1.8 - 19th January 2021

Version Date Comment
0.1 29/Jun/2009 Original code. giovanni ravazzani
0.2 09/Aug/2009 Added GridByIni
0.3 07/Apr/2010 Added GridResample
0.4 16/Oct/2010 function to compute cell area and distance
0.5 03/Feb/2011 Distance moved to GeoLib
0.6 01/Aug/2011 optional argument for cellsize output from GridConvert
0.7 19/Oct/2011 added getSum routines
0.8 03/Dec/2012 GetMin function
0.9 20/Mar/2013 correct a bug in SUBROUTINE ResampleFloat
1.0 09/Apr/2013 MinMaxNormalization and GetMax routines
1.1 11/Apr/2013 ZscoreNormalization and GetStDev routines
1.2 12/Mar/2016 GetRMSE function to compute Root Mean Square Error between two grids real
1.3 10/May/2016 GetBias function to compute Bias between two grids real
1.4 19/Dec/2016 statistic routines moved to new module GridStatistics
1.5 28/Nov/2017 GridByIni modified to read epsg code
1.6 03/Mar/2018 Added functions CellIsNoData and CellIsValid
1.7 28/Jan/2020 Grid2vector subroutine to transform grid content to an array 1D
1.8 19/Jan/2021 Added CellLength, moved ExtractBorder from function to subroutine

License

license: GNU GPL http://www.gnu.org/licenses/

This file is part of

MOSAICO -- MOdular library for raSter bAsed hydrologIcal appliCatiOn.

Copyright (C) 2011 Giovanni Ravazzani

Module Description:

library to operate on grids

Description: Description compute area ([m2) of grid excluding nodata



Interfaces

public interface ASSIGNMENT(=)

  • private subroutine AssignGridReal(mat, mask)

    assign value of mask real to mat real

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(inout) :: mat
    type(grid_real), intent(in) :: mask
  • private subroutine AssignGridInteger(mat, mask)

    assign value of mask integer to mat integer

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(inout) :: mat
    type(grid_integer), intent(in) :: mask
  • private subroutine AssignReal(mat, num)

    assign value to mat

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(inout) :: mat
    real(kind=float), intent(in) :: num
  • private subroutine AssignInteger(mat, num)

    assign value to mat

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(inout) :: mat
    integer, intent(in) :: num
  • private subroutine AssignGridRealInteger(mat, mask)

    assign value of mask real to mat integer. real numbers are truncated to integer part.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(inout) :: mat
    type(grid_real), intent(in) :: mask
  • private subroutine AssignGridIntegerReal(mat, mask)

    assign value of mask integer to mat real

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(inout) :: mat
    type(grid_integer), intent(in) :: mask

public interface CRSisEqual

  • private function CRSisEqualIntInt(mask, grid, checkCells) result(isEqual)

    return .TRUE. if the two grids have the same Coordinate Reference System, and the same spatial reference (cellsize, xllxorner, yllcorner, idim, jdim) If checkCells is given the function checks that grid has the same active cells of mask.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: mask
    type(grid_integer), intent(in) :: grid
    logical, intent(in), optional :: checkCells

    Return Value logical

  • private function CRSisEqualFloatFloat(mask, grid, checkCells) result(isEqual)

    return .TRUE. if the two grids have the same Coordinate Reference System, and the same spatial reference (cellsize, xllxorner, yllcorner, idim, jdim) If checkCells is given the function checks that grid has the same active cells of mask.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: mask
    type(grid_real), intent(in) :: grid
    logical, intent(in), optional :: checkCells

    Return Value logical

  • private function CRSisEqualFloatInt(mask, grid, checkCells) result(isEqual)

    return .TRUE. if the two grids have the same Coordinate Reference System, and the same spatial reference (cellsize, xllxorner, yllcorner, idim, jdim) If checkCells is given the function checks that grid has the same active cells of mask.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: mask
    type(grid_integer), intent(in) :: grid
    logical, intent(in), optional :: checkCells

    Return Value logical

  • private function CRSisEqualIntFloat(mask, grid, checkCells) result(isEqual)

    return .TRUE. if the two grids have the same Coordinate Reference System, and the same spatial reference (cellsize, xllxorner, yllcorner, idim, jdim) If checkCells is given the function checks that grid has the same active cells of mask.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: mask
    type(grid_real), intent(in) :: grid
    logical, intent(in), optional :: checkCells

    Return Value logical

public interface CellArea

  • private function CellAreaFloat(gridIn, i, j) result(cellarea)

    Description compute area (m2) of a cell of a grid as a function of latitude defined by the position of cell in local coordinate system (row, column). Input grid of type grid_real


    Reference:

    Sivakholundu, K. M., Prabaharan, N. (1998). A program to compute the area of an irregular polygon on a spheroidal surface, Computers & Geosciences, 24(8), 823-826.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: gridIn
    integer, intent(in) :: i

    row and column of cell

    integer, intent(in) :: j

    row and column of cell

    Return Value real(kind=float)

  • private function CellAreaInteger(gridIn, i, j) result(cellarea)

    Description compute area (m2) of a cell of a grid as a function of latitude defined by the position of cell in local coordinate system (row, column). Input grid of type grid_integer


    Reference:

    Sivakholundu, K. M., Prabaharan, N. (1998). A program to compute the area of an irregular polygon on a spheroidal surface, Computers & Geosciences, 24(8), 823-826.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: gridIn
    integer, intent(in) :: i

    row and column of cell

    integer, intent(in) :: j

    row and column of cell

    Return Value real(kind=float)

public interface CellIsNoData

  • private function CellIsNoDataInteger(i, j, grid)

    returns true if cell of grid_integer contains no data value

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    type(grid_integer), intent(in) :: grid

    Return Value logical

  • private function CellIsNoDataFloat(i, j, grid)

    return true if cell of grid_real contains no data value

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    type(grid_real), intent(in) :: grid

    Return Value logical

public interface CellIsValid

  • private function CellIsValidInteger(i, j, grid)

    return false if cell is out of grid either contains nodata value, true otherwise.

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    type(grid_integer), intent(in) :: grid

    Return Value logical

  • private function CellIsValidFloat(i, j, grid)

    return false if cell is out of grid either contains nodata value, true otherwise.

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    type(grid_real), intent(in) :: grid

    Return Value logical

public interface CellLength

  • private function CellLengthFloat(gridIn, i, j) result(length)

    Description compute average length (m) of a cell of a grid as the squareroot of area Input grid of type grid_real

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: gridIn
    integer, intent(in) :: i

    row and column of cell

    integer, intent(in) :: j

    row and column of cell

    Return Value real(kind=float)

  • private function CellLengthInteger(gridIn, i, j) result(length)

    Description compute average length (m) of a cell of a grid as the squareroot of area Input grid of type grid_integer

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: gridIn
    integer, intent(in) :: i

    row and column of cell

    integer, intent(in) :: j

    row and column of cell

    Return Value real(kind=float)

public interface ExtractBorder

  • private subroutine ExtractBorderFloat(grid, border, cardinal)

    Extracts only the cells on the external border. Other cells are assigned nodata. Border cell is the one that has at least a nodata value in the neighbouring 8 cells.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: grid
    type(grid_real) :: border
    logical, intent(in), optional :: cardinal
  • private subroutine ExtractBorderInteger(grid, border, cardinal)

    Extracts only the cells on the external border. Other cells are assigned nodata. Border cell is the one that has at least a nodata value in the neighbouring 8 cells. If cardinal is passed the routine checks only the four cells in the cardinal direction. This option is used to obtain border without duplicates. Default is check all the cells.

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: grid
    type(grid_integer), intent(out) :: border
    logical, intent(in), optional :: cardinal

public interface GetArea

  • private function GetAreaOfGridFloat(grid) result(area)

    Description compute area (m2) of grid excluding nodata

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: grid

    Return Value real(kind=float)

  • private function GetAreaOfGridInteger(grid) result(area)

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: grid

    Return Value real(kind=float)

public interface GetIJ

  • private subroutine GetIJfloat(X, Y, grid, i, j, check)

    returns X and Y coordinate given i and j position in grid(i,j)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=float), intent(in) :: X
    real(kind=float), intent(in) :: Y
    type(grid_real), intent(in) :: grid
    integer, intent(out) :: i
    integer, intent(out) :: j
    logical, intent(out), optional :: check

    return false if i and j are outside grid definition

  • private subroutine GetIJinteger(X, Y, grid, i, j, check)

    returns X and Y coordinate given i and j position in grid(i,j)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=float), intent(in) :: X
    real(kind=float), intent(in) :: Y
    type(grid_integer), intent(in) :: grid
    integer, intent(out) :: i
    integer, intent(out) :: j
    logical, intent(out), optional :: check

    return false if i and j are outside grid definition

public interface GetXY

  • private subroutine GetXYfloat(i, j, grid, X, Y, check)

    returns X and Y coordinate given i and j position in grid(i,j)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    type(grid_real), intent(in) :: grid
    real(kind=float), intent(out) :: X
    real(kind=float), intent(out) :: Y
    logical, intent(out), optional :: check

    return false if i and j are outside grid definition

  • private subroutine GetXYinteger(i, j, grid, X, Y, check)

    returns X and Y coordinate given i and j position in grid(i,j)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    type(grid_integer), intent(in) :: grid
    real(kind=float), intent(out) :: X
    real(kind=float), intent(out) :: Y
    logical, intent(out), optional :: check

    return false if i and j are outside grid definition

public interface Grid2vector

  • public subroutine Grid2vectorInteger(grid, vector)

    return an array 1D of numbers different than nodata in a grid_integer

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: grid
    integer(kind=short), intent(out), ALLOCATABLE :: vector(:)
  • public subroutine Grid2vectorFloat(grid, vector)

    return an array 1D of numbers different than nodata in a grid_real

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: grid
    real(kind=float), intent(out), ALLOCATABLE :: vector(:)

public interface GridByIni

  • private subroutine GridByIniFloat(ini, grid, section, time)

    read a grid_real using information stored in ini configuration file

    Arguments

    Type IntentOptional Attributes Name
    type(IniList), intent(in) :: ini
    type(grid_real), intent(out) :: grid
    character(len=*), intent(in) :: section
    type(DateTime), intent(in), optional :: time
  • private subroutine GridByIniInteger(ini, grid, section)

    read a grid_integer using information stored in ini configuration file

    Arguments

    Type IntentOptional Attributes Name
    type(IniList), intent(in) :: ini
    type(grid_integer), intent(out) :: grid
    character(len=*), intent(in) :: section
  • public subroutine GridByIniFloatSubSection(ini, grid, section, subsection)

    read a grid_real using information stored in ini configuration file defined in subsection [[...]]

    Arguments

    Type IntentOptional Attributes Name
    type(IniList), intent(in) :: ini
    type(grid_real), intent(out) :: grid
    character(len=*), intent(in) :: section
    character(len=*), intent(in) :: subsection
  • public subroutine GridByIniIntegerSubSection(ini, grid, section, subsection)

    read a grid_integer using information stored in ini configuration file defined in subsection [[.. ]]

    Arguments

    Type IntentOptional Attributes Name
    type(IniList), intent(in) :: ini
    type(grid_integer), intent(out) :: grid
    character(len=*), intent(in) :: section
    character(len=*), intent(in) :: subsection

public interface GridConvert

  • private subroutine GridConvertFloat(GridIn, GridOut, cellsize)

    coordinate conversion of a grid_real definition of corner points:

        A---------B
        |         |
        |         |
        |         |
        C---------D
    

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: GridIn
    type(grid_real), intent(inout) :: GridOut
    real(kind=float), intent(in), optional :: cellsize
  • private subroutine GridConvertInteger(GridIn, GridOut, cellsize)

    coordinate conversion of a grid_integer definition of corner points:

        A---------B
        |         |
        |         |
        |         |
        C---------D
    

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: GridIn
    type(grid_integer), intent(inout) :: GridOut
    real(kind=float), intent(in), optional :: cellsize

public interface GridResample

  • private subroutine ResampleFloatCell(grid, resampledGrid, newCellsize)

    Create a new grid_real with cellsize different from input grid The content of the created grid is filled in with nearest neighbor method

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: grid
    type(grid_real), intent(out) :: resampledGrid
    real(kind=float), intent(in) :: newCellsize
  • private subroutine ResampleIntegerCell(grid, resampledGrid, newCellsize)

    Create a new grid_integer with cellsize different from input grid The content of the created grid is filled in with nearest neighbor method

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: grid
    type(grid_integer), intent(out) :: resampledGrid
    real(kind=float), intent(in) :: newCellsize
  • private subroutine ResampleFloat(grid, resampledGrid)

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: grid
    type(grid_real), intent(inout) :: resampledGrid
  • private subroutine ResampleInteger(grid, resampledGrid)

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: grid
    type(grid_integer), intent(inout) :: resampledGrid

public interface GridShift

  • public subroutine ShiftInteger(gridin, gridout, shifteast, shiftnorth)

    Apply a shift togrid_integer. Creates a new grid with xllcorner and yllcorner modified

    Arguments

    Type IntentOptional Attributes Name
    type(grid_integer), intent(in) :: gridin
    type(grid_integer), intent(out) :: gridout
    real(kind=float), intent(in) :: shifteast

    amount of shift in east direction

    real(kind=float), intent(in) :: shiftnorth

    amount of shift in north direction

  • public subroutine ShiftReal(gridin, gridout, shifteast, shiftnorth)

    Apply a shift to grid_real. Modifies xllcorner and yllcorner

    Arguments

    Type IntentOptional Attributes Name
    type(grid_real), intent(in) :: gridin
    type(grid_real), intent(out) :: gridout
    real(kind=float), intent(in) :: shifteast

    amount of shift in east direction

    real(kind=float), intent(in) :: shiftnorth

    amount of shift in north direction

public interface IsOutOfGrid

  • private function IsOutOfGridFloat(i, j, grid)

    calculates if cell is out of grid space limits

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    type(grid_real), intent(in) :: grid

    Return Value logical

  • private function IsOutOfGridInteger(i, j, grid)

    calculates if cell is out of grid space limits

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: i
    integer, intent(in) :: j
    type(grid_integer), intent(in) :: grid

    Return Value logical


Functions

private function CRSisEqualFloatFloat(mask, grid, checkCells) result(isEqual)

return .TRUE. if the two grids have the same Coordinate Reference System, and the same spatial reference (cellsize, xllxorner, yllcorner, idim, jdim) If checkCells is given the function checks that grid has the same active cells of mask.

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: mask
type(grid_real), intent(in) :: grid
logical, intent(in), optional :: checkCells

Return Value logical

private function CRSisEqualFloatInt(mask, grid, checkCells) result(isEqual)

return .TRUE. if the two grids have the same Coordinate Reference System, and the same spatial reference (cellsize, xllxorner, yllcorner, idim, jdim) If checkCells is given the function checks that grid has the same active cells of mask.

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: mask
type(grid_integer), intent(in) :: grid
logical, intent(in), optional :: checkCells

Return Value logical

private function CRSisEqualIntFloat(mask, grid, checkCells) result(isEqual)

return .TRUE. if the two grids have the same Coordinate Reference System, and the same spatial reference (cellsize, xllxorner, yllcorner, idim, jdim) If checkCells is given the function checks that grid has the same active cells of mask.

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: mask
type(grid_real), intent(in) :: grid
logical, intent(in), optional :: checkCells

Return Value logical

private function CRSisEqualIntInt(mask, grid, checkCells) result(isEqual)

return .TRUE. if the two grids have the same Coordinate Reference System, and the same spatial reference (cellsize, xllxorner, yllcorner, idim, jdim) If checkCells is given the function checks that grid has the same active cells of mask.

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: mask
type(grid_integer), intent(in) :: grid
logical, intent(in), optional :: checkCells

Return Value logical

private function CellAreaFloat(gridIn, i, j) result(cellarea)

Description compute area (m2) of a cell of a grid as a function of latitude defined by the position of cell in local coordinate system (row, column). Input grid of type grid_real

Read more…

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: gridIn
integer, intent(in) :: i

row and column of cell

integer, intent(in) :: j

row and column of cell

Return Value real(kind=float)

private function CellAreaInteger(gridIn, i, j) result(cellarea)

Description compute area (m2) of a cell of a grid as a function of latitude defined by the position of cell in local coordinate system (row, column). Input grid of type grid_integer

Read more…

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: gridIn
integer, intent(in) :: i

row and column of cell

integer, intent(in) :: j

row and column of cell

Return Value real(kind=float)

private function CellIsNoDataFloat(i, j, grid)

return true if cell of grid_real contains no data value

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
type(grid_real), intent(in) :: grid

Return Value logical

private function CellIsNoDataInteger(i, j, grid)

returns true if cell of grid_integer contains no data value

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
type(grid_integer), intent(in) :: grid

Return Value logical

private function CellIsValidFloat(i, j, grid)

return false if cell is out of grid either contains nodata value, true otherwise.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
type(grid_real), intent(in) :: grid

Return Value logical

private function CellIsValidInteger(i, j, grid)

return false if cell is out of grid either contains nodata value, true otherwise.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
type(grid_integer), intent(in) :: grid

Return Value logical

private function CellLengthFloat(gridIn, i, j) result(length)

Description compute average length (m) of a cell of a grid as the squareroot of area Input grid of type grid_real

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: gridIn
integer, intent(in) :: i

row and column of cell

integer, intent(in) :: j

row and column of cell

Return Value real(kind=float)

private function CellLengthInteger(gridIn, i, j) result(length)

Description compute average length (m) of a cell of a grid as the squareroot of area Input grid of type grid_integer

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: gridIn
integer, intent(in) :: i

row and column of cell

integer, intent(in) :: j

row and column of cell

Return Value real(kind=float)

private function GetAreaOfGridFloat(grid) result(area)

Description compute area (m2) of grid excluding nodata

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: grid

Return Value real(kind=float)

private function GetAreaOfGridInteger(grid) result(area)

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: grid

Return Value real(kind=float)

private function IsOutOfGridFloat(i, j, grid)

calculates if cell is out of grid space limits

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
type(grid_real), intent(in) :: grid

Return Value logical

private function IsOutOfGridInteger(i, j, grid)

calculates if cell is out of grid space limits

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
type(grid_integer), intent(in) :: grid

Return Value logical


Subroutines

public subroutine Grid2vectorFloat(grid, vector)

return an array 1D of numbers different than nodata in a grid_real

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: grid
real(kind=float), intent(out), ALLOCATABLE :: vector(:)

public subroutine Grid2vectorInteger(grid, vector)

return an array 1D of numbers different than nodata in a grid_integer

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: grid
integer(kind=short), intent(out), ALLOCATABLE :: vector(:)

public subroutine GridByIniFloatSubSection(ini, grid, section, subsection)

read a grid_real using information stored in ini configuration file defined in subsection [[...]]

Arguments

Type IntentOptional Attributes Name
type(IniList), intent(in) :: ini
type(grid_real), intent(out) :: grid
character(len=*), intent(in) :: section
character(len=*), intent(in) :: subsection

public subroutine GridByIniIntegerSubSection(ini, grid, section, subsection)

read a grid_integer using information stored in ini configuration file defined in subsection [[.. ]]

Arguments

Type IntentOptional Attributes Name
type(IniList), intent(in) :: ini
type(grid_integer), intent(out) :: grid
character(len=*), intent(in) :: section
character(len=*), intent(in) :: subsection

public subroutine ShiftInteger(gridin, gridout, shifteast, shiftnorth)

Apply a shift togrid_integer. Creates a new grid with xllcorner and yllcorner modified

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: gridin
type(grid_integer), intent(out) :: gridout
real(kind=float), intent(in) :: shifteast

amount of shift in east direction

real(kind=float), intent(in) :: shiftnorth

amount of shift in north direction

public subroutine ShiftReal(gridin, gridout, shifteast, shiftnorth)

Apply a shift to grid_real. Modifies xllcorner and yllcorner

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: gridin
type(grid_real), intent(out) :: gridout
real(kind=float), intent(in) :: shifteast

amount of shift in east direction

real(kind=float), intent(in) :: shiftnorth

amount of shift in north direction

private subroutine AssignGridInteger(mat, mask)

assign value of mask integer to mat integer

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(inout) :: mat
type(grid_integer), intent(in) :: mask

private subroutine AssignGridIntegerReal(mat, mask)

assign value of mask integer to mat real

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(inout) :: mat
type(grid_integer), intent(in) :: mask

private subroutine AssignGridReal(mat, mask)

assign value of mask real to mat real

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(inout) :: mat
type(grid_real), intent(in) :: mask

private subroutine AssignGridRealInteger(mat, mask)

assign value of mask real to mat integer. real numbers are truncated to integer part.

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(inout) :: mat
type(grid_real), intent(in) :: mask

private subroutine AssignInteger(mat, num)

assign value to mat

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(inout) :: mat
integer, intent(in) :: num

private subroutine AssignReal(mat, num)

assign value to mat

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(inout) :: mat
real(kind=float), intent(in) :: num

private subroutine ExtractBorderFloat(grid, border, cardinal)

Extracts only the cells on the external border. Other cells are assigned nodata. Border cell is the one that has at least a nodata value in the neighbouring 8 cells.

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: grid
type(grid_real) :: border
logical, intent(in), optional :: cardinal

private subroutine ExtractBorderInteger(grid, border, cardinal)

Extracts only the cells on the external border. Other cells are assigned nodata. Border cell is the one that has at least a nodata value in the neighbouring 8 cells. If cardinal is passed the routine checks only the four cells in the cardinal direction. This option is used to obtain border without duplicates. Default is check all the cells.

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: grid
type(grid_integer), intent(out) :: border
logical, intent(in), optional :: cardinal

private subroutine GetIJfloat(X, Y, grid, i, j, check)

returns X and Y coordinate given i and j position in grid(i,j)

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: X
real(kind=float), intent(in) :: Y
type(grid_real), intent(in) :: grid
integer, intent(out) :: i
integer, intent(out) :: j
logical, intent(out), optional :: check

return false if i and j are outside grid definition

private subroutine GetIJinteger(X, Y, grid, i, j, check)

returns X and Y coordinate given i and j position in grid(i,j)

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: X
real(kind=float), intent(in) :: Y
type(grid_integer), intent(in) :: grid
integer, intent(out) :: i
integer, intent(out) :: j
logical, intent(out), optional :: check

return false if i and j are outside grid definition

private subroutine GetXYfloat(i, j, grid, X, Y, check)

returns X and Y coordinate given i and j position in grid(i,j)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
type(grid_real), intent(in) :: grid
real(kind=float), intent(out) :: X
real(kind=float), intent(out) :: Y
logical, intent(out), optional :: check

return false if i and j are outside grid definition

private subroutine GetXYinteger(i, j, grid, X, Y, check)

returns X and Y coordinate given i and j position in grid(i,j)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: i
integer, intent(in) :: j
type(grid_integer), intent(in) :: grid
real(kind=float), intent(out) :: X
real(kind=float), intent(out) :: Y
logical, intent(out), optional :: check

return false if i and j are outside grid definition

private subroutine GridByIniFloat(ini, grid, section, time)

read a grid_real using information stored in ini configuration file

Arguments

Type IntentOptional Attributes Name
type(IniList), intent(in) :: ini
type(grid_real), intent(out) :: grid
character(len=*), intent(in) :: section
type(DateTime), intent(in), optional :: time

private subroutine GridByIniInteger(ini, grid, section)

read a grid_integer using information stored in ini configuration file

Arguments

Type IntentOptional Attributes Name
type(IniList), intent(in) :: ini
type(grid_integer), intent(out) :: grid
character(len=*), intent(in) :: section

private subroutine GridConvertFloat(GridIn, GridOut, cellsize)

coordinate conversion of a grid_real definition of corner points:

Read more…

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: GridIn
type(grid_real), intent(inout) :: GridOut
real(kind=float), intent(in), optional :: cellsize

private subroutine GridConvertInteger(GridIn, GridOut, cellsize)

coordinate conversion of a grid_integer definition of corner points:

Read more…

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: GridIn
type(grid_integer), intent(inout) :: GridOut
real(kind=float), intent(in), optional :: cellsize

private subroutine ResampleFloat(grid, resampledGrid)

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: grid
type(grid_real), intent(inout) :: resampledGrid

private subroutine ResampleFloatCell(grid, resampledGrid, newCellsize)

Create a new grid_real with cellsize different from input grid The content of the created grid is filled in with nearest neighbor method

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: grid
type(grid_real), intent(out) :: resampledGrid
real(kind=float), intent(in) :: newCellsize

private subroutine ResampleInteger(grid, resampledGrid)

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: grid
type(grid_integer), intent(inout) :: resampledGrid

private subroutine ResampleIntegerCell(grid, resampledGrid, newCellsize)

Create a new grid_integer with cellsize different from input grid The content of the created grid is filled in with nearest neighbor method

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: grid
type(grid_integer), intent(out) :: resampledGrid
real(kind=float), intent(in) :: newCellsize