Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
     22! kind-parameters added to all INTEGER and REAL declaration statements,
     23! kinds are defined in new module kinds,
     24! old module precision_kind is removed,
     25! revision history before 2012 removed,
     26! comment fields (!:) to be used for variable explanations added to
     27! all variable declaration statements
    2228!
    2329!
     
    3541! Bugfix: disable max_pr_user check during prior namelist file check
    3642!
    37 ! 553 2010-09-01 14:09:06Z weinreis
    38 ! data_output_mask_user_* replaced by array data_output_masks_user
    39 !
    40 ! 410 2009-12-04 17:05:40Z letzel
    41 ! masked data output
    42 !
    43 ! 274 2009-03-26 15:11:21Z heinze
    44 ! Output of messages replaced by message handling routine.
    45 ! topography_grid_convention moved to inipar
    46 !
    4743! 217 2008-12-09 18:00:48Z letzel
    4844! +topography_grid_convention
     
    5551
    5652    USE control_parameters
     53   
     54    USE kinds
     55   
    5756    USE pegrid
     57   
    5858    USE statistics
     59   
    5960    USE user
    6061
    6162    IMPLICIT NONE
    6263
    63     CHARACTER (LEN=80) ::  zeile
     64    CHARACTER (LEN=80) ::  zeile   !:
    6465
    65     INTEGER ::  i, j, max_pr_user_tmp
     66    INTEGER(iwp) ::  i                 !:
     67    INTEGER(iwp) ::  j                 !:
     68    INTEGER(iwp) ::  max_pr_user_tmp   !:
    6669
    6770
    68     NAMELIST /userpar/  data_output_pr_user, data_output_user, region,  &
     71    NAMELIST /userpar/  data_output_pr_user, data_output_user, region,         &
    6972                        data_output_masks_user
    7073
     
    110113    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
    111114       IF ( max_pr_user /= max_pr_user_tmp )  THEN
    112           WRITE( message_string, * ) 'the number of user-defined profiles ', &
    113                      'given in &data_output_pr (', max_pr_user_tmp, ') doe', &
    114                      'snot match the one ',                                  &
    115                      '&found in the restart file (', max_pr_user,            &
     115          WRITE( message_string, * ) 'the number of user-defined profiles ',   &
     116                     'given in &data_output_pr (', max_pr_user_tmp, ') doe',   &
     117                     'snot match the one ',                                    &
     118                     '&found in the restart file (', max_pr_user,              &
    116119                                     ')'
    117120          CALL message( 'user_parin', 'UI0009', 1, 2, 0, 6, 0 )
Note: See TracChangeset for help on using the changeset viewer.