Ignore:
Timestamp:
Nov 22, 2018 10:28:35 AM (6 years ago)
Author:
suehring
Message:

further variables documented

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r3543 r3552  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! variables documented and unused variables removed
    2323!
    2424! Former revisions:
     
    306306       INTEGER(iwp) ::  tind_p !< time index for following time in mesoscale-offline nesting
    307307
    308        LOGICAL      ::  init         = .FALSE.
    309        LOGICAL      ::  from_file    = .FALSE.
     308       LOGICAL      ::  init         = .FALSE. !< flag indicating that offline nesting is already initialized
    310309
    311310       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surface_pressure !< time dependent surface pressure
     
    11711170       INTEGER(iwp) ::  val      !< value of the attribute
    11721171       
    1173        LOGICAL ::  global                 !< flag indicating a global or a variable's attribute
     1172       LOGICAL ::  global        !< flag indicating a global or a variable's attribute
    11741173
    11751174#if defined ( __netcdf )
     
    31353134       IMPLICIT NONE
    31363135
    3137        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names
     3136       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names !< string containing all variables on file
    31383137     
    31393138       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
     
    32813280       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
    32823281       INTEGER(iwp) ::  t          !< running index time dimension
    3283 
    3284        nest_offl%from_file = MERGE( .TRUE., .FALSE., input_pids_dynamic )
    32853282!
    32863283!--    Skip input if no forcing from larger-scale models is applied.
     
    50305027       INTEGER(iwp)                ::  id_var           !< dimension id
    50315028
    5032        REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
     5029       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var    !< variable to be read
    50335030#if defined( __netcdf )
    50345031
     
    53955392                                                         !< to its reverse memory access
    53965393
    5397        REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var  !< variable to be read
     5394       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var !< variable to be read
    53985395#if defined( __netcdf )
    53995396
     
    58745871       IMPLICIT NONE
    58755872
    5876        CHARACTER(LEN=6) ::  message_identifier
    5877        CHARACTER(LEN=*) ::  routine_name
    5878        CHARACTER(LEN=*), OPTIONAL ::  name
     5873       CHARACTER(LEN=6) ::  message_identifier !< string for the error number
     5874       CHARACTER(LEN=*) ::  routine_name       !< routine name where the error happened
     5875       CHARACTER(LEN=*), OPTIONAL ::  name     !< name of variable where reading failed
    58795876
    58805877       INTEGER(iwp) ::  errno
Note: See TracChangeset for help on using the changeset viewer.