Ignore:
Timestamp:
Nov 22, 2018 4:01:22 PM (6 years ago)
Author:
eckhard
Message:

inifor: Updated documentation

File:
1 edited

Legend:

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

    r3447 r3557  
    2626! -----------------
    2727! $Id$
     28! Updated documentation
     29!
     30!
     31! 3447 2018-10-29 15:52:54Z eckhard
    2832! Renamed source files for compatibilty with PALM build system
    2933!
     
    5155! Authors:
    5256! --------
    53 ! @author Eckhard Kadasch
     57!> @author Eckhard Kadasch (Deutscher Wetterdienst, Offenbach)
    5458!
    5559! Description:
     
    6670 IMPLICIT NONE
    6771
     72!------------------------------------------------------------------------------!
     73! Description:
     74! ------------
     75!> Contaner for the INIFOR command-line configuration
     76!------------------------------------------------------------------------------!
    6877 TYPE inifor_config
    6978    CHARACTER(LEN=DATE)  ::  start_date           !< String of the FORMAT YYYYMMDDHH indicating the start of the intended PALM-4U simulation
     
    8291    CHARACTER(LEN=SNAME) ::  soilmoisture_prefix  !< Prefix of input files for soil moisture spin-up, e.g 'laf' for COSMO-DE analyses
    8392
    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    CHARACTER(LEN=SNAME) ::  averaging_mode       !< destinguishes between level-based and heigh-based averaging
     94    CHARACTER(LEN=SNAME) ::  bc_mode              !< destinguishes realistic and idealistic forcing
     95    CHARACTER(LEN=SNAME) ::  ic_mode              !< destinguishes volume and profile initialization
     96    CHARACTER(LEN=SNAME) ::  rotation_method      !< selects method for velocity rotation
     97
     98    REAL(dp)             ::  p0                   !< manually specified surface pressure [Pa]
     99    REAL(dp)             ::  ug                   !< manually spefied geostrophic wind component in x direction [m/s]
     100    REAL(dp)             ::  vg                   !< manually spefied geostrophic wind component in y direction [m/s]
     101    REAL(dp)             ::  z0                   !< elevation of the PALM-4U domain above sea level [m]
    93102    REAL(dp)             ::  averaging_angle      !< latitudal and longitudal width of averaging regions [deg]
    94103   
    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  !<
     104    LOGICAL              ::  debug                       !< indicates whether --debug option was given
     105    LOGICAL              ::  p0_is_set                   !< indicates whether p0 was set manually
     106    LOGICAL              ::  ug_is_set                   !< indicates whether ug was set manually
     107    LOGICAL              ::  vg_is_set                   !< indicates whether vg was set manually
     108    LOGICAL              ::  flow_prefix_is_set          !<  indicates whether the flow prefix was set manually
     109    LOGICAL              ::  input_prefix_is_set         !<  indicates whether the input prefix was set manually
     110    LOGICAL              ::  radiation_prefix_is_set     !<  indicates whether the radiation prefix was set manually
     111    LOGICAL              ::  soil_prefix_is_set          !<  indicates whether the soil prefix was set manually
     112    LOGICAL              ::  soilmoisture_prefix_is_set  !<  indicates whether the soilmoisture prefix was set manually
    105113 END TYPE inifor_config
    106114
     115
     116!------------------------------------------------------------------------------!
     117! Description:
     118! ------------
     119!> Container for grid data, in partucular coordinates, interpolation neighbours
     120!> and weights
     121!------------------------------------------------------------------------------!
    107122 TYPE grid_definition
    108123    CHARACTER(LEN=SNAME)  ::  name(3)       !< names of the grid dimensions, e.g. (/'x', 'y', 'z'/) or (/'latitude', 'longitude', 'height'/)
     
    152167
    153168
     169!------------------------------------------------------------------------------!
     170! Description:
     171! ------------
     172!> Container for name and dimensions of the netCDF output file
     173!------------------------------------------------------------------------------!
    154174 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
     175    CHARACTER(LEN=PATH)   ::  name              !< file name
     176    INTEGER               ::  dimid_time        !< NetCDF IDs of the time dimension
     177    INTEGER               ::  dimids_scl(3)     !< NetCDF IDs of the grid dimensions for scalar points x, y, z
     178    INTEGER               ::  dimids_vel(3)     !< NetCDF IDs of the grid dimensions for velocity points xu, yu, zu
     179    INTEGER               ::  dimids_soil(3)    !< NetCDF IDs of the grid dimensions for soil points x, y, depth
     180    INTEGER               ::  dimvarid_time     !< NetCDF IDs of the time variable
     181    INTEGER               ::  dimvarids_scl(3)  !< NetCDF IDs of the grid coordinates of scalars x, y, z
     182    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).
     183    INTEGER               ::  dimvarids_soil(3) !< NetCDF IDs of the grid coordinates for soil points x, y, depth
     184    REAL(dp), POINTER     ::  time(:)           !< vector of output time steps
    165185 END TYPE nc_file
    166186
    167187
     188!------------------------------------------------------------------------------!
     189! Description:
     190! ------------
     191!> Metadata container for netCDF variables
     192!------------------------------------------------------------------------------!
    168193 TYPE nc_var
    169194    INTEGER                               ::  varid     !< NetCDF ID of the variable
     
    193218
    194219
    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.
     220!------------------------------------------------------------------------------!
     221! Description:
     222! ------------
     223!> Input/Output group, groups together nc_var-type output variabels that share
     224!> input variables as well as lists of the netCDF files they are stored in.
     225!> For instance, all boundary surfaces and initialization fields of the
     226!> potential temperature are base on the input netCDF variables T and P.
     227!------------------------------------------------------------------------------!
     228 TYPE io_group
    196229    INTEGER                          ::  nt             !< maximum number of output time steps across all output variables
    197230    INTEGER                          ::  nv             !< number of netCDF output variables
     
    208241
    209242
     243!------------------------------------------------------------------------------!
     244! Description:
     245! ------------
     246!> Container for input data arrays. read_input_variables() allocates a
     247!> one-dimensional array of containers, to accomodate all inputs of the given
     248!> IO group in one variable.
     249!------------------------------------------------------------------------------!
    210250 TYPE container
    211    REAL(dp), ALLOCATABLE ::  array(:,:,:)
    212    LOGICAL               ::  is_preprocessed = .FALSE.
     251   REAL(dp), ALLOCATABLE ::  array(:,:,:)               !< generic data array
     252   LOGICAL               ::  is_preprocessed = .FALSE.  !< flag indicating whether input array has been preprocessed
    213253 END TYPE container
    214254
Note: See TracChangeset for help on using the changeset viewer.