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

Last change on this file since 3447 was 3447, checked in by eckhard, 5 years ago

inifor: Renamed source files for compatibilty with PALM build system

  • Property svn:keywords set to Id
File size: 14.9 KB
Line 
1!> @file src/inifor_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: inifor_types.f90 3447 2018-10-29 15:52:54Z eckhard $
28! Renamed source files for compatibilty with PALM build system
29!
30!
31! 3395 2018-10-22 17:32:49Z eckhard
32! Added *_is_set LOGICALs to inifor_config type to indicate option invocation
33!     from the command-line
34! Added 1D index vertical weights lists to support addressing averaging regions
35!     by list of columns instead of index bounds
36!
37!
38! 3183 2018-07-27 14:25:55Z suehring
39! Introduced new PALM grid stretching:
40! - Converted vertical grid_definition coordinte variables to pointers
41! Improved command line interface:
42! - Moved INIFOR configuration into a new derived data type
43! Removed unnecessary variables
44!
45!
46! 3182 2018-07-27 13:36:03Z suehring
47! Initial revision
48!
49!
50!
51! Authors:
52! --------
53! @author Eckhard Kadasch
54!
55! Description:
56! ------------
57!> The types module provides derived data types used in INIFOR.
58!------------------------------------------------------------------------------!
59 MODULE types
60 
61 USE defs,                                                                     &
62    ONLY:  dp, DATE, PATH, SNAME, LNAME
63 USE netcdf,                                                                   &
64    ONLY:  NF90_MAX_VAR_DIMS, NF90_MAX_NAME
65
66 IMPLICIT NONE
67
68 TYPE inifor_config
69    CHARACTER(LEN=DATE)  ::  start_date           !< String of the FORMAT YYYYMMDDHH indicating the start of the intended PALM-4U simulation
70
71    CHARACTER(LEN=PATH)  ::  input_path           !< Path to the input data file directory
72    CHARACTER(LEN=PATH)  ::  hhl_file             !< Path to the file containing the COSMO-DE HHL variable (height of half layers, i.e. vertical cell faces)
73    CHARACTER(LEN=PATH)  ::  namelist_file        !< Path to the PALM-4U namelist file
74    CHARACTER(LEN=PATH)  ::  output_file          !< Path to the INIFOR output file (i.e. PALM-4U dynamic driver')
75    CHARACTER(LEN=PATH)  ::  soiltyp_file         !< Path to the file containing the COSMO-DE SOILTYP variable (map of COSMO-DE soil types)
76    CHARACTER(LEN=PATH)  ::  static_driver_file   !< Path to the file containing the COSMO-DE SOILTYP variable (map of COSMO-DE soil types)
77
78    CHARACTER(LEN=SNAME) ::  flow_prefix          !< Prefix of flow input files, e.g. 'laf' for COSMO-DE analyses
79    CHARACTER(LEN=SNAME) ::  input_prefix         !< Prefix of all input files, e.g. 'laf' for COSMO-DE analyses
80    CHARACTER(LEN=SNAME) ::  radiation_prefix     !< Prefix of radiation input files, e.g 'laf' for COSMO-DE analyses
81    CHARACTER(LEN=SNAME) ::  soil_prefix          !< Prefix of soil input files, e.g. 'laf' for COSMO-DE analyses
82    CHARACTER(LEN=SNAME) ::  soilmoisture_prefix  !< Prefix of input files for soil moisture spin-up, e.g 'laf' for COSMO-DE analyses
83
84    CHARACTER(LEN=SNAME) ::  averaging_mode
85    CHARACTER(LEN=SNAME) ::  bc_mode
86    CHARACTER(LEN=SNAME) ::  ic_mode
87    CHARACTER(LEN=SNAME) ::  rotation_method
88
89    REAL(dp)             ::  p0
90    REAL(dp)             ::  ug
91    REAL(dp)             ::  vg
92    REAL(dp)             ::  z0                   !< Elevation of the PALM-4U domain above sea level [m]
93    REAL(dp)             ::  averaging_angle      !< latitudal and longitudal width of averaging regions [deg]
94   
95
96    LOGICAL              ::  debug
97    LOGICAL              ::  p0_is_set
98    LOGICAL              ::  ug_is_set
99    LOGICAL              ::  vg_is_set
100    LOGICAL              ::  flow_prefix_is_set          !<
101    LOGICAL              ::  input_prefix_is_set         !<
102    LOGICAL              ::  radiation_prefix_is_set     !<
103    LOGICAL              ::  soil_prefix_is_set          !<
104    LOGICAL              ::  soilmoisture_prefix_is_set  !<
105 END TYPE inifor_config
106
107 TYPE grid_definition
108    CHARACTER(LEN=SNAME)  ::  name(3)       !< names of the grid dimensions, e.g. (/'x', 'y', 'z'/) or (/'latitude', 'longitude', 'height'/)
109    CHARACTER(LEN=SNAME)  ::  kind          !< names of the grid dimensions, e.g. (/'x', 'y', 'z'/) or (/'latitude', 'longitude', 'height'/)
110    INTEGER               ::  k_min         !< Index of lowest PALM grid level that is not cut by local COSMO orography; vertically separates interpolation and extrapolation region.
111    INTEGER               ::  nx            !< number of gridpoints in the first dimension
112    INTEGER               ::  ny            !< number of gridpoints in the second dimension
113    INTEGER               ::  nz            !< number of gridpoints in the third dimension, used for PALM points
114    INTEGER               ::  nlev          !< number of COSMO grid levels
115    INTEGER               ::  n_columns     !< number of averaging columns of the source grid
116    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.
117    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.
118    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.
119    INTEGER, ALLOCATABLE  ::  iii(:)        !< profile averaging neighbour indices
120    INTEGER, ALLOCATABLE  ::  jjj(:)        !< profile averaging neighbour indices
121    INTEGER, ALLOCATABLE  ::  kkk(:,:,:)    !< indices of vertical interpolation neightbours, kkk(<source column>, <PALM k level>, <neighbour index>)
122    REAL(dp)              ::  lx            !< domain length in the first dimension [m]
123    REAL(dp)              ::  ly            !< domain length in the second dimension [m]
124    REAL(dp)              ::  x0            !< x coordinate of PALM-4U domain projection centre, i.e. location of zero distortion
125    REAL(dp)              ::  y0            !< y coordinate of PALM-4U domain projection centre, i.e. location of zwro distortion
126    REAL(dp)              ::  z0            !< displacement of the coordinate origin above sea level [m]
127    REAL(dp), ALLOCATABLE ::  x(:)          !< coordinates of cell centers in x direction [m]
128    REAL(dp), ALLOCATABLE ::  y(:)          !< coordinates of cell centers in y direction [m]
129    REAL(dp), POINTER     ::  z(:)          !< coordinates of cell centers in z direction [m]
130    REAL(dp), ALLOCATABLE ::  h(:,:,:)      !< heights grid point for intermediate grids [m]
131    REAL(dp), POINTER     ::  cosmo_h(:,:,:)!< pointer to appropriate COSMO level heights (scalar/w) [m]
132    REAL(dp), POINTER     ::  hhl(:,:,:)    !< heights of half layers (cell faces) above sea level in COSMO-DE, read in from
133    REAL(dp), POINTER     ::  hfl(:,:,:)    !< heights of full layers (cell centres) above sea level in COSMO-DE, computed as arithmetic average of hhl
134    REAL(dp), POINTER     ::  depths(:)     !< depths of output soil layers, equal the depths of the source model (e.g. COSMO-DE)
135    REAL(dp), ALLOCATABLE ::  xu(:)         !< coordinates of cell faces in x direction [m]
136    REAL(dp), ALLOCATABLE ::  yv(:)         !< coordinates of cell faces in y direction [m]
137    REAL(dp), POINTER     ::  zw(:)         !< coordinates of cell faces in z direction [m]
138    REAL(dp), ALLOCATABLE ::  lat(:)        !< rotated-pole latitudes of scalars (cell centers) of the COSMO-DE grid [rad]
139    REAL(dp), ALLOCATABLE ::  lon(:)        !< rotated-pole longitudes of scalars (cell centres) of the COSMO-DE grid [rad]
140    REAL(dp), ALLOCATABLE ::  latv(:)       !< rotated-pole latitudes of v winds (face centres in latitudal/y direction) [rad]
141    REAL(dp), ALLOCATABLE ::  lonu(:)       !< rotated-pole latitudes of u winds (face centres in longitudal/x direction) [rad]
142    REAL(dp), ALLOCATABLE ::  clat(:,:)     !< latitudes of PALM-4U cell centres in COSMO-DE's rotated-pole grid [rad]
143    REAL(dp), ALLOCATABLE ::  clon(:,:)     !< longitudes of PALM-4U scalars (cell centres) in COSMO-DE's rotated-pole grid [rad]
144    REAL(dp), ALLOCATABLE ::  clatu(:,:)    !< latitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
145    REAL(dp), ALLOCATABLE ::  clonu(:,:)    !< longitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
146    REAL(dp), ALLOCATABLE ::  clatv(:,:)    !< latitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
147    REAL(dp), ALLOCATABLE ::  clonv(:,:)    !< longitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
148    REAL(dp), ALLOCATABLE ::  w_horiz(:,:,:)   !< weights for bilinear horizontal interpolation
149    REAL(dp), ALLOCATABLE ::  w_verti(:,:,:,:) !< weights for linear vertical interpolation
150    REAL(dp), ALLOCATABLE ::  w(:,:,:)      !< vertical interpolation weights, w(<source_column>, <PALM k level>, <neighbour index>) [-]
151 END TYPE grid_definition
152
153
154 TYPE nc_file
155    CHARACTER(LEN=PATH)   ::  name          !< file name
156    INTEGER               ::  dimid_time    !< NetCDF IDs of the time dimension
157    INTEGER               ::  dimids_scl(3) !< NetCDF IDs of the grid dimensions for scalar points x, y, z
158    INTEGER               ::  dimids_vel(3) !< NetCDF IDs of the grid dimensions for velocity points xu, yu, zu
159    INTEGER               ::  dimids_soil(3)!< NetCDF IDs of the grid dimensions for soil points x, y, depth
160    INTEGER               ::  dimvarid_time !< NetCDF IDs of the time variable
161    INTEGER               ::  dimvarids_scl(3) !< NetCDF IDs of the grid coordinates of scalars x, y, z
162    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).
163    INTEGER               ::  dimvarids_soil(3)!< NetCDF IDs of the grid coordinates for soil points x, y, depth
164    REAL(dp), POINTER     ::  time(:)       ! vector of output time steps
165 END TYPE nc_file
166
167
168 TYPE nc_var
169    INTEGER                               ::  varid     !< NetCDF ID of the variable
170    INTEGER                               ::  input_id  !< ID of the correpsonding input variables, only valid for output variables
171    INTEGER                               ::  ndim      !< number of NetCDF dimensions
172    INTEGER                               ::  nt        !< number of output time steps
173    INTEGER                               ::  lod       !< NetCDF attribute indicating the PALM-4U level of detail
174    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimids    !< NetCDF IDs of the dimensions
175    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimvarids !< IDs of NetCDF dimension variables
176    INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) ::  dimlen    !< length of NetCDF dimensions
177    CHARACTER(LEN=NF90_MAX_NAME), DIMENSION(NF90_MAX_VAR_DIMS) ::  dimname !< names of NetCDF dimensions
178    CHARACTER(LEN=SNAME)                  ::  name                      !< NetCDF short name of the variable
179    CHARACTER(LEN=LNAME)                  ::  standard_name             !< NetCDF standard name of the variable
180    CHARACTER(LEN=LNAME)                  ::  long_name                 !< NetCDF long name of the variable
181    CHARACTER(LEN=LNAME)                  ::  source                    !< NetCDF attribute indicating the data source for the output
182    CHARACTER(LEN=SNAME)                  ::  units                     !< NetCDF units of the variable
183    CHARACTER(LEN=SNAME)                  ::  kind                      !< Kind of grid
184    CHARACTER(LEN=SNAME)                  ::  task                      !< Processing task that generates this variable, e.g. 'interpolate_2d' or 'average profile'
185    LOGICAL                               ::  to_be_processed = .FALSE. !< INIFOR flag indicating whether variable shall be processed
186    LOGICAL                               ::  is_internal = .FALSE.     !< INIFOR flag indicating whether variable shall be written to netCDF file (.FALSE.) or kept for later (.TRUE.)
187    LOGICAL                               ::  is_read = .FALSE.         !< INIFOR flag indicating whether variable has been read
188    LOGICAL                               ::  is_upside_down  = .FALSE. !< INIFOR flag indicating whether vertical dimension is reversed (typically the case with COSMO-DE atmospheric fields)
189    TYPE(grid_definition), POINTER        ::  grid                      !< Pointer to the corresponding output grid
190    TYPE(grid_definition), POINTER        ::  intermediate_grid         !< Pointer to the corresponding intermediate grid
191    TYPE(grid_definition), POINTER        ::  averaging_grid         !< Pointer to the corresponding intermediate grid
192 END TYPE nc_var
193
194
195 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.
196    INTEGER                          ::  nt             !< maximum number of output time steps across all output variables
197    INTEGER                          ::  nv             !< number of netCDF output variables
198    INTEGER                          ::  n_inputs       !< number of input variables
199    INTEGER                          ::  n_output_quantities !< number of physical quantities required for computing netCDF output variables
200    CHARACTER(LEN=SNAME)             ::  kind           !< kind of I/O group
201    CHARACTER(LEN=PATH), ALLOCATABLE ::  in_files(:)    !< list of nt input files
202    TYPE(nc_var), ALLOCATABLE        ::  out_vars(:)    !< list of output variables
203    TYPE(nc_var), ALLOCATABLE        ::  in_var_list(:) !< list of input variables
204    LOGICAL                          ::  to_be_processed = .FALSE. !< Inifor flag indicating whether I/O group shall be processed
205    LOGICAL                          ::  is_accumulated = .FALSE.  !< Flag indicating whether this I/O group contains accumulated variables
206    LOGICAL                          ::  is_preprocessed = .FALSE. !< Inifor flag indicating whether the I/O group has been preprocessed
207 END TYPE io_group 
208
209
210 TYPE container
211   REAL(dp), ALLOCATABLE ::  array(:,:,:)
212   LOGICAL               ::  is_preprocessed = .FALSE.
213 END TYPE container
214
215 END MODULE types
216
Note: See TracBrowser for help on using the repository browser.