Changeset 564


Ignore:
Timestamp:
Sep 30, 2010 1:18:59 PM (14 years ago)
Author:
helmke
Message:

several changes for an unlimited output of mask data and message IDs changed

Location:
palm/trunk/SOURCE
Files:
7 edited

Legend:

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

    r520 r564  
    44! Current revisions:
    55! -----------------
    6 !
     6! start number of mask output files changed to 201, netcdf message identifiers
     7! of masked output changed
    78!
    89! Former revisions:
     
    139140          ENDIF
    140141
    141        CASE ( 101:103, 106, 111:113, 116, 121:160 )
     142       CASE ( 101:103, 106, 111:113, 116, 201:200+2*max_masks )
    142143
    143144          IF ( netcdf_data_format < 3 )  THEN
     
    13661367          ENDIF
    13671368
    1368        CASE ( 121:160 )
     1369       CASE ( 201:200+2*max_masks )
    13691370!
    13701371!--       Set filename depending on unit number
    1371           IF ( file_id <= 140 )  THEN
    1372              mid = file_id - 120
     1372          IF ( file_id <= 200+max_masks )  THEN
     1373             mid = file_id - 200
    13731374             WRITE ( mask_char,'(I2.2)')  mid
    13741375             filename = 'DATA_MASK_' // mask_char // '_NETCDF' // coupling_char
    13751376             av = 0
    13761377          ELSE
    1377              mid = file_id - 140
     1378             mid = file_id - (200+max_masks)
    13781379             WRITE ( mask_char,'(I2.2)')  mid
    13791380             filename = 'DATA_MASK_' // mask_char // '_AV_NETCDF' // &
     
    13961397             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set_mask(mid,av) )
    13971398#endif
    1398              CALL handle_netcdf_error( 'check_open', 9998 )
     1399             CALL handle_netcdf_error( 'check_open', 456 )
    13991400!
    14001401!--          Read header information and set all ids. If there is a mismatch
     
    14071408             IF ( .NOT. netcdf_extend )  THEN
    14081409                nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
    1409                 CALL handle_netcdf_error( 'check_open', 9998 )
     1410                CALL handle_netcdf_error( 'check_open', 457 )
    14101411                CALL local_system('rm ' // TRIM( filename ) )
    14111412             ENDIF
     
    14501451             ENDIF
    14511452
    1452              CALL handle_netcdf_error( 'check_open', 9998 )
     1453             CALL handle_netcdf_error( 'check_open', 458 )
    14531454!
    14541455!--          Define the header
     
    14601461#else
    14611462
    1462        CASE ( 101:109, 111:113, 116, 121:160 )
     1463       CASE ( 101:109, 111:113, 116, 201:200+2*max_masks )
    14631464
    14641465!
  • palm/trunk/SOURCE/check_parameters.f90

    r554 r564  
    44! Current revisions:
    55! -----------------
    6 !
     6! palm message identifiers of masked output changed, 20 replaced by max_masks
    77!
    88! Former revisions:
     
    15051505       IF ( dt_do3d           == 9999999.9 )  dt_do3d           = dt_data_output
    15061506       IF ( dt_data_output_av == 9999999.9 )  dt_data_output_av = dt_data_output
    1507        DO  mid = 1, 20
     1507       DO  mid = 1, max_masks
    15081508          IF ( dt_domask(mid) == 9999999.9 )  dt_domask(mid)    = dt_data_output
    15091509       ENDDO
     
    15261526    IF ( skip_time_data_output_av == 9999999.9 ) &
    15271527                                skip_time_data_output_av = skip_time_data_output
    1528     DO  mid = 1, 20
     1528    DO  mid = 1, max_masks
    15291529       IF ( skip_time_domask(mid) == 9999999.9 ) &
    15301530                                skip_time_domask(mid)    = skip_time_data_output
     
    26922692       WRITE( message_string, * )  'illegal value: masks must be >= 0 and ', &
    26932693            '<= ', max_masks, ' (=max_masks)'
    2694        CALL message( 'check_parameters', 'PA9998', 1, 2, 0, 6, 0 )
     2694       CALL message( 'check_parameters', 'PA0325', 1, 2, 0, 6, 0 )
    26952695    ENDIF
    26962696    IF ( masks > 0 )  THEN
     
    27022702               'illegal value: mask_scale_x, mask_scale_y and mask_scale_z', &
    27032703               'must be > 0.0'
    2704           CALL message( 'check_parameters', 'PA9998', 1, 2, 0, 6, 0 )
     2704          CALL message( 'check_parameters', 'PA0326', 1, 2, 0, 6, 0 )
    27052705       ENDIF
    27062706!
  • palm/trunk/SOURCE/close_file.f90

    r494 r564  
    44! Current revisions:
    55! -----------------
    6 !
     6! start number of mask output files changed to 201, netcdf message identifiers
     7! of masked output changed
    78!
    89! Former revisions:
     
    100101!
    101102!-- Close all open unit numbers
    102     DO  fid = 1, 160
     103    DO  fid = 1, 200+2*max_masks
    103104
    104105       IF ( openfile(fid)%opened .OR. openfile(fid)%opened_before )  THEN
     
    509510                ENDIF
    510511
    511              CASE ( 121:160 )
     512             CASE ( 201:200+2*max_masks )
    512513             
    513514                IF ( netcdf_output  .AND.  &
     
    515516!
    516517!--                decompose fid into mid and av
    517                    IF ( fid <= 140 )  THEN
    518                       mid = fid - 120
     518                   IF ( fid <= 200+max_masks )  THEN
     519                      mid = fid - 200
    519520                      av = 0
    520521                   ELSE
    521                       mid = fid - 140
     522                      mid = fid - (200+max_masks)
    522523                      av = 1
    523524                   ENDIF
    524525                   nc_stat = NF90_CLOSE( id_set_mask(mid,av) )
    525                    CALL handle_netcdf_error( 'close_file', 9998 )
     526                   CALL handle_netcdf_error( 'close_file', 459 )
    526527               
    527528                ENDIF
  • palm/trunk/SOURCE/data_output_mask.f90

    r494 r564  
    44! Current revisions:
    55! -----------------
    6 !
     6! start number of mask output files changed to 201, netcdf message identifiers
     7! of masked output changed, palm message identifiers of masked output changed
    78!
    89! Former revisions:
     
    6061    IF ( netcdf_output  .AND.  ( myid == 0  .OR.  netcdf_data_format > 2 ) ) &
    6162    THEN
    62        CALL check_open( 120+mid+av*max_masks )
     63       CALL check_open( 200+mid+av*max_masks )
    6364    ENDIF
    6465
     
    8283                               start = (/ domask_time_count(mid,av) /),       &
    8384                               count = (/ 1 /) )
    84        CALL handle_netcdf_error( 'data_output_mask', 9998 )
     85       CALL handle_netcdf_error( 'data_output_mask', 460 )
    8586    ENDIF
    8687
     
    300301                WRITE ( message_string, * ) 'no output available for: ', &
    301302                                            TRIM( domask(mid,av,if) )
    302                 CALL message( 'data_output_mask', 'PA9998', 0, 0, 0, 6, 0 )
     303                CALL message( 'data_output_mask', 'PA0327', 0, 0, 0, 6, 0 )
    303304             ENDIF
    304305
     
    339340               count = (/ mask_size_l(mid,1), mask_size_l(mid,2),  &
    340341                          mask_size_l(mid,3), 1 /) )
    341           CALL handle_netcdf_error( 'data_output_mask', 9998 )
     342          CALL handle_netcdf_error( 'data_output_mask', 461 )
    342343       ELSE
    343344#endif
     
    386387                  count = (/ mask_size(mid,1), mask_size(mid,2), &
    387388                             mask_size(mid,3), 1 /) )
    388              CALL handle_netcdf_error( 'data_output_mask', 9998 )
     389             CALL handle_netcdf_error( 'data_output_mask', 462 )
    389390
    390391          ELSE
     
    431432            count = (/ mask_size_l(mid,1), mask_size_l(mid,2), &
    432433                       mask_size_l(mid,3), 1 /) )
    433        CALL handle_netcdf_error( 'data_output_mask', 9998 )
     434       CALL handle_netcdf_error( 'data_output_mask', 463 )
    434435#endif
    435436
  • palm/trunk/SOURCE/init_masks.f90

    r558 r564  
    44! Current revisions:
    55! -----------------
    6 !
     6! assignment of mask_xyz_loop added, palm message identifiers of masked output
     7! changed
    78!
    89! Former revisions:
     
    6465                        '3 (NetCDF 4) and 4 (NetCDF 4 Classic model)'//  &
    6566                        '&are currently not supported (not yet tested).'
    66        CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     67       CALL message( 'init_masks', 'PA0328', 1, 2, 0, 6, 0 )
    6768    ENDIF
    6869
     
    7071!-- Store data output parameters for masked data output in few shared arrays
    7172    DO mid = 1, masks
     73   
    7274       do_mask     (mid,:) = data_output_masks(mid,:)
    7375       do_mask_user(mid,:) = data_output_masks_user(mid,:)
     
    7577       mask      (mid,2,:) = mask_y(mid,:)
    7678       mask      (mid,3,:) = mask_z(mid,:)
    77        mask_loop (mid,1,:) = mask_x_loop(mid,:)
    78        mask_loop (mid,2,:) = mask_y_loop(mid,:)
    79        mask_loop (mid,3,:) = mask_z_loop(mid,:)
     79       
     80       IF ( mask_x_loop(mid,1) == -1.0 .AND. mask_x_loop(mid,2) == -1.0  &
     81            .AND. mask_x_loop(mid,3) == -1.0 ) THEN
     82          mask_loop(mid,1,1:2) = -1.0
     83          mask_loop(mid,1,3) = 0.0
     84       ELSE
     85          mask_loop(mid,1,:) = mask_x_loop(mid,:)
     86       ENDIF
     87       IF ( mask_y_loop(mid,1) == -1.0 .AND. mask_y_loop(mid,2) == -1.0  &
     88            .AND. mask_y_loop(mid,3) == -1.0 ) THEN
     89          mask_loop(mid,2,1:2) = -1.0
     90          mask_loop(mid,2,3) = 0.0
     91       ELSE
     92          mask_loop(mid,2,:) = mask_y_loop(mid,:)
     93       ENDIF
     94       IF ( mask_z_loop(mid,1) == -1.0 .AND. mask_z_loop(mid,2) == -1.0  &
     95            .AND. mask_z_loop(mid,3) == -1.0 ) THEN
     96          mask_loop(mid,3,1:2) = -1.0
     97          mask_loop(mid,3,3) = 0.0
     98       ELSE
     99          mask_loop(mid,3,:) = mask_z_loop(mid,:)
     100       ENDIF
     101       
    80102    ENDDO
    81103   
     
    107129                     'given by data_output_mask and data_output_mask_user ', &
    108130                     'exceeds the limit of 100'
    109                 CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     131                CALL message( 'init_masks', 'PA0329', 1, 2, 0, 6, 0 )
    110132             ENDIF
    111133             do_mask(mid,i) = do_mask_user(mid,j)
     
    138160                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    139161                        '" requires constant_diffusion = .FALSE.'
    140                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     162                   CALL message( 'init_masks', 'PA0103', 1, 2, 0, 6, 0 )
    141163                ENDIF
    142164                unit = 'm2/s2'
     
    147169                        '" requires a "particles_par"-NAMELIST in the ', &
    148170                        'parameter file (PARIN)'
    149                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     171                   CALL message( 'init_masks', 'PA0104', 1, 2, 0, 6, 0 )
    150172                ENDIF
    151173                IF ( TRIM( var ) == 'pc' )  unit = 'number'
     
    156178                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    157179                        '" requires humidity = .TRUE.'
    158                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     180                   CALL message( 'init_masks', 'PA0105', 1, 2, 0, 6, 0 )
    159181                ENDIF
    160182                IF ( TRIM( var ) == 'q'   )  unit = 'kg/kg'
     
    166188                        '" requires cloud_physics = .TRUE. or cloud_droplets', &
    167189                        ' = .TRUE.'
    168                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     190                   CALL message( 'init_masks', 'PA0108', 1, 2, 0, 6, 0 )
    169191                ENDIF
    170192                unit = 'kg/kg'
     
    174196                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    175197                        '" requires cloud_droplets = .TRUE.'
    176                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     198                   CALL message( 'init_masks', 'PA0107', 1, 2, 0, 6, 0 )
    177199                ENDIF
    178200                IF ( TRIM( var ) == 'ql_c'  )  unit = 'kg/kg'
     
    184206                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    185207                        '" requires cloud_physics = .TRUE.'
    186                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     208                   CALL message( 'init_masks', 'PA0108', 1, 2, 0, 6, 0 )
    187209                ENDIF
    188210                unit = 'kg/kg'
     
    192214                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    193215                        '" requires ocean = .TRUE.'
    194                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     216                   CALL message( 'init_masks', 'PA0109', 1, 2, 0, 6, 0 )
    195217                ENDIF
    196218                unit = 'kg/m3'
     
    200222                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    201223                        '" requires passive_scalar = .TRUE.'
    202                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     224                   CALL message( 'init_masks', 'PA0110', 1, 2, 0, 6, 0 )
    203225                ENDIF
    204226                unit = 'conc'
     
    208230                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    209231                        '" requires ocean = .TRUE.'
    210                    CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     232                   CALL message( 'init_masks', 'PA0109', 1, 2, 0, 6, 0 )
    211233                ENDIF
    212234                unit = 'psu'
     
    216238                     'output: "', TRIM( var ), '" is only allowed', &
    217239                     'for horizontal cross section'
    218                 CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     240                CALL message( 'init_masks', 'PA0111', 1, 2, 0, 6, 0 )
    219241!                IF ( TRIM( var ) == 'lwp*'  .AND.  .NOT. cloud_physics )  THEN
    220242!                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    221243!                         '" requires cloud_physics = .TRUE.'
    222 !                   CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     244!                   CALL message( 'init_masks', 'PA0108', 1, 2, 0, 6, 0 )
    223245!                ENDIF
    224246!                IF ( TRIM( var ) == 'pra*'  .AND.  .NOT. precipitation )  THEN
    225247!                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    226248!                         '" requires precipitation = .TRUE.'
    227 !                   CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     249!                   CALL message( 'init_masks', 'PA0112', 1, 2, 0, 6, 0 )
    228250!                ENDIF
    229251!                IF ( TRIM( var ) == 'pra*'  .AND.  j == 1 )  THEN
     
    231253!                         ' precipitation amount "', TRIM( var ),         &
    232254!                         '" not possible'
    233 !                   CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     255!                   CALL message( 'init_masks', 'PA0113', 1, 2, 0, 6, 0 )
    234256!                ENDIF
    235257!                IF ( TRIM( var ) == 'prr*'  .AND.  .NOT. precipitation )  THEN
    236258!                   WRITE ( message_string, * ) 'output of "', TRIM( var ), &
    237259!                         '" requires precipitation = .TRUE.'
    238 !                   CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     260!                   CALL message( 'init_masks', 'PA0112', 1, 2, 0, 6, 0 )
    239261!                ENDIF
    240262!
     
    262284                           'output or data_output_user: "', &
    263285                           TRIM( do_mask(mid,i) ), '"'
    264                       CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     286                      CALL message( 'init_masks', 'PA0114', 1, 2, 0, 6, 0 )
    265287                   ELSE
    266288                      WRITE ( message_string, * ) 'illegal value for data_',&
    267289                           'output: "', TRIM( do_mask(mid,i) ), '"'
    268                       CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     290                      CALL message( 'init_masks', 'PA0330', 1, 2, 0, 6, 0 )
    269291                   ENDIF
    270292                ENDIF
     
    451473                     m,' in mask ',mid,' along dimension ',dim,  &
    452474                     ' exceeds ',nxyz_string,' = ',nxyz
    453                 CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     475                CALL message( 'init_masks', 'PA0331', 1, 2, 0, 6, 0 )
    454476             ENDIF
    455477             IF ( m >= lb .AND. m <= ub )  THEN
     
    490512                     nxyz_string,'*',dxyz_string,'/mask_scale(',dim,')=', &
    491513                     nxyz*dxyz/mask_scale(dim)
    492                 CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     514                CALL message( 'init_masks', 'PA0332', 1, 2, 0, 6, 0 )
    493515             ENDIF
    494516             loop_begin  = NINT( mask_loop(mid,dim,1) * mask_scale(dim) * ddxyz )
     
    507529                     mask_loop(mid,dim,2),'&exceed zw(nz)/mask_scale(',dim, &
    508530                     ')=',zw(nz)/mask_scale(dim)
    509                 CALL message( 'init_masks', 'PA9998', 1, 2, 0, 6, 0 )
     531                CALL message( 'init_masks', 'PA0333', 1, 2, 0, 6, 0 )
    510532             ENDIF
    511533             ind_array =  &
     
    530552                     'match the desired heights&within the stretching ', &
    531553                     'region. Recommendation: use mask instead of mask_loop.'
    532                 CALL message( 'init_masks', 'PA9998', 0, 1, 0, 6, 0 )
     554                CALL message( 'init_masks', 'PA0334', 0, 1, 0, 6, 0 )
    533555             ENDIF
    534556
  • palm/trunk/SOURCE/modules.f90

    r559 r564  
    55! Current revisions:
    66! -----------------
    7 !
     7! nc_precision and netcdf_precision dimension changed to 11, all default
     8! values of mask_xyz_loop changed to -1.0, dimension of openfile changed to
     9! 200+2*max_masks, max_masks changed to 50
    810!
    911! Former revisions:
     
    303305       LOGICAL ::  opened, opened_before
    304306    END TYPE file_status
    305 
    306     TYPE(file_status), DIMENSION(200) :: openfile = file_status(.FALSE.,.FALSE.)
    307 
    308 
    309     INTEGER, PARAMETER :: mask_xyz_dimension = 100, max_masks = 20
     307   
     308    INTEGER, PARAMETER :: mask_xyz_dimension = 100, max_masks = 50
     309
     310    TYPE(file_status), DIMENSION(200+2*max_masks) ::                &
     311                             openfile = file_status(.FALSE.,.FALSE.)
    310312
    311313    CHARACTER (LEN=1)    ::  cycle_mg = 'w', timestep_reason = ' '
     
    354356    CHARACTER (LEN=10), DIMENSION(300) ::  data_output_pr = ' '
    355357    CHARACTER (LEN=10), DIMENSION(200) ::  data_output_pr_user = ' '
    356     CHARACTER (LEN=20), DIMENSION(50)  ::  netcdf_precision = ' '
     358    CHARACTER (LEN=20), DIMENSION(11)  ::  netcdf_precision = ' '
    357359
    358360    CHARACTER (LEN=10), DIMENSION(max_masks,0:1,100) ::  domask = ' '
     
    549551    REAL, DIMENSION(:), ALLOCATABLE ::  dp_smooth_factor
    550552
    551     REAL, DIMENSION(max_masks,mask_xyz_dimension) ::       &
     553    REAL, DIMENSION(max_masks,mask_xyz_dimension) :: &
    552554        mask_x = -1.0, mask_y = -1.0, mask_z = -1.0
    553     REAL, DIMENSION(max_masks,3) ::                        &
    554         mask_x_loop = (/ -1.0, -1.0, -1.0, -1.0, -1.0,     & 
    555                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    556                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    557                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    558                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    559                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    560                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    561                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    562                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    563                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    564                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    565                           0.0,  0.0,  0.0,  0.0,  0.0  /), &
    566        
    567         mask_y_loop = (/ -1.0, -1.0, -1.0, -1.0, -1.0,     & 
    568                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    569                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    570                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    571                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    572                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    573                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    574                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    575                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    576                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    577                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    578                           0.0,  0.0,  0.0,  0.0,  0.0  /), &
    579                            
    580         mask_z_loop = (/ -1.0, -1.0, -1.0, -1.0, -1.0,     & 
    581                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    582                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    583                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    584                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    585                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    586                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    587                          -1.0, -1.0, -1.0, -1.0, -1.0,     &
    588                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    589                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    590                           0.0,  0.0,  0.0,  0.0,  0.0,     &
    591                           0.0,  0.0,  0.0,  0.0,  0.0  /) 
     555    REAL, DIMENSION(max_masks,3) ::                  &
     556        mask_x_loop = -1.0, mask_y_loop = -1.0, mask_z_loop = -1.0
    592557   
    593558!
     
    1026991    INTEGER, DIMENSION(10)  ::  id_var_dospx, id_var_dospy
    1027992    INTEGER, DIMENSION(20)  ::  id_var_prt
    1028     INTEGER, DIMENSION(50)  ::  nc_precision
     993    INTEGER, DIMENSION(11)  ::  nc_precision
    1029994    INTEGER, DIMENSION(dopr_norm_num) ::  id_var_norm_dopr
    1030995
  • palm/trunk/SOURCE/netcdf.f90

    r520 r564  
    77! Current revisions:
    88! ------------------
    9 !
     9! nc_precision changed from 40 masks to 1 mask, start number of mask output
     10! files changed to 201, netcdf message identifiers of masked output changed
    1011!
    1112! Former revisions:
     
    176177                nc_precision(8) = j
    177178             CASE ( 'masks' )
    178                 nc_precision(11:50) = j
    179              CASE ( 'mask01' )
    180179                nc_precision(11) = j
    181              CASE ( 'mask02' )
    182                 nc_precision(12) = j
    183              CASE ( 'mask03' )
    184                 nc_precision(13) = j
    185              CASE ( 'mask04' )
    186                 nc_precision(14) = j
    187              CASE ( 'mask05' )
    188                 nc_precision(15) = j
    189              CASE ( 'mask06' )
    190                 nc_precision(16) = j
    191              CASE ( 'mask07' )
    192                 nc_precision(17) = j
    193              CASE ( 'mask08' )
    194                 nc_precision(18) = j
    195              CASE ( 'mask09' )
    196                 nc_precision(19) = j
    197              CASE ( 'mask10' )
    198                 nc_precision(20) = j
    199              CASE ( 'mask11' )
    200                 nc_precision(21) = j
    201              CASE ( 'mask12' )
    202                 nc_precision(22) = j
    203              CASE ( 'mask13' )
    204                 nc_precision(23) = j
    205              CASE ( 'mask14' )
    206                 nc_precision(24) = j
    207              CASE ( 'mask15' )
    208                 nc_precision(25) = j
    209              CASE ( 'mask16' )
    210                 nc_precision(26) = j
    211              CASE ( 'mask17' )
    212                 nc_precision(27) = j
    213              CASE ( 'mask18' )
    214                 nc_precision(28) = j
    215              CASE ( 'mask19' )
    216                 nc_precision(29) = j
    217              CASE ( 'mask20' )
    218                 nc_precision(30) = j
    219              CASE ( 'maskav01' )
    220                 nc_precision(31) = j
    221              CASE ( 'maskav02' )
    222                 nc_precision(32) = j
    223              CASE ( 'maskav03' )
    224                 nc_precision(33) = j
    225              CASE ( 'maskav04' )
    226                 nc_precision(34) = j
    227              CASE ( 'maskav05' )
    228                 nc_precision(35) = j
    229              CASE ( 'maskav06' )
    230                 nc_precision(36) = j
    231              CASE ( 'maskav07' )
    232                 nc_precision(37) = j
    233              CASE ( 'maskav08' )
    234                 nc_precision(38) = j
    235              CASE ( 'maskav09' )
    236                 nc_precision(39) = j
    237              CASE ( 'maskav10' )
    238                 nc_precision(40) = j
    239              CASE ( 'maskav11' )
    240                 nc_precision(41) = j
    241              CASE ( 'maskav12' )
    242                 nc_precision(42) = j
    243              CASE ( 'maskav13' )
    244                 nc_precision(43) = j
    245              CASE ( 'maskav14' )
    246                 nc_precision(44) = j
    247              CASE ( 'maskav15' )
    248                 nc_precision(45) = j
    249              CASE ( 'maskav16' )
    250                 nc_precision(46) = j
    251              CASE ( 'maskav17' )
    252                 nc_precision(47) = j
    253              CASE ( 'maskav18' )
    254                 nc_precision(48) = j
    255              CASE ( 'maskav19' )
    256                 nc_precision(49) = j
    257              CASE ( 'maskav20' )
    258                 nc_precision(50) = j
    259180             CASE ( 'all' )
    260181                nc_precision    = j
     
    297218!--       mid and av
    298219          file_id = av
    299           IF ( file_id <= 140 )  THEN
    300              mid = file_id - 120
     220          IF ( file_id <= 200+max_masks )  THEN
     221             mid = file_id - 200
    301222             av = 0
    302223          ELSE
    303              mid = file_id - 140
     224             mid = file_id - (200+max_masks)
    304225             av = 1
    305226          ENDIF
     
    309230          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, &
    310231               'Conventions', 'COARDS' )
    311           CALL handle_netcdf_error( 'netcdf', 9998 )
     232          CALL handle_netcdf_error( 'netcdf', 464 )
    312233
    313234          IF ( av == 0 )  THEN
     
    320241                                  TRIM( run_description_header ) //    &
    321242                                  TRIM( time_average_text ) )
    322           CALL handle_netcdf_error( 'netcdf', 9998 )
     243          CALL handle_netcdf_error( 'netcdf', 465 )
    323244          IF ( av == 1 )  THEN
    324245             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    325246             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, &
    326247                                     'time_avg', TRIM( time_average_text ) )
    327              CALL handle_netcdf_error( 'netcdf', 9998 )
     248             CALL handle_netcdf_error( 'netcdf', 466 )
    328249          ENDIF
    329250
     
    332253          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'time', NF90_UNLIMITED, &
    333254                                  id_dim_time_mask(mid,av) )
    334           CALL handle_netcdf_error( 'netcdf', 9998 )
     255          CALL handle_netcdf_error( 'netcdf', 467 )
    335256
    336257          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'time', NF90_DOUBLE, &
    337258                                  id_dim_time_mask(mid,av), &
    338259                                  id_var_time_mask(mid,av) )
    339           CALL handle_netcdf_error( 'netcdf', 9998 )
     260          CALL handle_netcdf_error( 'netcdf', 468 )
    340261
    341262          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
    342263                                  id_var_time_mask(mid,av), 'units', &
    343264                                  'seconds')
    344           CALL handle_netcdf_error( 'netcdf', 9998 )
     265          CALL handle_netcdf_error( 'netcdf', 469 )
    345266
    346267!
     
    349270          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'zu_3d', &
    350271                                  mask_size(mid,3), id_dim_zu_mask(mid,av) )
    351           CALL handle_netcdf_error( 'netcdf', 9998 )
     272          CALL handle_netcdf_error( 'netcdf', 470 )
    352273
    353274          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'zu_3d', NF90_DOUBLE, &
    354275                                  id_dim_zu_mask(mid,av), &
    355276                                  id_var_zu_mask(mid,av) )
    356           CALL handle_netcdf_error( 'netcdf', 9998 )
     277          CALL handle_netcdf_error( 'netcdf', 471 )
    357278
    358279          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_zu_mask(mid,av), &
    359280                                  'units', 'meters' )
    360           CALL handle_netcdf_error( 'netcdf', 9998 )
     281          CALL handle_netcdf_error( 'netcdf', 472 )
    361282
    362283!
     
    364285          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'zw_3d', &
    365286                                  mask_size(mid,3), id_dim_zw_mask(mid,av) )
    366           CALL handle_netcdf_error( 'netcdf', 9998 )
     287          CALL handle_netcdf_error( 'netcdf', 473 )
    367288
    368289          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'zw_3d', NF90_DOUBLE, &
    369290                                  id_dim_zw_mask(mid,av), &
    370291                                  id_var_zw_mask(mid,av) )
    371           CALL handle_netcdf_error( 'netcdf', 9998 )
     292          CALL handle_netcdf_error( 'netcdf', 474 )
    372293
    373294          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_zw_mask(mid,av), &
    374295                                  'units', 'meters' )
    375           CALL handle_netcdf_error( 'netcdf', 9998 )
     296          CALL handle_netcdf_error( 'netcdf', 475 )
    376297
    377298!
     
    379300          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'x', &
    380301                                  mask_size(mid,1), id_dim_x_mask(mid,av) )
    381           CALL handle_netcdf_error( 'netcdf', 9998 )
     302          CALL handle_netcdf_error( 'netcdf', 476 )
    382303
    383304          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'x', NF90_DOUBLE, &
    384305                                  id_dim_x_mask(mid,av), id_var_x_mask(mid,av) )
    385           CALL handle_netcdf_error( 'netcdf', 9998 )
     306          CALL handle_netcdf_error( 'netcdf', 477 )
    386307
    387308          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_x_mask(mid,av), &
    388309                                  'units', 'meters' )
    389           CALL handle_netcdf_error( 'netcdf', 9998 )
     310          CALL handle_netcdf_error( 'netcdf', 478 )
    390311
    391312!
     
    393314          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'xu', &
    394315                                  mask_size(mid,1), id_dim_xu_mask(mid,av) )
    395           CALL handle_netcdf_error( 'netcdf', 9998 )
     316          CALL handle_netcdf_error( 'netcdf', 479 )
    396317
    397318          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'xu', NF90_DOUBLE, &
    398319                                  id_dim_xu_mask(mid,av), &
    399320                                  id_var_xu_mask(mid,av) )
    400           CALL handle_netcdf_error( 'netcdf', 9998 )
     321          CALL handle_netcdf_error( 'netcdf', 480 )
    401322
    402323          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_xu_mask(mid,av), &
    403324                                  'units', 'meters' )
    404           CALL handle_netcdf_error( 'netcdf', 9998 )
     325          CALL handle_netcdf_error( 'netcdf', 481 )
    405326
    406327!
     
    408329          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'y', &
    409330                                  mask_size(mid,2), id_dim_y_mask(mid,av) )
    410           CALL handle_netcdf_error( 'netcdf', 9998 )
     331          CALL handle_netcdf_error( 'netcdf', 482 )
    411332
    412333          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'y', NF90_DOUBLE, &
    413334                                  id_dim_y_mask(mid,av), id_var_y_mask(mid,av) )
    414           CALL handle_netcdf_error( 'netcdf', 9998 )
     335          CALL handle_netcdf_error( 'netcdf', 483 )
    415336
    416337          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_y_mask(mid,av), &
    417338                                  'units', 'meters' )
    418           CALL handle_netcdf_error( 'netcdf', 9998 )
     339          CALL handle_netcdf_error( 'netcdf', 484 )
    419340
    420341!
     
    422343          nc_stat = NF90_DEF_DIM( id_set_mask(mid,av), 'yv', &
    423344                                  mask_size(mid,2), id_dim_yv_mask(mid,av) )
    424           CALL handle_netcdf_error( 'netcdf', 9998 )
     345          CALL handle_netcdf_error( 'netcdf', 485 )
    425346
    426347          nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), 'yv', NF90_DOUBLE, &
    427348                                  id_dim_yv_mask(mid,av), &
    428349                                  id_var_yv_mask(mid,av) )
    429           CALL handle_netcdf_error( 'netcdf', 9998 )
     350          CALL handle_netcdf_error( 'netcdf', 486 )
    430351
    431352          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), id_var_yv_mask(mid,av), &
    432353                                  'units', 'meters' )
    433           CALL handle_netcdf_error( 'netcdf', 9998 )
     354          CALL handle_netcdf_error( 'netcdf', 487 )
    434355
    435356!
     
    443364                                        id_dim_y_mask(mid,av) /), &
    444365                                     id_var_zusi_mask(mid,av) )
    445              CALL handle_netcdf_error( 'netcdf', 9998 )
     366             CALL handle_netcdf_error( 'netcdf', 488 )
    446367             
    447368             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
    448369                                     id_var_zusi_mask(mid,av), &
    449370                                     'units', 'meters' )
    450              CALL handle_netcdf_error( 'netcdf', 9998 )
     371             CALL handle_netcdf_error( 'netcdf', 489 )
    451372             
    452373             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
    453374                                     id_var_zusi_mask(mid,av), &
    454375                                     'long_name', 'zu(nzb_s_inner)' )
    455              CALL handle_netcdf_error( 'netcdf', 9998 )
     376             CALL handle_netcdf_error( 'netcdf', 490 )
    456377
    457378!             
     
    461382                                        id_dim_y_mask(mid,av) /), &
    462383                                     id_var_zwwi_mask(mid,av) )
    463              CALL handle_netcdf_error( 'netcdf', 9998 )
     384             CALL handle_netcdf_error( 'netcdf', 491 )
    464385             
    465386             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
    466387                                     id_var_zwwi_mask(mid,av), &
    467388                                     'units', 'meters' )
    468              CALL handle_netcdf_error( 'netcdf', 9998 )
     389             CALL handle_netcdf_error( 'netcdf', 492 )
    469390             
    470391             nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), &
    471392                                     id_var_zwwi_mask(mid,av), &
    472393                                     'long_name', 'zw(nzb_w_inner)' )
    473              CALL handle_netcdf_error( 'netcdf', 9998 )
     394             CALL handle_netcdf_error( 'netcdf', 493 )
    474395
    475396          ENDIF             
     
    548469!--          Define the grid
    549470             nc_stat = NF90_DEF_VAR( id_set_mask(mid,av), domask(mid,av,i), &
    550                                      nc_precision(10+mid+av*20),            &
     471                                     nc_precision(11),            &
    551472                                     (/ id_x, id_y, id_z,                   &
    552473                                        id_dim_time_mask(mid,av) /),        &
     
    556477                WRITE ( message_string, * ) 'no grid defined for', &
    557478                     ' variable ', TRIM( domask(mid,av,i) )
    558                 CALL message( 'define_netcdf_header', 'PA9998', 0, 1, 0, 6, 0 )
     479                CALL message( 'define_netcdf_header', 'PA0244', 0, 1, 0, 6, 0 )
    559480             ENDIF
    560481
    561482             var_list = TRIM( var_list ) // TRIM( domask(mid,av,i) ) // ';'
    562483
    563              CALL handle_netcdf_error( 'netcdf', 9998 )
     484             CALL handle_netcdf_error( 'netcdf', 494 )
    564485!
    565486!--          Store the 'real' name of the variable (with *, for example)
     
    569490                                     id_var_domask(mid,av,i), &
    570491                                     'long_name', domask(mid,av,i) )
    571              CALL handle_netcdf_error( 'netcdf', 9998 )
     492             CALL handle_netcdf_error( 'netcdf', 495 )
    572493!
    573494!--          Define the variable's unit
     
    575496                                     id_var_domask(mid,av,i), &
    576497                                     'units', TRIM( domask_unit(mid,av,i) ) )
    577              CALL handle_netcdf_error( 'netcdf', 9998 )
     498             CALL handle_netcdf_error( 'netcdf', 496 )
    578499
    579500             i = i + 1
     
    590511          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, &
    591512                                  'VAR_LIST', var_list )
    592           CALL handle_netcdf_error( 'netcdf', 9998 )
     513          CALL handle_netcdf_error( 'netcdf', 497 )
    593514
    594515!
    595516!--       Leave NetCDF define mode
    596517          nc_stat = NF90_ENDDEF( id_set_mask(mid,av) )
    597           CALL handle_netcdf_error( 'netcdf', 9998 )
     518          CALL handle_netcdf_error( 'netcdf', 498 )
    598519
    599520!
     
    606527                                  netcdf_data, start = (/ 1 /),               &
    607528                                  count = (/ mask_size(mid,1) /) )
    608           CALL handle_netcdf_error( 'netcdf', 9998 )
     529          CALL handle_netcdf_error( 'netcdf', 499 )
    609530
    610531          netcdf_data = mask_i_global(mid,:mask_size(mid,1)) * dx
     
    613534                                  netcdf_data, start = (/ 1 /),               &
    614535                                  count = (/ mask_size(mid,1) /) )
    615           CALL handle_netcdf_error( 'netcdf', 9998 )
     536          CALL handle_netcdf_error( 'netcdf', 500 )
    616537
    617538          DEALLOCATE( netcdf_data )
     
    626547                                  netcdf_data, start = (/ 1 /),               &
    627548                                  count = (/ mask_size(mid,2) /))
    628           CALL handle_netcdf_error( 'netcdf', 9998 )
     549          CALL handle_netcdf_error( 'netcdf', 501 )
    629550
    630551          netcdf_data = mask_j_global(mid,:mask_size(mid,2)) * dy
     
    633554                                  netcdf_data, start = (/ 1 /),    &
    634555                                  count = (/ mask_size(mid,2) /))
    635           CALL handle_netcdf_error( 'netcdf', 9998 )
     556          CALL handle_netcdf_error( 'netcdf', 502 )
    636557
    637558          DEALLOCATE( netcdf_data )
     
    646567                                  netcdf_data, start = (/ 1 /), &
    647568                                  count = (/ mask_size(mid,3) /) )
    648           CALL handle_netcdf_error( 'netcdf', 9998 )
     569          CALL handle_netcdf_error( 'netcdf', 503 )
    649570
    650571          netcdf_data = zw( mask_k_global(mid,:mask_size(mid,3)) )
     
    653574                                  netcdf_data, start = (/ 1 /), &
    654575                                  count = (/ mask_size(mid,3) /) )
    655           CALL handle_netcdf_error( 'netcdf', 9998 )
     576          CALL handle_netcdf_error( 'netcdf', 504 )
    656577
    657578          DEALLOCATE( netcdf_data )
     
    671592                                     count = (/ mask_size(mid,1), &
    672593                                                mask_size(mid,2) /) )
    673              CALL handle_netcdf_error( 'netcdf', 9998 )
     594             CALL handle_netcdf_error( 'netcdf', 505 )
    674595
    675596             netcdf_data_2d = zw_w_inner( mask_i_global(mid,:mask_size(mid,1)),&
     
    682603                                     count = (/ mask_size(mid,1), &
    683604                                                mask_size(mid,2) /) )
    684              CALL handle_netcdf_error( 'netcdf', 9998 )
     605             CALL handle_netcdf_error( 'netcdf', 506 )
    685606
    686607             DEALLOCATE( netcdf_data_2d )
     
    698619!--       mid and av
    699620          file_id = av
    700           IF ( file_id <= 140 )  THEN
    701              mid = file_id - 120
     621          IF ( file_id <= 200+max_masks )  THEN
     622             mid = file_id - 200
    702623             av = 0
    703624          ELSE
    704              mid = file_id - 140
     625             mid = file_id - (200+max_masks)
    705626             av = 1
    706627          ENDIF
     
    713634          nc_stat = NF90_GET_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'VAR_LIST',&
    714635                                  var_list_old )
    715           CALL handle_netcdf_error( 'netcdf', 9998 )
     636          CALL handle_netcdf_error( 'netcdf', 507 )
    716637
    717638          var_list = ';'
     
    733654                  '&but this file cannot be extended due to variable ', &
    734655                  'mismatch.&New file is created instead.'
    735              CALL message( 'define_netcdf_header', 'PA9998', 0, 1, 0, 6, 0 )
     656             CALL message( 'define_netcdf_header', 'PA0335', 0, 1, 0, 6, 0 )
    736657             extend = .FALSE.
    737658             RETURN
     
    742663          nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'zu', &
    743664                                    id_var_zu_mask(mid,av) )
    744           CALL handle_netcdf_error( 'netcdf', 9998 )
     665          CALL handle_netcdf_error( 'netcdf', 508 )
    745666
    746667          nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av),     &
    747668                                           id_var_zu_mask(mid,av),  &
    748669                                           dimids = id_dim_zu_mask_old )
    749           CALL handle_netcdf_error( 'netcdf', 9998 )
     670          CALL handle_netcdf_error( 'netcdf', 509 )
    750671          id_dim_zu_mask(mid,av) = id_dim_zu_mask_old(1)
    751672
     
    753674                                            id_dim_zu_mask(mid,av), &
    754675                                            len = nz_old )
    755           CALL handle_netcdf_error( 'netcdf', 9998 )
     676          CALL handle_netcdf_error( 'netcdf', 510 )
    756677
    757678          IF ( mask_size(mid,3) /= nz_old )  THEN
     
    761682                  ' number of&vertical grid points.', &
    762683                  '&New file is created instead.'
    763              CALL message( 'define_netcdf_header', 'PA9998', 0, 1, 0, 6, 0 )
     684             CALL message( 'define_netcdf_header', 'PA0336', 0, 1, 0, 6, 0 )
    764685             extend = .FALSE.
    765686             RETURN
     
    773694          nc_stat = NF90_INQ_VARID( id_set_mask(mid,av), 'time', &
    774695                                    id_var_time_mask(mid,av) )
    775           CALL handle_netcdf_error( 'netcdf', 9998 )
     696          CALL handle_netcdf_error( 'netcdf', 511 )
    776697
    777698          nc_stat = NF90_INQUIRE_VARIABLE( id_set_mask(mid,av), &
    778699                                           id_var_time_mask(mid,av), &
    779700                                           dimids = id_dim_time_old )
    780           CALL handle_netcdf_error( 'netcdf', 9998 )
     701          CALL handle_netcdf_error( 'netcdf', 512 )
    781702          id_dim_time_mask(mid,av) = id_dim_time_old(1)
    782703
     
    784705                                            id_dim_time_mask(mid,av), &
    785706                                            len = domask_time_count(mid,av) )
    786           CALL handle_netcdf_error( 'netcdf', 9998 )
     707          CALL handle_netcdf_error( 'netcdf', 513 )
    787708
    788709          nc_stat = NF90_GET_VAR( id_set_mask(mid,av), &
     
    791712                                  start = (/ domask_time_count(mid,av) /), &
    792713                                  count = (/ 1 /) )
    793           CALL handle_netcdf_error( 'netcdf', 9998 )
     714          CALL handle_netcdf_error( 'netcdf', 514 )
    794715
    795716          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    799720                  'output time&is less or equal than the last output time ', &
    800721                  'on this file.&New file is created instead.'
    801              CALL message( 'define_netcdf_header', 'PA9998', 0, 1, 0, 6, 0 )
     722             CALL message( 'define_netcdf_header', 'PA0337', 0, 1, 0, 6, 0 )
    802723             domask_time_count(mid,av) = 0
    803724             extend = .FALSE.
     
    813734                                       TRIM( domask(mid,av,i) ), &
    814735                                       id_var_domask(mid,av,i) )
    815              CALL handle_netcdf_error( 'netcdf', 9998 )
     736             CALL handle_netcdf_error( 'netcdf', 515 )
    816737             i = i + 1
    817738          ENDDO
     
    831752          ENDIF
    832753          nc_stat = NF90_REDEF( id_set_mask(mid,av) )
    833           CALL handle_netcdf_error( 'netcdf', 9998 )
     754          CALL handle_netcdf_error( 'netcdf', 516 )
    834755          nc_stat = NF90_PUT_ATT( id_set_mask(mid,av), NF90_GLOBAL, 'title', &
    835756                                  TRIM( run_description_header ) //    &
    836757                                  TRIM( time_average_text ) )
    837           CALL handle_netcdf_error( 'netcdf', 9998 )
     758          CALL handle_netcdf_error( 'netcdf', 517 )
    838759          nc_stat = NF90_ENDDEF( id_set_mask(mid,av) )
    839           CALL handle_netcdf_error( 'netcdf', 9998 )
     760          CALL handle_netcdf_error( 'netcdf', 518 )
    840761          WRITE ( message_string, * ) 'NetCDF file for ', TRIM( var ), &
    841762               ' data for mask', mid, ' from previous run found.', &
    842763               '&This file will be extended.'
    843           CALL message( 'define_netcdf_header', 'PA9998', 0, 0, 0, 6, 0 )
     764          CALL message( 'define_netcdf_header', 'PA0338', 0, 0, 0, 6, 0 )
    844765!
    845766!--       restore original parameter file_id (=formal parameter av) into av
Note: See TracChangeset for help on using the changeset viewer.