source: palm/trunk/UTIL/inifor/src/types.f90 @ 2977

Last change on this file since 2977 was 2718, checked in by maronga, 6 years ago

deleting of deprecated files; headers updated where needed

  • Property svn:keywords set to Id
File size: 10.8 KB
Line 
1!> @file src/types.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2017-2018 Leibniz Universitaet Hannover
18! Copyright 2017-2018 Deutscher Wetterdienst Offenbach
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: types.f90 2718 2018-01-02 08:49:38Z kanani $
28! Initial revision
29!
30!
31!
32! Authors:
33! --------
34! @author Eckhard Kadasch
35!
36! Description:
37! ------------
38!> The types module provides derived data types used in INIFOR.
39!------------------------------------------------------------------------------!
40 MODULE types
41 
42 USE defs,                                                                     &
43    ONLY:  dp, PATH, SNAME, LNAME
44 USE netcdf,                                                                   &
45    ONLY:  NF90_MAX_VAR_DIMS, NF90_MAX_NAME
46
47 IMPLICIT NONE
48
49 TYPE grid_definition
50    CHARACTER(LEN=SNAME)  ::  name(3)       !< names of the grid dimensions, e.g. (/'x', 'y', 'z'/) or (/'latitude', 'longitude', 'height'/)
51    INTEGER               ::  nx            !< number of gridpoints in the first dimension
52    INTEGER               ::  ny            !< number of gridpoints in the second dimension
53    INTEGER               ::  nz            !< number of gridpoints in the third dimension
54    INTEGER, ALLOCATABLE  ::  ii(:,:,:)     !< Given a point (i,j,k) in the PALM-4U grid, ii(i,j,l) gives the x index of the l'th horizontl neighbour on the COSMO-DE grid.
55    INTEGER, ALLOCATABLE  ::  jj(:,:,:)     !< Given a point (i,j,k) in the PALM-4U grid, jj(i,j,l) gives the y index of the l'th horizontl neighbour on the COSMO-DE grid.
56    INTEGER, ALLOCATABLE  ::  kk(:,:,:,:)   !< Given a point (i,j,k) in the PALM-4U grid, kk(i,j,k,l) gives the z index of the l'th vertical neighbour in the intermediate grid.
57    REAL(dp)              ::  dx            !< grid spacing in the first dimension [m]
58    REAL(dp)              ::  dy            !< grid spacing in the second dimension [m]
59    REAL(dp)              ::  dz            !< grid spacing in the third dimension [m]
60    REAL(dp)              ::  dxi           !< inverse grid spacing in the first dimension [m^-1]
61    REAL(dp)              ::  dyi           !< inverse grid spacing in the second dimension [m^-1]
62    REAL(dp)              ::  dzi           !< inverse grid spacing in the third dimension [m^-1]
63    REAL(dp)              ::  lx            !< domain length in the first dimension [m]
64    REAL(dp)              ::  ly            !< domain length in the second dimension [m]
65    REAL(dp)              ::  lz            !< domain length in the third dimension [m]
66    REAL(dp)              ::  x0            !< x coordinate of PALM-4U domain projection centre, i.e. location of zero distortion
67    REAL(dp)              ::  y0            !< y coordinate of PALM-4U domain projection centre, i.e. location of zwro distortion
68    REAL(dp)              ::  z0            !< displacement of the coordinate origin above sea level [m]
69    REAL(dp), ALLOCATABLE ::  x(:)          !< coordinates of cell centers in x direction [m]
70    REAL(dp), ALLOCATABLE ::  y(:)          !< coordinates of cell centers in y direction [m]
71    REAL(dp), ALLOCATABLE ::  z(:)          !< coordinates of cell centers in z direction [m]
72    REAL(dp), ALLOCATABLE ::  h(:,:,:)      !< heights grid point for intermediate grids [m]
73    REAL(dp), POINTER     ::  hhl(:,:,:)    !< heights of half layers (cell faces) above sea level in COSMO-DE, read in from
74    REAL(dp), POINTER     ::  hfl(:,:,:)    !< heights of full layers (cell centres) above sea level in COSMO-DE, computed as arithmetic average of hhl
75    REAL(dp), POINTER     ::  depths(:)     !< depths of output soil layers, equal the depths of the source model (e.g. COSMO-DE)
76    REAL(dp), ALLOCATABLE ::  xu(:)         !< coordinates of cell faces in x direction [m]
77    REAL(dp), ALLOCATABLE ::  yv(:)         !< coordinates of cell faces in y direction [m]
78    REAL(dp), ALLOCATABLE ::  zw(:)         !< coordinates of cell faces in z direction [m]
79    REAL(dp), ALLOCATABLE ::  lat(:)        !< rotated-pole latitudes of scalars (cell centers) of the COSMO-DE grid [rad]
80    REAL(dp), ALLOCATABLE ::  lon(:)        !< rotated-pole longitudes of scalars (cell centres) of the COSMO-DE grid [rad]
81    REAL(dp), ALLOCATABLE ::  latv(:)       !< rotated-pole latitudes of v winds (face centres in latitudal/y direction) [rad]
82    REAL(dp), ALLOCATABLE ::  lonu(:)       !< rotated-pole latitudes of u winds (face centres in longitudal/x direction) [rad]
83    REAL(dp), ALLOCATABLE ::  clat(:,:)     !< latitudes of PALM-4U cell centres in COSMO-DE's rotated-pole grid [rad]
84    REAL(dp), ALLOCATABLE ::  clon(:,:)     !< longitudes of PALM-4U scalars (cell centres) in COSMO-DE's rotated-pole grid [rad]
85    REAL(dp), ALLOCATABLE ::  clatu(:,:)    !< latitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
86    REAL(dp), ALLOCATABLE ::  clonu(:,:)    !< longitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
87    REAL(dp), ALLOCATABLE ::  clatv(:,:)    !< latitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
88    REAL(dp), ALLOCATABLE ::  clonv(:,:)    !< longitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
89    REAL(dp), ALLOCATABLE ::  w_horiz(:,:,:)   !< weights for bilinear horizontal interpolation
90    REAL(dp), ALLOCATABLE ::  w_verti(:,:,:,:) !< weights for linear vertical interpolation
91 END TYPE
92
93
94 TYPE nc_file
95    CHARACTER(LEN=PATH)   ::  name          !< file name
96    INTEGER               ::  dimid_time    !< NetCDF IDs of the time dimension
97    INTEGER               ::  dimids_scl(3) !< NetCDF IDs of the grid dimensions for scalar points x, y, z
98    INTEGER               ::  dimids_vel(3) !< NetCDF IDs of the grid dimensions for velocity points xu, yu, zu
99    INTEGER               ::  dimids_soil(3)!< NetCDF IDs of the grid dimensions for soil points x, y, depth
100    INTEGER               ::  dimvarid_time !< NetCDF IDs of the time variable
101    INTEGER               ::  dimvarids_scl(3) !< NetCDF IDs of the grid coordinates of scalars x, y, z
102    INTEGER               ::  dimvarids_vel(3) !< NetCDF IDs of the grid coordinates of velocities xu, yu, zu. Note that velocities are located at mix of both coordinates, e.g. u(xu, y, z).
103    INTEGER               ::  dimvarids_soil(3)!< NetCDF IDs of the grid coordinates for soil points x, y, depth
104    REAL(dp), POINTER     ::  time(:)       ! vector of output time steps
105 END TYPE
106
107
108 TYPE nc_var
109    INTEGER                               ::  varid     !< NetCDF ID of the variable
110    INTEGER                               ::  input_id  !< ID of the correpsonding input variables, only valid for output variables
111    INTEGER                               ::  ndim      !< number of NetCDF dimensions
112    INTEGER                               ::  nt        !< number of output time steps
113    INTEGER                               ::  lod       !< NetCDF attribute indicating the PALM-4U level of detail
114    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimids    !< NetCDF IDs of the dimensions
115    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimvarids !< IDs of NetCDF dimension variables
116    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimlen    !< length of NetCDF dimensions
117    CHARACTER(LEN=NF90_MAX_NAME), DIMENSION(NF90_MAX_VAR_DIMS) ::  dimname !< names of NetCDF dimensions
118    CHARACTER(LEN=SNAME)                  ::  name                      !< NetCDF short name of the variable
119    CHARACTER(LEN=LNAME)                  ::  standard_name             !< NetCDF standard name of the variable
120    CHARACTER(LEN=LNAME)                  ::  long_name                 !< NetCDF long name of the variable
121    CHARACTER(LEN=LNAME)                  ::  source                    !< NetCDF attribute indicating the data source for the output
122    CHARACTER(LEN=SNAME)                  ::  units                     !< NetCDF units of the variable
123    CHARACTER(LEN=SNAME)                  ::  kind                      !< Kind of grid
124    CHARACTER(LEN=SNAME)                  ::  task                      !< Processing task that generates this variable, e.g. 'interpolate_2d' or 'average profile'
125    LOGICAL                               ::  to_be_processed = .FALSE. !< Inifor flag indicating whether variable shall be processed
126    LOGICAL                               ::  is_read = .FALSE.         !< Inifor flag indicating whether variable has been read
127    LOGICAL                               ::  is_upside_down  = .FALSE. !< Inifor flag indicating whether variable shall be processed
128    TYPE(grid_definition), POINTER        ::  grid                      !< Pointer to the corresponding output grid
129    TYPE(grid_definition), POINTER        ::  intermediate_grid         !< Pointer to the corresponding intermediate grid
130 END TYPE nc_var
131
132
133 TYPE io_group                                          !< Input/Output group, groups together output variabels that share their input variables. For instance, all boundary surfaces and initialization fields of the potential temperature are base on T and p.
134    INTEGER                          ::  nt             !< maximum number of output time steps across all output variables
135    INTEGER                          ::  nv             !< number of output variables
136    CHARACTER(LEN=SNAME)             ::  kind           !< kind of I/O group
137    CHARACTER(LEN=PATH), ALLOCATABLE ::  in_files(:)    !< list of nt input files
138    TYPE(nc_var), ALLOCATABLE        ::  out_vars(:)    !< list of output variables
139    TYPE(nc_var), ALLOCATABLE        ::  in_var_list(:) !< list of input variables
140    LOGICAL                          ::  to_be_processed = .FALSE. !< Inifor flag indicating whether I/O group shall be processed
141    LOGICAL                          ::  is_accumulated = .FALSE.  !< Flag indicating whether this I/O group contains accumulated variables
142    LOGICAL                          ::  is_preprocessed = .FALSE. !< Inifor flag indicating whether the I/O group has been preprocessed
143 END TYPE io_group 
144
145
146 TYPE container
147   REAL(dp), ALLOCATABLE ::  array(:,:,:)
148   LOGICAL               ::  is_preprocessed = .FALSE.
149 END TYPE container
150
151 END MODULE types
152
Note: See TracBrowser for help on using the repository browser.