!! Copyright (C) Stichting Deltares, 2005-2014. !! !! This file is part of iMOD. !! !! This program is free software: you can redistribute it and/or modify !! it under the terms of the GNU General Public License as published by !! the Free Software Foundation, either version 3 of the License, or !! (at your option) any later version. !! !! This program is distributed in the hope that it will be useful, !! but WITHOUT ANY WARRANTY; without even the implied warranty of !! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the !! GNU General Public License for more details. !! !! You should have received a copy of the GNU General Public License !! along with this program. If not, see . !! !! Contact: imod.support@deltares.nl !! Stichting Deltares !! P.O. Box 177 !! 2600 MH Delft, The Netherlands. MODULE IMOD_IDF_PAR implicit none type mapheader ! main header character(len=27) :: signature integer(kind=2) :: version integer(kind=4) :: gisFileId integer(kind=2) :: projection integer(kind=4) :: attrTable integer(kind=2) :: dataType integer(kind=4) :: byteOrder ! raster header integer(kind=2) :: valueScale integer(kind=2) :: cellRepr real(kind=8) :: xUL real(kind=8) :: yUL integer(kind=4) :: nrRows integer(kind=4) :: nrCols real(kind=8) :: cellSizeX real(kind=8) :: cellSizeY real(kind=8) :: angle integer :: i4minVal, i4maxVal real :: r4minVal, r4maxVal end type mapheader TYPE IDFOBJ INTEGER :: IU INTEGER :: NCOL INTEGER :: NROW INTEGER :: IEQ !=0:equi =1:non-equi INTEGER :: ITB !=0: =1:usage of top/bot information INTEGER :: IXV !=0:storage in x =1:storage in v INTEGER :: JD !=julian date (if neccessary) INTEGER :: ILAY !=ilay of idf (if neccessary) INTEGER :: UNITS !=units REAL :: XMIN,YMIN,XMAX,YMAX REAL :: DX,DY !equi.distance if ieq=0 REAL :: TOP,BOT !top and bot information REAL :: NODATA,DMIN,DMAX REAL,DIMENSION(:),POINTER :: SX !x.coord. network REAL,DIMENSION(:),POINTER :: SY !y.coord. network REAL,DIMENSION(:,:),POINTER :: X !idfvalues in matrix REAL,DIMENSION(:),POINTER :: V !idfvalues in vector INTEGER(KIND=2),DIMENSION(:,:),POINTER :: YSEL !idfvalues in vector, irow/icol CHARACTER(LEN=4),DIMENSION(:),POINTER :: COMMENT !comments INTEGER :: NTHREAD CHARACTER(LEN=256) :: FNAME ! name of the idf logical :: lmap = .false. type(mapheader), pointer :: maphdr => null() END TYPE IDFOBJ END MODULE IMOD_IDF_PAR module imod_map_par implicit none ! parameters integer, parameter :: cr_int1 = 1 ! 4 integer, parameter :: cr_int2 = 2 ! 21 integer, parameter :: cr_int4 = 3 ! 38 integer, parameter :: ncrint = cr_int4 integer, parameter :: cr_uint1 = 4 ! 0 integer, parameter :: cr_uint2 = 5 ! 17 integer, parameter :: cr_uint4 = 6 ! 34 integer, parameter :: cr_real4 = 7 ! 90 integer, parameter :: cr_real8 = 8 ! 219 integer, parameter :: cr_undef = 9 ! 100 integer, parameter :: ncr = cr_undef integer, dimension(ncr) :: crval data crval/4,21,38,0,17,34,90,219,100/ character(len=5), dimension(ncr) :: crstr data crstr/'int1 ','int2 ','int4 ','uint1','uint2','uint4','real4','real8','undef'/ integer(kind=4), dimension(ncrint) :: crintmv data crintmv/-2147483648,-256,-32768/ integer, parameter :: pt_xy = 1 integer, parameter :: pt_utm = 2 integer, parameter :: pt_latlon = 3 integer, parameter :: pt_cart = 4 integer, parameter :: pt_rdm = 5 integer, parameter :: v1npt = pt_rdm integer, dimension(v1npt) :: v1ptval data v1ptval/0,1,2,3,4/ character(len=4), dimension(v1npt) :: v1ptstr data v1ptstr/'xy ','utm ','latlon','cart ','rdm '/ integer, parameter :: pt_yinct2b = 1 integer, parameter :: pt_ydect2b = 2 integer, parameter :: v2npt = pt_ydect2b integer, dimension(v2npt) :: v2ptval data v2ptval/0,1/ integer, parameter :: vs_boolean = 1 integer, parameter :: vs_nominal = 2 integer, parameter :: vs_ordinal = 3 integer, parameter :: vs_scalar = 4 integer, parameter :: vs_direction = 5 integer, parameter :: vs_ldd = 6 integer, parameter :: vs_vector = 7 integer, parameter :: nvs = vs_vector integer, dimension(nvs) :: vsval data vsval/224,226,242,235,251,240,236/ character(len=13), dimension(v2npt) :: v2ptstr data v2ptstr/'y increasing ','y decreasing'/ end module imod_map_par