source: palm/trunk/UTIL/inifor/src/inifor_types.f90 @ 4901

Last change on this file since 4901 was 4843, checked in by raasch, 3 years ago

local namelist parameter added to switch off the module although the respective module namelist appears in the namelist file, further copyright updates

  • Property svn:keywords set to Id
File size: 20.0 KB
RevLine 
[3447]1!> @file src/inifor_types.f90
[2696]2!------------------------------------------------------------------------------!
[2718]3! This file is part of the PALM model system.
[2696]4!
[2718]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
[2696]8! version.
9!
[2718]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.
[2696]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!
[4843]17! Copyright 2017-2021 Leibniz Universitaet Hannover
18! Copyright 2017-2021 Deutscher Wetterdienst Offenbach
[2696]19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
[4659]23!
24!
[3183]25! Former revisions:
26! -----------------
27! $Id: inifor_types.f90 4843 2021-01-15 15:22:11Z banzhafs $
[4675]28! Added INIFOR configuration flag for soil profile initialization
29!
30!
31! 4659 2020-08-31 11:21:17Z eckhard
[4659]32! Added flag in support of new command-line option '--precipitation'
33! Improved code formatting
34!
35!
36! 4568 2020-06-19 11:56:30Z eckhard
[4568]37! Handle COSMO soil data with and without additional surface temperature
38!
39!
40! 4553 2020-06-03 16:34:15Z eckhard
[4553]41! Minor code readability improvements
42!
43!
44! 4538 2020-05-18 13:45:35Z eckhard
[4538]45! Added boolean indicator for --static-driver option invocation
46!
47!
48! 4523 2020-05-07 15:58:16Z eckhard
[4523]49! respect integer working precision (iwp) specified in inifor_defs.f90
50!
51!
52! 4481 2020-03-31 18:55:54Z maronga
[3997]53! Added boolean indicator for --elevation option invocation, sorted varibles
54!
55!
56! 3866 2019-04-05 14:25:01Z eckhard
[3866]57! Use PALM's working precision
58!
59!
60! 3779 2019-03-05 11:13:35Z eckhard
[3779]61! Improved variable naming
62!
63! 3680 2019-01-18 14:54:12Z knoop
[3618]64! Prefixed all INIFOR modules with inifor_
65!
66!
67! 3557 2018-11-22 16:01:22Z eckhard
[3557]68! Updated documentation
69!
70!
71! 3447 2018-10-29 15:52:54Z eckhard
[3447]72! Renamed source files for compatibilty with PALM build system
73!
74!
75! 3395 2018-10-22 17:32:49Z eckhard
[3395]76! Added *_is_set LOGICALs to inifor_config type to indicate option invocation
77!     from the command-line
78! Added 1D index vertical weights lists to support addressing averaging regions
79!     by list of columns instead of index bounds
80!
81!
82! 3183 2018-07-27 14:25:55Z suehring
[3182]83! Introduced new PALM grid stretching:
84! - Converted vertical grid_definition coordinte variables to pointers
85! Improved command line interface:
86! - Moved INIFOR configuration into a new derived data type
87! Removed unnecessary variables
[2696]88!
89!
[3183]90! 3182 2018-07-27 13:36:03Z suehring
[2696]91! Initial revision
92!
93!
94!
95! Authors:
96! --------
[3557]97!> @author Eckhard Kadasch (Deutscher Wetterdienst, Offenbach)
[2696]98!
99! Description:
100! ------------
101!> The types module provides derived data types used in INIFOR.
102!------------------------------------------------------------------------------!
[3618]103 MODULE inifor_types
[2696]104 
[3618]105 USE inifor_defs,                                                              &
[4523]106    ONLY:  DATE, PATH, SNAME, LNAME, iwp, wp
[3866]107
108#if defined ( __netcdf )
[2696]109 USE netcdf,                                                                   &
110    ONLY:  NF90_MAX_VAR_DIMS, NF90_MAX_NAME
[3866]111#endif
[2696]112
113 IMPLICIT NONE
114
[3557]115!------------------------------------------------------------------------------!
116! Description:
117! ------------
118!> Contaner for the INIFOR command-line configuration
119!------------------------------------------------------------------------------!
[3182]120 TYPE inifor_config
121    CHARACTER(LEN=DATE)  ::  start_date           !< String of the FORMAT YYYYMMDDHH indicating the start of the intended PALM-4U simulation
122
123    CHARACTER(LEN=PATH)  ::  input_path           !< Path to the input data file directory
124    CHARACTER(LEN=PATH)  ::  hhl_file             !< Path to the file containing the COSMO-DE HHL variable (height of half layers, i.e. vertical cell faces)
125    CHARACTER(LEN=PATH)  ::  namelist_file        !< Path to the PALM-4U namelist file
126    CHARACTER(LEN=PATH)  ::  output_file          !< Path to the INIFOR output file (i.e. PALM-4U dynamic driver')
127    CHARACTER(LEN=PATH)  ::  soiltyp_file         !< Path to the file containing the COSMO-DE SOILTYP variable (map of COSMO-DE soil types)
128    CHARACTER(LEN=PATH)  ::  static_driver_file   !< Path to the file containing the COSMO-DE SOILTYP variable (map of COSMO-DE soil types)
129
130    CHARACTER(LEN=SNAME) ::  flow_prefix          !< Prefix of flow input files, e.g. 'laf' for COSMO-DE analyses
[3395]131    CHARACTER(LEN=SNAME) ::  input_prefix         !< Prefix of all input files, e.g. 'laf' for COSMO-DE analyses
132    CHARACTER(LEN=SNAME) ::  radiation_prefix     !< Prefix of radiation input files, e.g 'laf' for COSMO-DE analyses
[3182]133    CHARACTER(LEN=SNAME) ::  soil_prefix          !< Prefix of soil input files, e.g. 'laf' for COSMO-DE analyses
[4659]134    CHARACTER(LEN=SNAME) ::  precipitation_prefix !< Prefix of input files for precipitation forcing, e.g 'laf' for COSMO-DE analyses
[3182]135
[3557]136    CHARACTER(LEN=SNAME) ::  averaging_mode       !< destinguishes between level-based and heigh-based averaging
137    CHARACTER(LEN=SNAME) ::  bc_mode              !< destinguishes realistic and idealistic forcing
138    CHARACTER(LEN=SNAME) ::  ic_mode              !< destinguishes volume and profile initialization
[4675]139    CHARACTER(LEN=SNAME) ::  isc_mode             !< destinguishes volume and profile soil initialization
[3557]140    CHARACTER(LEN=SNAME) ::  rotation_method      !< selects method for velocity rotation
[3182]141
[3866]142    REAL(wp)             ::  p0                   !< manually specified surface pressure [Pa]
143    REAL(wp)             ::  ug                   !< manually spefied geostrophic wind component in x direction [m/s]
144    REAL(wp)             ::  vg                   !< manually spefied geostrophic wind component in y direction [m/s]
145    REAL(wp)             ::  z0                   !< elevation of the PALM-4U domain above sea level [m]
146    REAL(wp)             ::  averaging_angle      !< latitudal and longitudal width of averaging regions [deg]
[3395]147   
[3557]148    LOGICAL              ::  debug                       !< indicates whether --debug option was given
[3779]149    LOGICAL              ::  flow_prefix_is_set          !< indicates whether the flow prefix was set manually
150    LOGICAL              ::  input_prefix_is_set         !< indicates whether the input prefix was set manually
[3997]151    LOGICAL              ::  p0_is_set                   !< indicates whether p0 was set manually
[3779]152    LOGICAL              ::  radiation_prefix_is_set     !< indicates whether the radiation prefix was set manually
153    LOGICAL              ::  soil_prefix_is_set          !< indicates whether the soil prefix was set manually
[4659]154    LOGICAL              ::  precipitation_prefix_is_set !< indicates whether the precipitation prefix was set manually
155    LOGICAL              ::  process_precipitation       !< indicates whether precipitation should be processed
[4538]156    LOGICAL              ::  static_driver_is_set        !< indicates whether a static driver was given
[3997]157    LOGICAL              ::  ug_defined_by_user          !< indicates whether ug was set manually
158    LOGICAL              ::  vg_defined_by_user          !< indicates whether vg was set manually
159    LOGICAL              ::  z0_is_set                   !< indicates whether z0 was set manually
[3182]160 END TYPE inifor_config
161
[3557]162
163!------------------------------------------------------------------------------!
164! Description:
165! ------------
166!> Container for grid data, in partucular coordinates, interpolation neighbours
167!> and weights
168!------------------------------------------------------------------------------!
[2696]169 TYPE grid_definition
170    CHARACTER(LEN=SNAME)  ::  name(3)       !< names of the grid dimensions, e.g. (/'x', 'y', 'z'/) or (/'latitude', 'longitude', 'height'/)
[3395]171    CHARACTER(LEN=SNAME)  ::  kind          !< names of the grid dimensions, e.g. (/'x', 'y', 'z'/) or (/'latitude', 'longitude', 'height'/)
[4523]172    INTEGER(iwp)               ::  k_min         !< Index of lowest PALM grid level that is not cut by local COSMO orography; vertically separates interpolation and extrapolation region.
173    INTEGER(iwp)               ::  nx            !< number of gridpoints in the first dimension
174    INTEGER(iwp)               ::  ny            !< number of gridpoints in the second dimension
175    INTEGER(iwp)               ::  nz            !< number of gridpoints in the third dimension, used for PALM points
176    INTEGER(iwp)               ::  nlev          !< number of COSMO grid levels
177    INTEGER(iwp)               ::  n_columns     !< number of averaging columns of the source grid
178    INTEGER(iwp), 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.
179    INTEGER(iwp), 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.
180    INTEGER(iwp), 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.
181    INTEGER(iwp), ALLOCATABLE  ::  iii(:)        !< profile averaging neighbour indices
182    INTEGER(iwp), ALLOCATABLE  ::  jjj(:)        !< profile averaging neighbour indices
183    INTEGER(iwp), ALLOCATABLE  ::  kkk(:,:,:)    !< indices of vertical interpolation neightbours, kkk(<source column>, <PALM k level>, <neighbour index>)
[3866]184    REAL(wp)              ::  lx            !< domain length in the first dimension [m]
185    REAL(wp)              ::  ly            !< domain length in the second dimension [m]
186    REAL(wp)              ::  x0            !< x coordinate of PALM-4U domain projection centre, i.e. location of zero distortion
187    REAL(wp)              ::  y0            !< y coordinate of PALM-4U domain projection centre, i.e. location of zwro distortion
188    REAL(wp)              ::  z0            !< displacement of the coordinate origin above sea level [m]
189    REAL(wp), ALLOCATABLE ::  x(:)          !< coordinates of cell centers in x direction [m]
190    REAL(wp), ALLOCATABLE ::  y(:)          !< coordinates of cell centers in y direction [m]
191    REAL(wp), POINTER     ::  z(:)          !< coordinates of cell centers in z direction [m]
[4553]192    REAL(wp), ALLOCATABLE ::  intermediate_h(:,:,:) !< heights grid point for intermediate grids [m]
[3866]193    REAL(wp), POINTER     ::  cosmo_h(:,:,:)!< pointer to appropriate COSMO level heights (scalar/w) [m]
194    REAL(wp), POINTER     ::  hhl(:,:,:)    !< heights of half layers (cell faces) above sea level in COSMO-DE, read in from
195    REAL(wp), POINTER     ::  hfl(:,:,:)    !< heights of full layers (cell centres) above sea level in COSMO-DE, computed as arithmetic average of hhl
196    REAL(wp), POINTER     ::  depths(:)     !< depths of output soil layers, equal the depths of the source model (e.g. COSMO-DE)
197    REAL(wp), ALLOCATABLE ::  xu(:)         !< coordinates of cell faces in x direction [m]
198    REAL(wp), ALLOCATABLE ::  yv(:)         !< coordinates of cell faces in y direction [m]
199    REAL(wp), POINTER     ::  zw(:)         !< coordinates of cell faces in z direction [m]
200    REAL(wp), ALLOCATABLE ::  lat(:)        !< rotated-pole latitudes of scalars (cell centers) of the COSMO-DE grid [rad]
201    REAL(wp), ALLOCATABLE ::  lon(:)        !< rotated-pole longitudes of scalars (cell centres) of the COSMO-DE grid [rad]
202    REAL(wp), ALLOCATABLE ::  latv(:)       !< rotated-pole latitudes of v winds (face centres in latitudal/y direction) [rad]
203    REAL(wp), ALLOCATABLE ::  lonu(:)       !< rotated-pole latitudes of u winds (face centres in longitudal/x direction) [rad]
204    REAL(wp), ALLOCATABLE ::  clat(:,:)     !< latitudes of PALM-4U cell centres in COSMO-DE's rotated-pole grid [rad]
205    REAL(wp), ALLOCATABLE ::  clon(:,:)     !< longitudes of PALM-4U scalars (cell centres) in COSMO-DE's rotated-pole grid [rad]
206    REAL(wp), ALLOCATABLE ::  clatu(:,:)    !< latitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
207    REAL(wp), ALLOCATABLE ::  clonu(:,:)    !< longitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
208    REAL(wp), ALLOCATABLE ::  clatv(:,:)    !< latitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
209    REAL(wp), ALLOCATABLE ::  clonv(:,:)    !< longitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
210    REAL(wp), ALLOCATABLE ::  w_horiz(:,:,:)   !< weights for bilinear horizontal interpolation
211    REAL(wp), ALLOCATABLE ::  w_verti(:,:,:,:) !< weights for linear vertical interpolation
212    REAL(wp), ALLOCATABLE ::  w(:,:,:)      !< vertical interpolation weights, w(<source_column>, <PALM k level>, <neighbour index>) [-]
[3182]213 END TYPE grid_definition
[2696]214
215
[3557]216!------------------------------------------------------------------------------!
217! Description:
218! ------------
219!> Container for name and dimensions of the netCDF output file
220!------------------------------------------------------------------------------!
[2696]221 TYPE nc_file
[3557]222    CHARACTER(LEN=PATH)   ::  name              !< file name
223    INTEGER               ::  dimid_time        !< NetCDF IDs of the time dimension
224    INTEGER               ::  dimids_scl(3)     !< NetCDF IDs of the grid dimensions for scalar points x, y, z
225    INTEGER               ::  dimids_vel(3)     !< NetCDF IDs of the grid dimensions for velocity points xu, yu, zu
226    INTEGER               ::  dimids_soil(3)    !< NetCDF IDs of the grid dimensions for soil points x, y, depth
227    INTEGER               ::  dimvarid_time     !< NetCDF IDs of the time variable
228    INTEGER               ::  dimvarids_scl(3)  !< NetCDF IDs of the grid coordinates of scalars x, y, z
229    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).
230    INTEGER               ::  dimvarids_soil(3) !< NetCDF IDs of the grid coordinates for soil points x, y, depth
[3866]231    REAL(wp), POINTER     ::  time(:)           !< vector of output time steps
[3182]232 END TYPE nc_file
[2696]233
234
[3557]235!------------------------------------------------------------------------------!
236! Description:
237! ------------
238!> Metadata container for netCDF variables
239!------------------------------------------------------------------------------!
[3866]240#if defined ( __netcdf )
[2696]241 TYPE nc_var
242    INTEGER                               ::  varid     !< NetCDF ID of the variable
243    INTEGER                               ::  input_id  !< ID of the correpsonding input variables, only valid for output variables
244    INTEGER                               ::  ndim      !< number of NetCDF dimensions
[4523]245    INTEGER(iwp)                          ::  nt        !< number of output time steps
[2696]246    INTEGER                               ::  lod       !< NetCDF attribute indicating the PALM-4U level of detail
247    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimids    !< NetCDF IDs of the dimensions
248    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimvarids !< IDs of NetCDF dimension variables
249    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimlen    !< length of NetCDF dimensions
250    CHARACTER(LEN=NF90_MAX_NAME), DIMENSION(NF90_MAX_VAR_DIMS) ::  dimname !< names of NetCDF dimensions
251    CHARACTER(LEN=SNAME)                  ::  name                      !< NetCDF short name of the variable
252    CHARACTER(LEN=LNAME)                  ::  standard_name             !< NetCDF standard name of the variable
253    CHARACTER(LEN=LNAME)                  ::  long_name                 !< NetCDF long name of the variable
254    CHARACTER(LEN=LNAME)                  ::  source                    !< NetCDF attribute indicating the data source for the output
255    CHARACTER(LEN=SNAME)                  ::  units                     !< NetCDF units of the variable
256    CHARACTER(LEN=SNAME)                  ::  kind                      !< Kind of grid
257    CHARACTER(LEN=SNAME)                  ::  task                      !< Processing task that generates this variable, e.g. 'interpolate_2d' or 'average profile'
[3182]258    LOGICAL                               ::  to_be_processed = .FALSE. !< INIFOR flag indicating whether variable shall be processed
[3395]259    LOGICAL                               ::  is_internal = .FALSE.     !< INIFOR flag indicating whether variable shall be written to netCDF file (.FALSE.) or kept for later (.TRUE.)
[4659]260    LOGICAL                               ::  is_optional = .FALSE.     !< Flag indicating whether INIFOR may continue if the the netCDF variable cannot be processed, e.g. if files are missing
[3182]261    LOGICAL                               ::  is_read = .FALSE.         !< INIFOR flag indicating whether variable has been read
[3395]262    LOGICAL                               ::  is_upside_down  = .FALSE. !< INIFOR flag indicating whether vertical dimension is reversed (typically the case with COSMO-DE atmospheric fields)
[4568]263    LOGICAL                               ::  has_redundant_first_level !< INIFOR flag inidicating whether a soil variable has a redundant first level (e.g. COSMO's T_SO may contain the surface temperature at depth=0, which is a redundant copy the first model layer)
[2696]264    TYPE(grid_definition), POINTER        ::  grid                      !< Pointer to the corresponding output grid
265    TYPE(grid_definition), POINTER        ::  intermediate_grid         !< Pointer to the corresponding intermediate grid
[4659]266    TYPE(grid_definition), POINTER        ::  averaging_grid            !< Pointer to the corresponding intermediate grid
[2696]267 END TYPE nc_var
268
269
[3557]270!------------------------------------------------------------------------------!
271! Description:
272! ------------
273!> Input/Output group, groups together nc_var-type output variabels that share
274!> input variables as well as lists of the netCDF files they are stored in.
275!> For instance, all boundary surfaces and initialization fields of the
276!> potential temperature are base on the input netCDF variables T and P.
277!------------------------------------------------------------------------------!
278 TYPE io_group
[4659]279    INTEGER(iwp)                     ::  nt                  !< maximum number of output time steps across all output variables
280    INTEGER(iwp)                     ::  nv                  !< number of netCDF output variables
281    INTEGER(iwp)                     ::  n_inputs            !< number of input variables
282    INTEGER(iwp)                     ::  n_output_quantities !< number of physical quantities required for computing netCDF output variables
283    CHARACTER(LEN=SNAME)             ::  name                !< name of I/O group
284    CHARACTER(LEN=SNAME)             ::  kind                !< kind of I/O group
285    CHARACTER(LEN=PATH), ALLOCATABLE ::  in_files(:)         !< list of nt input files
286    TYPE(nc_var), ALLOCATABLE        ::  out_vars(:)         !< list of output variables
287    TYPE(nc_var), ALLOCATABLE        ::  in_var_list(:)      !< list of input variables
[2696]288    LOGICAL                          ::  to_be_processed = .FALSE. !< Inifor flag indicating whether I/O group shall be processed
289    LOGICAL                          ::  is_accumulated = .FALSE.  !< Flag indicating whether this I/O group contains accumulated variables
[4659]290    LOGICAL                          ::  is_optional = .FALSE.     !< Flag indicating whether INIFOR may continue if group cannot be processed, e.g. if files are missing
[2696]291    LOGICAL                          ::  is_preprocessed = .FALSE. !< Inifor flag indicating whether the I/O group has been preprocessed
292 END TYPE io_group 
[3866]293#endif
[2696]294
[3557]295!------------------------------------------------------------------------------!
296! Description:
297! ------------
298!> Container for input data arrays. read_input_variables() allocates a
299!> one-dimensional array of containers, to accomodate all inputs of the given
300!> IO group in one variable.
301!------------------------------------------------------------------------------!
[2696]302 TYPE container
[3866]303   REAL(wp), ALLOCATABLE ::  array(:,:,:)               !< generic data array
[3557]304   LOGICAL               ::  is_preprocessed = .FALSE.  !< flag indicating whether input array has been preprocessed
[2696]305 END TYPE container
306
[3618]307 END MODULE inifor_types
Note: See TracBrowser for help on using the repository browser.