Ignore:
Timestamp:
Jul 27, 2018 1:36:03 PM (6 years ago)
Author:
suehring
Message:

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/src/types.f90

    r2718 r3182  
    2121! Current revisions:
    2222! -----------------
     23! Introduced new PALM grid stretching:
     24! - Converted vertical grid_definition coordinte variables to pointers
     25! Improved command line interface:
     26! - Moved INIFOR configuration into a new derived data type
     27! Removed unnecessary variables
    2328!
    2429!
     
    4146 
    4247 USE defs,                                                                     &
    43     ONLY:  dp, PATH, SNAME, LNAME
     48    ONLY:  dp, DATE, PATH, SNAME, LNAME
    4449 USE netcdf,                                                                   &
    4550    ONLY:  NF90_MAX_VAR_DIMS, NF90_MAX_NAME
    4651
    4752 IMPLICIT NONE
     53
     54 TYPE inifor_config
     55    CHARACTER(LEN=DATE)  ::  start_date           !< String of the FORMAT YYYYMMDDHH indicating the start of the intended PALM-4U simulation
     56
     57    CHARACTER(LEN=PATH)  ::  input_path           !< Path to the input data file directory
     58    CHARACTER(LEN=PATH)  ::  hhl_file             !< Path to the file containing the COSMO-DE HHL variable (height of half layers, i.e. vertical cell faces)
     59    CHARACTER(LEN=PATH)  ::  namelist_file        !< Path to the PALM-4U namelist file
     60    CHARACTER(LEN=PATH)  ::  output_file          !< Path to the INIFOR output file (i.e. PALM-4U dynamic driver')
     61    CHARACTER(LEN=PATH)  ::  soiltyp_file         !< Path to the file containing the COSMO-DE SOILTYP variable (map of COSMO-DE soil types)
     62    CHARACTER(LEN=PATH)  ::  static_driver_file   !< Path to the file containing the COSMO-DE SOILTYP variable (map of COSMO-DE soil types)
     63
     64    CHARACTER(LEN=SNAME) ::  flow_prefix          !< Prefix of flow input files, e.g. 'laf' for COSMO-DE analyses
     65    CHARACTER(LEN=SNAME) ::  soil_prefix          !< Prefix of soil input files, e.g. 'laf' for COSMO-DE analyses
     66    CHARACTER(LEN=SNAME) ::  radiation_prefix     !< Prefix of radiation input files, e.g 'laf' for COSMO-DE analyses
     67    CHARACTER(LEN=SNAME) ::  soilmoisture_prefix  !< Prefix of input files for soil moisture spin-up, e.g 'laf' for COSMO-DE analyses
     68
     69    CHARACTER(LEN=SNAME) ::  bc_mode
     70    CHARACTER(LEN=SNAME) ::  ic_mode
     71    CHARACTER(LEN=SNAME) ::  rotation_method
     72
     73    REAL(dp)             ::  p0
     74    REAL(dp)             ::  ug
     75    REAL(dp)             ::  vg
     76    REAL(dp)             ::  z0 !< Elevation of the PALM-4U domain above sea level [m]
     77 END TYPE inifor_config
    4878
    4979 TYPE grid_definition
     
    5585    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.
    5686    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]
    6387    REAL(dp)              ::  lx            !< domain length in the first dimension [m]
    6488    REAL(dp)              ::  ly            !< domain length in the second dimension [m]
    65     REAL(dp)              ::  lz            !< domain length in the third dimension [m]
    6689    REAL(dp)              ::  x0            !< x coordinate of PALM-4U domain projection centre, i.e. location of zero distortion
    6790    REAL(dp)              ::  y0            !< y coordinate of PALM-4U domain projection centre, i.e. location of zwro distortion
     
    6992    REAL(dp), ALLOCATABLE ::  x(:)          !< coordinates of cell centers in x direction [m]
    7093    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]
     94    REAL(dp), POINTER    ::  z(:)          !< coordinates of cell centers in z direction [m]
    7295    REAL(dp), ALLOCATABLE ::  h(:,:,:)      !< heights grid point for intermediate grids [m]
    7396    REAL(dp), POINTER     ::  hhl(:,:,:)    !< heights of half layers (cell faces) above sea level in COSMO-DE, read in from
     
    7699    REAL(dp), ALLOCATABLE ::  xu(:)         !< coordinates of cell faces in x direction [m]
    77100    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]
     101    REAL(dp), POINTER    ::  zw(:)         !< coordinates of cell faces in z direction [m]
    79102    REAL(dp), ALLOCATABLE ::  lat(:)        !< rotated-pole latitudes of scalars (cell centers) of the COSMO-DE grid [rad]
    80103    REAL(dp), ALLOCATABLE ::  lon(:)        !< rotated-pole longitudes of scalars (cell centres) of the COSMO-DE grid [rad]
     
    89112    REAL(dp), ALLOCATABLE ::  w_horiz(:,:,:)   !< weights for bilinear horizontal interpolation
    90113    REAL(dp), ALLOCATABLE ::  w_verti(:,:,:,:) !< weights for linear vertical interpolation
    91  END TYPE
     114 END TYPE grid_definition
    92115
    93116
     
    103126    INTEGER               ::  dimvarids_soil(3)!< NetCDF IDs of the grid coordinates for soil points x, y, depth
    104127    REAL(dp), POINTER     ::  time(:)       ! vector of output time steps
    105  END TYPE
     128 END TYPE nc_file
    106129
    107130
     
    123146    CHARACTER(LEN=SNAME)                  ::  kind                      !< Kind of grid
    124147    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
     148    LOGICAL                               ::  to_be_processed = .FALSE. !< INIFOR flag indicating whether variable shall be processed
     149    LOGICAL                               ::  is_read = .FALSE.         !< INIFOR flag indicating whether variable has been read
     150    LOGICAL                               ::  is_upside_down  = .FALSE. !< INIFOR flag indicating whether variable shall be processed
    128151    TYPE(grid_definition), POINTER        ::  grid                      !< Pointer to the corresponding output grid
    129152    TYPE(grid_definition), POINTER        ::  intermediate_grid         !< Pointer to the corresponding intermediate grid
Note: See TracChangeset for help on using the changeset viewer.