Ignore:
Timestamp:
Apr 5, 2019 2:25:01 PM (5 years ago)
Author:
eckhard
Message:

inifor: Use PALM's working precision; improved error handling, coding style, and comments

File:
1 edited

Legend:

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

    r3779 r3866  
    2626! -----------------
    2727! $Id$
     28! Use PALM's working precision
     29!
     30!
     31! 3779 2019-03-05 11:13:35Z eckhard
    2832! Improved variable naming
    2933!
     
    6872!> The types module provides derived data types used in INIFOR.
    6973!------------------------------------------------------------------------------!
    70 #if defined ( __netcdf )
    7174 MODULE inifor_types
    7275 
    7376 USE inifor_defs,                                                              &
    74     ONLY:  dp, DATE, PATH, SNAME, LNAME
     77    ONLY:  DATE, PATH, SNAME, LNAME, wp
     78
     79#if defined ( __netcdf )
    7580 USE netcdf,                                                                   &
    7681    ONLY:  NF90_MAX_VAR_DIMS, NF90_MAX_NAME
     82#endif
    7783
    7884 IMPLICIT NONE
     
    104110    CHARACTER(LEN=SNAME) ::  rotation_method      !< selects method for velocity rotation
    105111
    106     REAL(dp)             ::  p0                   !< manually specified surface pressure [Pa]
    107     REAL(dp)             ::  ug                   !< manually spefied geostrophic wind component in x direction [m/s]
    108     REAL(dp)             ::  vg                   !< manually spefied geostrophic wind component in y direction [m/s]
    109     REAL(dp)             ::  z0                   !< elevation of the PALM-4U domain above sea level [m]
    110     REAL(dp)             ::  averaging_angle      !< latitudal and longitudal width of averaging regions [deg]
     112    REAL(wp)             ::  p0                   !< manually specified surface pressure [Pa]
     113    REAL(wp)             ::  ug                   !< manually spefied geostrophic wind component in x direction [m/s]
     114    REAL(wp)             ::  vg                   !< manually spefied geostrophic wind component in y direction [m/s]
     115    REAL(wp)             ::  z0                   !< elevation of the PALM-4U domain above sea level [m]
     116    REAL(wp)             ::  averaging_angle      !< latitudal and longitudal width of averaging regions [deg]
    111117   
    112118    LOGICAL              ::  debug                       !< indicates whether --debug option was given
     
    143149    INTEGER, ALLOCATABLE  ::  jjj(:)        !< profile averaging neighbour indices
    144150    INTEGER, ALLOCATABLE  ::  kkk(:,:,:)    !< indices of vertical interpolation neightbours, kkk(<source column>, <PALM k level>, <neighbour index>)
    145     REAL(dp)              ::  lx            !< domain length in the first dimension [m]
    146     REAL(dp)              ::  ly            !< domain length in the second dimension [m]
    147     REAL(dp)              ::  x0            !< x coordinate of PALM-4U domain projection centre, i.e. location of zero distortion
    148     REAL(dp)              ::  y0            !< y coordinate of PALM-4U domain projection centre, i.e. location of zwro distortion
    149     REAL(dp)              ::  z0            !< displacement of the coordinate origin above sea level [m]
    150     REAL(dp), ALLOCATABLE ::  x(:)          !< coordinates of cell centers in x direction [m]
    151     REAL(dp), ALLOCATABLE ::  y(:)          !< coordinates of cell centers in y direction [m]
    152     REAL(dp), POINTER     ::  z(:)          !< coordinates of cell centers in z direction [m]
    153     REAL(dp), ALLOCATABLE ::  h(:,:,:)      !< heights grid point for intermediate grids [m]
    154     REAL(dp), POINTER     ::  cosmo_h(:,:,:)!< pointer to appropriate COSMO level heights (scalar/w) [m]
    155     REAL(dp), POINTER     ::  hhl(:,:,:)    !< heights of half layers (cell faces) above sea level in COSMO-DE, read in from
    156     REAL(dp), POINTER     ::  hfl(:,:,:)    !< heights of full layers (cell centres) above sea level in COSMO-DE, computed as arithmetic average of hhl
    157     REAL(dp), POINTER     ::  depths(:)     !< depths of output soil layers, equal the depths of the source model (e.g. COSMO-DE)
    158     REAL(dp), ALLOCATABLE ::  xu(:)         !< coordinates of cell faces in x direction [m]
    159     REAL(dp), ALLOCATABLE ::  yv(:)         !< coordinates of cell faces in y direction [m]
    160     REAL(dp), POINTER     ::  zw(:)         !< coordinates of cell faces in z direction [m]
    161     REAL(dp), ALLOCATABLE ::  lat(:)        !< rotated-pole latitudes of scalars (cell centers) of the COSMO-DE grid [rad]
    162     REAL(dp), ALLOCATABLE ::  lon(:)        !< rotated-pole longitudes of scalars (cell centres) of the COSMO-DE grid [rad]
    163     REAL(dp), ALLOCATABLE ::  latv(:)       !< rotated-pole latitudes of v winds (face centres in latitudal/y direction) [rad]
    164     REAL(dp), ALLOCATABLE ::  lonu(:)       !< rotated-pole latitudes of u winds (face centres in longitudal/x direction) [rad]
    165     REAL(dp), ALLOCATABLE ::  clat(:,:)     !< latitudes of PALM-4U cell centres in COSMO-DE's rotated-pole grid [rad]
    166     REAL(dp), ALLOCATABLE ::  clon(:,:)     !< longitudes of PALM-4U scalars (cell centres) in COSMO-DE's rotated-pole grid [rad]
    167     REAL(dp), ALLOCATABLE ::  clatu(:,:)    !< latitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
    168     REAL(dp), ALLOCATABLE ::  clonu(:,:)    !< longitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
    169     REAL(dp), ALLOCATABLE ::  clatv(:,:)    !< latitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
    170     REAL(dp), ALLOCATABLE ::  clonv(:,:)    !< longitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
    171     REAL(dp), ALLOCATABLE ::  w_horiz(:,:,:)   !< weights for bilinear horizontal interpolation
    172     REAL(dp), ALLOCATABLE ::  w_verti(:,:,:,:) !< weights for linear vertical interpolation
    173     REAL(dp), ALLOCATABLE ::  w(:,:,:)      !< vertical interpolation weights, w(<source_column>, <PALM k level>, <neighbour index>) [-]
     151    REAL(wp)              ::  lx            !< domain length in the first dimension [m]
     152    REAL(wp)              ::  ly            !< domain length in the second dimension [m]
     153    REAL(wp)              ::  x0            !< x coordinate of PALM-4U domain projection centre, i.e. location of zero distortion
     154    REAL(wp)              ::  y0            !< y coordinate of PALM-4U domain projection centre, i.e. location of zwro distortion
     155    REAL(wp)              ::  z0            !< displacement of the coordinate origin above sea level [m]
     156    REAL(wp), ALLOCATABLE ::  x(:)          !< coordinates of cell centers in x direction [m]
     157    REAL(wp), ALLOCATABLE ::  y(:)          !< coordinates of cell centers in y direction [m]
     158    REAL(wp), POINTER     ::  z(:)          !< coordinates of cell centers in z direction [m]
     159    REAL(wp), ALLOCATABLE ::  h(:,:,:)      !< heights grid point for intermediate grids [m]
     160    REAL(wp), POINTER     ::  cosmo_h(:,:,:)!< pointer to appropriate COSMO level heights (scalar/w) [m]
     161    REAL(wp), POINTER     ::  hhl(:,:,:)    !< heights of half layers (cell faces) above sea level in COSMO-DE, read in from
     162    REAL(wp), POINTER     ::  hfl(:,:,:)    !< heights of full layers (cell centres) above sea level in COSMO-DE, computed as arithmetic average of hhl
     163    REAL(wp), POINTER     ::  depths(:)     !< depths of output soil layers, equal the depths of the source model (e.g. COSMO-DE)
     164    REAL(wp), ALLOCATABLE ::  xu(:)         !< coordinates of cell faces in x direction [m]
     165    REAL(wp), ALLOCATABLE ::  yv(:)         !< coordinates of cell faces in y direction [m]
     166    REAL(wp), POINTER     ::  zw(:)         !< coordinates of cell faces in z direction [m]
     167    REAL(wp), ALLOCATABLE ::  lat(:)        !< rotated-pole latitudes of scalars (cell centers) of the COSMO-DE grid [rad]
     168    REAL(wp), ALLOCATABLE ::  lon(:)        !< rotated-pole longitudes of scalars (cell centres) of the COSMO-DE grid [rad]
     169    REAL(wp), ALLOCATABLE ::  latv(:)       !< rotated-pole latitudes of v winds (face centres in latitudal/y direction) [rad]
     170    REAL(wp), ALLOCATABLE ::  lonu(:)       !< rotated-pole latitudes of u winds (face centres in longitudal/x direction) [rad]
     171    REAL(wp), ALLOCATABLE ::  clat(:,:)     !< latitudes of PALM-4U cell centres in COSMO-DE's rotated-pole grid [rad]
     172    REAL(wp), ALLOCATABLE ::  clon(:,:)     !< longitudes of PALM-4U scalars (cell centres) in COSMO-DE's rotated-pole grid [rad]
     173    REAL(wp), ALLOCATABLE ::  clatu(:,:)    !< latitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
     174    REAL(wp), ALLOCATABLE ::  clonu(:,:)    !< longitudes of PALM-4U u winds (cell faces in u direction) in COSMO-DE's rotated-pole grid [rad]
     175    REAL(wp), ALLOCATABLE ::  clatv(:,:)    !< latitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
     176    REAL(wp), ALLOCATABLE ::  clonv(:,:)    !< longitudes of PALM-4U v winds (cell faces in v direction) in COSMO-DE's rotated-pole grid [rad]
     177    REAL(wp), ALLOCATABLE ::  w_horiz(:,:,:)   !< weights for bilinear horizontal interpolation
     178    REAL(wp), ALLOCATABLE ::  w_verti(:,:,:,:) !< weights for linear vertical interpolation
     179    REAL(wp), ALLOCATABLE ::  w(:,:,:)      !< vertical interpolation weights, w(<source_column>, <PALM k level>, <neighbour index>) [-]
    174180 END TYPE grid_definition
    175181
     
    190196    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).
    191197    INTEGER               ::  dimvarids_soil(3) !< NetCDF IDs of the grid coordinates for soil points x, y, depth
    192     REAL(dp), POINTER     ::  time(:)           !< vector of output time steps
     198    REAL(wp), POINTER     ::  time(:)           !< vector of output time steps
    193199 END TYPE nc_file
    194200
     
    199205!> Metadata container for netCDF variables
    200206!------------------------------------------------------------------------------!
     207#if defined ( __netcdf )
    201208 TYPE nc_var
    202209    INTEGER                               ::  varid     !< NetCDF ID of the variable
     
    247254    LOGICAL                          ::  is_preprocessed = .FALSE. !< Inifor flag indicating whether the I/O group has been preprocessed
    248255 END TYPE io_group
    249 
     256#endif
    250257
    251258!------------------------------------------------------------------------------!
     
    257264!------------------------------------------------------------------------------!
    258265 TYPE container
    259    REAL(dp), ALLOCATABLE ::  array(:,:,:)               !< generic data array
     266   REAL(wp), ALLOCATABLE ::  array(:,:,:)               !< generic data array
    260267   LOGICAL               ::  is_preprocessed = .FALSE.  !< flag indicating whether input array has been preprocessed
    261268 END TYPE container
    262269
    263270 END MODULE inifor_types
    264 #endif
    265 
Note: See TracChangeset for help on using the changeset viewer.