Ignore:
Timestamp:
Mar 18, 2009 12:26:04 PM (15 years ago)
Author:
heinze
Message:

Output of NetCDF messages with aid of message handling routine.

File:
1 edited

Legend:

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

    r257 r263  
    77! Current revisions:
    88! ------------------
     9! Output of NetCDF messages with aid of message handling routine.
    910! Output of messages replaced by message handling routine.
    1011!
     
    187188          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'Conventions', &
    188189                                  'COARDS' )
    189           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 62 )
     190          CALL handle_netcdf_error( 'netcdf', 62 )
    190191
    191192          IF ( av == 0 )  THEN
     
    198199                                  TRIM( run_description_header ) //    &
    199200                                  TRIM( time_average_text ) )
    200           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 63 )
     201          CALL handle_netcdf_error( 'netcdf', 63 )
    201202          IF ( av == 1 )  THEN
    202203             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    203204             nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'time_avg', &
    204205                                     TRIM( time_average_text ) )
    205              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 63 )
     206             CALL handle_netcdf_error( 'netcdf', 63 )
    206207          ENDIF
    207208
     
    210211          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'time', NF90_UNLIMITED, &
    211212                                  id_dim_time_3d(av) )
    212           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 64 )
     213          CALL handle_netcdf_error( 'netcdf', 64 )
    213214
    214215          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'time', NF90_DOUBLE, &
    215216                                  id_dim_time_3d(av), id_var_time_3d(av) )
    216           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 65 )
     217          CALL handle_netcdf_error( 'netcdf', 65 )
    217218
    218219          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_time_3d(av), 'units', &
    219220                                  'seconds')
    220           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 66 )
     221          CALL handle_netcdf_error( 'netcdf', 66 )
    221222
    222223!
     
    225226          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'zu_3d', nz_do3d-nzb+1, &
    226227                                  id_dim_zu_3d(av) )
    227           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 67 )
     228          CALL handle_netcdf_error( 'netcdf', 67 )
    228229
    229230          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'zu_3d', NF90_DOUBLE, &
    230231                                  id_dim_zu_3d(av), id_var_zu_3d(av) )
    231           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 68 )
     232          CALL handle_netcdf_error( 'netcdf', 68 )
    232233
    233234          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zu_3d(av), 'units', &
    234235                                  'meters' )
    235           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 69 )
     236          CALL handle_netcdf_error( 'netcdf', 69 )
    236237
    237238!
     
    239240          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'zw_3d', nz_do3d-nzb+1, &
    240241                                  id_dim_zw_3d(av) )
    241           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 70 )
     242          CALL handle_netcdf_error( 'netcdf', 70 )
    242243
    243244          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'zw_3d', NF90_DOUBLE, &
    244245                                  id_dim_zw_3d(av), id_var_zw_3d(av) )
    245           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 71 )
     246          CALL handle_netcdf_error( 'netcdf', 71 )
    246247
    247248          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zw_3d(av), 'units', &
    248249                                  'meters' )
    249           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 72 )
     250          CALL handle_netcdf_error( 'netcdf', 72 )
    250251
    251252!
    252253!--       Define x-axis (for scalar position)
    253254          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'x', nx+2, id_dim_x_3d(av) )
    254           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 73 )
     255          CALL handle_netcdf_error( 'netcdf', 73 )
    255256
    256257          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'x', NF90_DOUBLE, &
    257258                                  id_dim_x_3d(av), id_var_x_3d(av) )
    258           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 74 )
     259          CALL handle_netcdf_error( 'netcdf', 74 )
    259260
    260261          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_x_3d(av), 'units', &
    261262                                  'meters' )
    262           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 75 )
     263          CALL handle_netcdf_error( 'netcdf', 75 )
    263264
    264265!
    265266!--       Define x-axis (for u position)
    266267          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'xu', nx+2, id_dim_xu_3d(av) )
    267           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 358 )
     268          CALL handle_netcdf_error( 'netcdf', 358 )
    268269
    269270          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'xu', NF90_DOUBLE, &
    270271                                  id_dim_xu_3d(av), id_var_xu_3d(av) )
    271           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 359 )
     272          CALL handle_netcdf_error( 'netcdf', 359 )
    272273
    273274          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_xu_3d(av), 'units', &
    274275                                  'meters' )
    275           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 360 )
     276          CALL handle_netcdf_error( 'netcdf', 360 )
    276277
    277278!
    278279!--       Define y-axis (for scalar position)
    279280          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'y', ny+2, id_dim_y_3d(av) )
    280           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 76 )
     281          CALL handle_netcdf_error( 'netcdf', 76 )
    281282
    282283          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'y', NF90_DOUBLE, &
    283284                                  id_dim_y_3d(av), id_var_y_3d(av) )
    284           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 77 )
     285          CALL handle_netcdf_error( 'netcdf', 77 )
    285286
    286287          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_y_3d(av), 'units', &
    287288                                  'meters' )
    288           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 78 )
     289          CALL handle_netcdf_error( 'netcdf', 78 )
    289290
    290291!
    291292!--       Define y-axis (for v position)
    292293          nc_stat = NF90_DEF_DIM( id_set_3d(av), 'yv', ny+2, id_dim_yv_3d(av) )
    293           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 361 )
     294          CALL handle_netcdf_error( 'netcdf', 361 )
    294295
    295296          nc_stat = NF90_DEF_VAR( id_set_3d(av), 'yv', NF90_DOUBLE, &
    296297                                  id_dim_yv_3d(av), id_var_yv_3d(av) )
    297           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 362 )
     298          CALL handle_netcdf_error( 'netcdf', 362 )
    298299
    299300          nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_yv_3d(av), 'units', &
    300301                                  'meters' )
    301           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 363 )
     302          CALL handle_netcdf_error( 'netcdf', 363 )
    302303
    303304!
     
    310311                                     (/ id_dim_x_3d(av), id_dim_y_3d(av) /), &
    311312                                     id_var_zusi_3d(av) )
    312              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 413 )
     313             CALL handle_netcdf_error( 'netcdf', 413 )
    313314             
    314315             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zusi_3d(av), &
    315316                                     'units', 'meters' )
    316              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 414 )
     317             CALL handle_netcdf_error( 'netcdf', 414 )
    317318             
    318319             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zusi_3d(av), &
    319320                                     'long_name', 'zu(nzb_s_inner)' )
    320              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 415 )
     321             CALL handle_netcdf_error( 'netcdf', 415 )
    321322
    322323!             
     
    325326                                     (/ id_dim_x_3d(av), id_dim_y_3d(av) /), &
    326327                                     id_var_zwwi_3d(av) )
    327              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 416 )
     328             CALL handle_netcdf_error( 'netcdf', 416 )
    328329             
    329330             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zwwi_3d(av), &
    330331                                     'units', 'meters' )
    331              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 417 )
     332             CALL handle_netcdf_error( 'netcdf', 417 )
    332333             
    333334             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_zwwi_3d(av), &
    334335                                     'long_name', 'zw(nzb_w_inner)' )
    335              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 418 )
     336             CALL handle_netcdf_error( 'netcdf', 418 )
    336337
    337338          ENDIF             
     
    422423             var_list = TRIM( var_list ) // TRIM( do3d(av,i) ) // ';'
    423424
    424              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 79 )
     425             CALL handle_netcdf_error( 'netcdf', 79 )
    425426!
    426427!--          Store the 'real' name of the variable (with *, for example)
     
    429430             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_do3d(av,i), &
    430431                                     'long_name', do3d(av,i) )
    431              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 80 )
     432             CALL handle_netcdf_error( 'netcdf', 80 )
    432433!
    433434!--          Define the variable's unit
    434435             nc_stat = NF90_PUT_ATT( id_set_3d(av), id_var_do3d(av,i), &
    435436                                     'units', TRIM( do3d_unit(av,i) ) )
    436              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 357 )
     437             CALL handle_netcdf_error( 'netcdf', 357 )
    437438
    438439             i = i + 1
     
    449450          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', &
    450451                                  var_list )
    451           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 81 )
     452          CALL handle_netcdf_error( 'netcdf', 81 )
    452453
    453454!
    454455!--       Leave NetCDF define mode
    455456          nc_stat = NF90_ENDDEF( id_set_3d(av) )
    456           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 82 )
     457          CALL handle_netcdf_error( 'netcdf', 82 )
    457458
    458459!
     
    466467          nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_x_3d(av), netcdf_data, &
    467468                                  start = (/ 1 /), count = (/ nx+2 /) )
    468           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 83 )
     469          CALL handle_netcdf_error( 'netcdf', 83 )
    469470
    470471          DO  i = 0, nx+1
     
    475476                                  netcdf_data, start = (/ 1 /),    &
    476477                                  count = (/ nx+2 /) )
    477           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 385 )
     478          CALL handle_netcdf_error( 'netcdf', 385 )
    478479
    479480          DEALLOCATE( netcdf_data )
     
    489490          nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_y_3d(av), netcdf_data, &
    490491                                  start = (/ 1 /), count = (/ ny+2 /))
    491           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 84 )
     492          CALL handle_netcdf_error( 'netcdf', 84 )
    492493
    493494          DO  i = 0, ny+1
     
    498499                                  netcdf_data, start = (/ 1 /),    &
    499500                                  count = (/ ny+2 /))
    500           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 387 )
     501          CALL handle_netcdf_error( 'netcdf', 387 )
    501502
    502503          DEALLOCATE( netcdf_data )
     
    507508                                  zu(nzb:nz_do3d), start = (/ 1 /), &
    508509                                  count = (/ nz_do3d-nzb+1 /) )
    509           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 85 )
     510          CALL handle_netcdf_error( 'netcdf', 85 )
     511
    510512
    511513          nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zw_3d(av),    &
    512514                                  zw(nzb:nz_do3d), start = (/ 1 /), &
    513515                                  count = (/ nz_do3d-nzb+1 /) )
    514           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 86 )
     516          CALL handle_netcdf_error( 'netcdf', 86 )
    515517
    516518
     
    523525                                     start = (/ 1, 1 /), &
    524526                                     count = (/ nx+2, ny+2 /) )
    525              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 419 )
     527             CALL handle_netcdf_error( 'netcdf', 419 )
    526528
    527529             nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av), &
     
    529531                                     start = (/ 1, 1 /), &
    530532                                     count = (/ nx+2, ny+2 /) )
    531              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 420 )
     533             CALL handle_netcdf_error( 'netcdf', 420 )
    532534
    533535          ENDIF
     
    542544          nc_stat = NF90_GET_ATT( id_set_3d(av), NF90_GLOBAL, 'VAR_LIST', &
    543545                                  var_list_old )
    544           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 87 )
     546          CALL handle_netcdf_error( 'netcdf', 87 )
    545547
    546548          var_list = ';'
     
    571573!--       Get and compare the number of vertical gridpoints
    572574          nc_stat = NF90_INQ_VARID( id_set_3d(av), 'zu_3d', id_var_zu_3d(av) )
    573           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 88 )
     575          CALL handle_netcdf_error( 'netcdf', 88 )
    574576
    575577          nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_zu_3d(av), &
    576578                                           dimids = id_dim_zu_3d_old )
    577           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 89 )
     579          CALL handle_netcdf_error( 'netcdf', 89 )
    578580          id_dim_zu_3d(av) = id_dim_zu_3d_old(1)
    579581
    580582          nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_zu_3d(av), &
    581583                                            len = nz_old )
    582           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 90 )
     584          CALL handle_netcdf_error( 'netcdf', 90 )
    583585
    584586          IF ( nz_do3d-nzb+1 /= nz_old )  THEN
     
    600602!--       on the file.
    601603          nc_stat = NF90_INQ_VARID( id_set_3d(av), 'time', id_var_time_3d(av) )
    602           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 91 )
     604          CALL handle_netcdf_error( 'netcdf', 91 )
    603605
    604606          nc_stat = NF90_INQUIRE_VARIABLE( id_set_3d(av), id_var_time_3d(av), &
    605607                                           dimids = id_dim_time_old )
    606           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 92 )
     608          CALL handle_netcdf_error( 'netcdf', 92 )
     609
    607610          id_dim_time_3d(av) = id_dim_time_old(1)
    608611
    609612          nc_stat = NF90_INQUIRE_DIMENSION( id_set_3d(av), id_dim_time_3d(av), &
    610613                                            len = do3d_time_count(av) )
    611           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 93 )
     614          CALL handle_netcdf_error( 'netcdf', 93 )
    612615
    613616          nc_stat = NF90_GET_VAR( id_set_3d(av), id_var_time_3d(av), &
     
    615618                                  start = (/ do3d_time_count(av) /), &
    616619                                  count = (/ 1 /) )
    617           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 94 )
     620          CALL handle_netcdf_error( 'netcdf', 94 )
    618621
    619622          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    638641             nc_stat = NF90_INQ_VARID( id_set_3d(av), TRIM( do3d(av,i) ), &
    639642                                       id_var_do3d(av,i) )
    640              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 95 )
     643             CALL handle_netcdf_error( 'netcdf', 95 )
    641644             i = i + 1
    642645          ENDDO
     
    646649          nc_stat = NF90_PUT_ATT( id_set_3d(av), NF90_GLOBAL, 'title', &
    647650                                  TRIM( run_description_header ) )
    648           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 96 )
     651          CALL handle_netcdf_error( 'netcdf', 96 )
    649652          message_string = 'NetCDF file for volume data ' //             &
    650653                           TRIM( var ) // ' from previous run found.' // &
     
    658661          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'Conventions', &
    659662                                  'COARDS' )
    660           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 97 )
     663          CALL handle_netcdf_error( 'netcdf', 97 )
    661664
    662665          IF ( av == 0 )  THEN
     
    669672                                  TRIM( run_description_header ) //    &
    670673                                  TRIM( time_average_text ) )
    671           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 98 )
     674          CALL handle_netcdf_error( 'netcdf', 98 )
    672675          IF ( av == 1 )  THEN
    673676             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    674677             nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'time_avg', &
    675678                                     TRIM( time_average_text ) )
    676              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 98 )
     679             CALL handle_netcdf_error( 'netcdf', 98 )
    677680          ENDIF
    678681
     
    681684          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'time', NF90_UNLIMITED, &
    682685                                  id_dim_time_xy(av) )
    683           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 99 )
     686          CALL handle_netcdf_error( 'netcdf', 99 )
    684687
    685688          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'time', NF90_DOUBLE, &
    686689                                  id_dim_time_xy(av), id_var_time_xy(av) )
    687           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 100 )
     690          CALL handle_netcdf_error( 'netcdf', 100 )
    688691
    689692          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_time_xy(av), 'units', &
    690693                                  'seconds')
    691           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 101 )
     694          CALL handle_netcdf_error( 'netcdf', 101 )
    692695
    693696!
     
    707710!--       Define vertical coordinate grid (zu grid)
    708711          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'zu_xy', ns, id_dim_zu_xy(av) )
    709           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 102 )
     712          CALL handle_netcdf_error( 'netcdf', 102 )
    710713
    711714          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zu_xy', NF90_DOUBLE, &
    712715                                  id_dim_zu_xy(av), id_var_zu_xy(av) )
    713           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 103 )
     716          CALL handle_netcdf_error( 'netcdf', 103 )
    714717
    715718          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zu_xy(av), 'units', &
    716719                                  'meters' )
    717           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 104 )
     720          CALL handle_netcdf_error( 'netcdf', 104 )
    718721
    719722!
    720723!--       Define vertical coordinate grid (zw grid)
    721724          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'zw_xy', ns, id_dim_zw_xy(av) )
    722           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 105 )
     725          CALL handle_netcdf_error( 'netcdf', 105 )
    723726
    724727          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zw_xy', NF90_DOUBLE, &
    725728                                  id_dim_zw_xy(av), id_var_zw_xy(av) )
    726           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 106 )
     729          CALL handle_netcdf_error( 'netcdf', 106 )
    727730
    728731          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zw_xy(av), 'units', &
    729732                                  'meters' )
    730           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 107 )
     733          CALL handle_netcdf_error( 'netcdf', 107 )
    731734
    732735!
     
    735738          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'zu1_xy', 1, &
    736739                                  id_dim_zu1_xy(av) )
    737           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 108 )
     740          CALL handle_netcdf_error( 'netcdf', 108 )
    738741
    739742          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'zu1_xy', NF90_DOUBLE, &
    740743                                  id_dim_zu1_xy(av), id_var_zu1_xy(av) )
    741           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 109 )
     744          CALL handle_netcdf_error( 'netcdf', 109 )
    742745
    743746          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zu1_xy(av), 'units', &
    744747                                  'meters' )
    745           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 110 )
     748          CALL handle_netcdf_error( 'netcdf', 110 )
    746749
    747750!
     
    750753          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'ind_z_xy', NF90_DOUBLE, &
    751754                                  id_dim_zu_xy(av), id_var_ind_z_xy(av) )
    752           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 111 )
     755          CALL handle_netcdf_error( 'netcdf', 111 )
    753756
    754757          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_ind_z_xy(av), 'units', &
    755758                                  'gridpoints')
    756           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 112 )
     759          CALL handle_netcdf_error( 'netcdf', 112 )
    757760
    758761!
    759762!--       Define x-axis (for scalar position)
    760763          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'x', nx+2, id_dim_x_xy(av) )
    761           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 113 )
     764          CALL handle_netcdf_error( 'netcdf', 113 )
    762765
    763766          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'x', NF90_DOUBLE, &
    764767                                  id_dim_x_xy(av), id_var_x_xy(av) )
    765           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 114 )
     768          CALL handle_netcdf_error( 'netcdf', 114 )
     769
    766770
    767771          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_x_xy(av), 'units', &
    768772                                  'meters' )
    769           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 115 )
     773          CALL handle_netcdf_error( 'netcdf', 115 )
    770774
    771775!
    772776!--       Define x-axis (for u position)
    773777          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'xu', nx+2, id_dim_xu_xy(av) )
    774           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 388 )
     778          CALL handle_netcdf_error( 'netcdf', 388 )
    775779
    776780          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'xu', NF90_DOUBLE, &
    777781                                  id_dim_xu_xy(av), id_var_xu_xy(av) )
    778           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 389 )
     782          CALL handle_netcdf_error( 'netcdf', 389 )
    779783
    780784          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_xu_xy(av), 'units', &
    781785                                  'meters' )
    782           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 390 )
     786          CALL handle_netcdf_error( 'netcdf', 390 )
    783787
    784788!
    785789!--       Define y-axis (for scalar position)
    786790          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'y', ny+2, id_dim_y_xy(av) )
    787           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 116 )
     791          CALL handle_netcdf_error( 'netcdf', 116 )
    788792
    789793          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'y', NF90_DOUBLE, &
    790794                                  id_dim_y_xy(av), id_var_y_xy(av) )
    791           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 117 )
     795          CALL handle_netcdf_error( 'netcdf', 117 )
    792796
    793797          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_y_xy(av), 'units', &
    794798                                  'meters' )
    795           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 118 )
     799          CALL handle_netcdf_error( 'netcdf', 118 )
    796800
    797801!
    798802!--       Define y-axis (for scalar position)
    799803          nc_stat = NF90_DEF_DIM( id_set_xy(av), 'yv', ny+2, id_dim_yv_xy(av) )
    800           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 364 )
     804          CALL handle_netcdf_error( 'netcdf', 364 )
    801805
    802806          nc_stat = NF90_DEF_VAR( id_set_xy(av), 'yv', NF90_DOUBLE, &
    803807                                  id_dim_yv_xy(av), id_var_yv_xy(av) )
    804           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 365 )
     808          CALL handle_netcdf_error( 'netcdf', 365 )
    805809
    806810          nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_yv_xy(av), 'units', &
    807811                                  'meters' )
    808           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 366 )
     812          CALL handle_netcdf_error( 'netcdf', 366 )
    809813
    810814!
     
    817821                                     (/ id_dim_x_xy(av), id_dim_y_xy(av) /), &
    818822                                     id_var_zusi_xy(av) )
    819              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 421 )
     823             CALL handle_netcdf_error( 'netcdf', 421 )
    820824             
    821825             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zusi_xy(av), &
    822826                                     'units', 'meters' )
    823              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 422 )
     827             CALL handle_netcdf_error( 'netcdf', 422 )
    824828             
    825829             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zusi_xy(av), &
    826830                                     'long_name', 'zu(nzb_s_inner)' )
    827              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 423 )
     831             CALL handle_netcdf_error( 'netcdf', 423 )
    828832
    829833!             
     
    832836                                     (/ id_dim_x_xy(av), id_dim_y_xy(av) /), &
    833837                                     id_var_zwwi_xy(av) )
    834              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 424 )
     838             CALL handle_netcdf_error( 'netcdf', 424 )
    835839             
    836840             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zwwi_xy(av), &
    837841                                     'units', 'meters' )
    838              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 425 )
     842             CALL handle_netcdf_error( 'netcdf', 425 )
    839843             
    840844             nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_zwwi_xy(av), &
    841845                                     'long_name', 'zw(nzb_w_inner)' )
    842              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 426 )
     846             CALL handle_netcdf_error( 'netcdf', 426 )
    843847
    844848          ENDIF
     
    953957                ENDIF
    954958
    955                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 119 )
     959                CALL handle_netcdf_error( 'netcdf', 119 )
    956960!
    957961!--             Store the 'real' name of the variable (with *, for example)
     
    960964                nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_do2d(av,i), &
    961965                                        'long_name', do2d(av,i) )
    962                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 120 )
     966                CALL handle_netcdf_error( 'netcdf', 120 )
    963967!
    964968!--             Define the variable's unit
    965969                nc_stat = NF90_PUT_ATT( id_set_xy(av), id_var_do2d(av,i), &
    966970                                        'units', TRIM( do2d_unit(av,i) ) )
    967                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 354 )
     971                CALL handle_netcdf_error( 'netcdf', 354 )
    968972             ENDIF
    969973
     
    981985          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', &
    982986                                  var_list )
    983           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 121 )
     987          CALL handle_netcdf_error( 'netcdf', 121 )
    984988
    985989!
    986990!--       Leave NetCDF define mode
    987991          nc_stat = NF90_ENDDEF( id_set_xy(av) )
    988           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 122 )
     992          CALL handle_netcdf_error( 'netcdf', 122 )
    989993
    990994!
     
    10041008                                  netcdf_data, start = (/ 1 /),    &
    10051009                                  count = (/ ns /) )
    1006           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 123 )
     1010          CALL handle_netcdf_error( 'netcdf', 123 )
    10071011
    10081012!
     
    10181022                                  netcdf_data, start = (/ 1 /),    &
    10191023                                  count = (/ ns /) )
    1020           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 124 )
     1024          CALL handle_netcdf_error( 'netcdf', 124 )
    10211025
    10221026!
     
    10261030                                  netcdf_data, start = (/ 1 /),       &
    10271031                                  count = (/ ns /) )
    1028           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 125 )
     1032          CALL handle_netcdf_error( 'netcdf', 125 )
    10291033
    10301034          DEALLOCATE( netcdf_data )
     
    10351039                                  (/ zu(nzb+1) /), start = (/ 1 /), &
    10361040                                  count = (/ 1 /) )
    1037           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 126 )
     1041          CALL handle_netcdf_error( 'netcdf', 126 )
    10381042
    10391043!
     
    10471051          nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_x_xy(av), netcdf_data, &
    10481052                                  start = (/ 1 /), count = (/ nx+2 /) )
    1049           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 127 )
     1053          CALL handle_netcdf_error( 'netcdf', 127 )
    10501054
    10511055          DO  i = 0, nx+1
     
    10561060                                  netcdf_data, start = (/ 1 /),    &
    10571061                                  count = (/ nx+2 /) )
    1058           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 367 )
     1062          CALL handle_netcdf_error( 'netcdf', 367 )
    10591063
    10601064          DEALLOCATE( netcdf_data )
     
    10701074          nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_y_xy(av), netcdf_data, &
    10711075                                  start = (/ 1 /), count = (/ ny+2 /))
    1072           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 128 )
     1076          CALL handle_netcdf_error( 'netcdf', 128 )
    10731077
    10741078          DO  i = 0, ny+1
     
    10791083                                  netcdf_data, start = (/ 1 /),    &
    10801084                                  count = (/ ny+2 /))
    1081           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 368 )
     1085          CALL handle_netcdf_error( 'netcdf', 368 )
    10821086
    10831087          DEALLOCATE( netcdf_data )
     
    10911095                                     start = (/ 1, 1 /), &
    10921096                                     count = (/ nx+2, ny+2 /) )
    1093              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 427 )
     1097             CALL handle_netcdf_error( 'netcdf', 427 )
    10941098
    10951099             nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av), &
     
    10971101                                     start = (/ 1, 1 /), &
    10981102                                     count = (/ nx+2, ny+2 /) )
    1099              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 428 )
     1103             CALL handle_netcdf_error( 'netcdf', 428 )
    11001104
    11011105          ENDIF
     
    11111115          nc_stat = NF90_GET_ATT( id_set_xy(av), NF90_GLOBAL, 'VAR_LIST', &
    11121116                                  var_list_old )
    1113           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 129 )
     1117          CALL handle_netcdf_error( 'netcdf', 129 )
    11141118
    11151119          var_list = ';'
     
    11521156!--       Get and compare the number of horizontal cross sections
    11531157          nc_stat = NF90_INQ_VARID( id_set_xy(av), 'zu_xy', id_var_zu_xy(av) )
    1154           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 130 )
     1158          CALL handle_netcdf_error( 'netcdf', 130 )
    11551159
    11561160          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_zu_xy(av), &
    11571161                                           dimids = id_dim_zu_xy_old )
    1158           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 131 )
     1162          CALL handle_netcdf_error( 'netcdf', 131 )
    11591163          id_dim_zu_xy(av) = id_dim_zu_xy_old(1)
    11601164
    11611165          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_zu_xy(av), &
    11621166                                            len = ns_old )
    1163           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 132 )
     1167          CALL handle_netcdf_error( 'netcdf', 132 )
    11641168
    11651169          IF ( ns /= ns_old )  THEN
     
    11801184
    11811185          nc_stat = NF90_GET_VAR( id_set_xy(av), id_var_zu_xy(av), netcdf_data )
    1182           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 133 )
     1186          CALL handle_netcdf_error( 'netcdf', 133 )
    11831187
    11841188          DO  i = 1, ns
     
    12181222!--       on the file.
    12191223          nc_stat = NF90_INQ_VARID( id_set_xy(av), 'time', id_var_time_xy(av) )
    1220           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 134 )
     1224          CALL handle_netcdf_error( 'netcdf', 134 )
    12211225
    12221226          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xy(av), id_var_time_xy(av), &
    12231227                                           dimids = id_dim_time_old )
    1224           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 135 )
     1228          CALL handle_netcdf_error( 'netcdf', 135 )
    12251229          id_dim_time_xy(av) = id_dim_time_old(1)
    12261230
    12271231          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xy(av), id_dim_time_xy(av), &
    12281232                                            len = do2d_xy_time_count(av) )
    1229           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 136 )
     1233          CALL handle_netcdf_error( 'netcdf', 136 )
    12301234
    12311235          nc_stat = NF90_GET_VAR( id_set_xy(av), id_var_time_xy(av),    &
     
    12331237                                  start = (/ do2d_xy_time_count(av) /), &
    12341238                                  count = (/ 1 /) )
    1235           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 137 )
     1239          CALL handle_netcdf_error( 'netcdf', 137 )
    12361240
    12371241          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    12591263                nc_stat = NF90_INQ_VARID( id_set_xy(av), netcdf_var_name, &
    12601264                                          id_var_do2d(av,i) )
    1261                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 138 )
     1265                CALL handle_netcdf_error( 'netcdf', 138 )
    12621266             ENDIF
    12631267             i = i + 1
     
    12681272          nc_stat = NF90_PUT_ATT( id_set_xy(av), NF90_GLOBAL, 'title', &
    12691273                                  TRIM( run_description_header ) )
    1270           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 139 )
     1274          CALL handle_netcdf_error( 'netcdf', 139 )
    12711275          message_string = 'NetCDF file for cross-sections ' //           &
    12721276                            TRIM( var ) // ' from previous run found.' // &
     
    12811285          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'Conventions', &
    12821286                                  'COARDS' )
    1283           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 140 )
     1287          CALL handle_netcdf_error( 'netcdf', 140 )
    12841288
    12851289          IF ( av == 0 )  THEN
     
    12921296                                  TRIM( run_description_header )  //   &
    12931297                                  TRIM( time_average_text ) )
    1294           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 141 )
     1298          CALL handle_netcdf_error( 'netcdf', 141 )
    12951299          IF ( av == 1 )  THEN
    12961300             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    12971301             nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'time_avg', &
    12981302                                     TRIM( time_average_text ) )
    1299              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 141 )
     1303             CALL handle_netcdf_error( 'netcdf', 141 )
    13001304          ENDIF
    13011305
     
    13041308          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'time', NF90_UNLIMITED, &
    13051309                                  id_dim_time_xz(av) )
    1306           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 142 )
     1310          CALL handle_netcdf_error( 'netcdf', 142 )
    13071311
    13081312          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'time', NF90_DOUBLE, &
    13091313                                  id_dim_time_xz(av), id_var_time_xz(av) )
    1310           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 143 )
     1314          CALL handle_netcdf_error( 'netcdf', 143 )
    13111315
    13121316          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_time_xz(av), 'units', &
    13131317                                  'seconds')
    1314           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 144 )
     1318          CALL handle_netcdf_error( 'netcdf', 144 )
    13151319
    13161320!
     
    13301334!--       Define y-axis (for scalar position)
    13311335          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'y_xz', ns, id_dim_y_xz(av) )
    1332           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 145 )
     1336          CALL handle_netcdf_error( 'netcdf', 145 )
    13331337
    13341338          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'y_xz', NF90_DOUBLE, &
    13351339                                  id_dim_y_xz(av), id_var_y_xz(av) )
    1336           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 146 )
     1340          CALL handle_netcdf_error( 'netcdf', 146 )
    13371341
    13381342          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_y_xz(av), 'units', &
    13391343                                  'meters' )
    1340           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 147 )
     1344          CALL handle_netcdf_error( 'netcdf', 147 )
    13411345
    13421346!
    13431347!--       Define y-axis (for v position)
    13441348          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'yv_xz', ns, id_dim_yv_xz(av) )
    1345           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 369 )
     1349          CALL handle_netcdf_error( 'netcdf', 369 )
    13461350
    13471351          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'yv_xz', NF90_DOUBLE, &
    13481352                                  id_dim_yv_xz(av), id_var_yv_xz(av) )
    1349           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 370 )
     1353          CALL handle_netcdf_error( 'netcdf', 370 )
    13501354
    13511355          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_yv_xz(av), 'units', &
    13521356                                  'meters' )
    1353           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 371 )
     1357          CALL handle_netcdf_error( 'netcdf', 371 )
    13541358
    13551359!
     
    13581362          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'ind_y_xz', NF90_DOUBLE, &
    13591363                                  id_dim_y_xz(av), id_var_ind_y_xz(av) )
    1360           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 148 )
     1364          CALL handle_netcdf_error( 'netcdf', 148 )
    13611365
    13621366          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_ind_y_xz(av), 'units', &
    13631367                                  'gridpoints')
    1364           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 149 )
     1368          CALL handle_netcdf_error( 'netcdf', 149 )
    13651369
    13661370!
    13671371!--       Define x-axis (for scalar position)
    13681372          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'x', nx+2, id_dim_x_xz(av) )
    1369           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 150 )
     1373          CALL handle_netcdf_error( 'netcdf', 150 )
    13701374
    13711375          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'x', NF90_DOUBLE, &
    13721376                                  id_dim_x_xz(av), id_var_x_xz(av) )
    1373           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 151 )
     1377          CALL handle_netcdf_error( 'netcdf', 151 )
    13741378
    13751379          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_x_xz(av), 'units', &
    13761380                                  'meters' )
    1377           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 152 )
     1381          CALL handle_netcdf_error( 'netcdf', 152 )
    13781382
    13791383!
    13801384!--       Define x-axis (for u position)
    13811385          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'xu', nx+2, id_dim_xu_xz(av) )
    1382           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 372 )
     1386          CALL handle_netcdf_error( 'netcdf', 372 )
    13831387
    13841388          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'xu', NF90_DOUBLE, &
    13851389                                  id_dim_xu_xz(av), id_var_xu_xz(av) )
    1386           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 373 )
     1390          CALL handle_netcdf_error( 'netcdf', 373 )
    13871391
    13881392          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_xu_xz(av), 'units', &
    13891393                                  'meters' )
    1390           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 374 )
     1394          CALL handle_netcdf_error( 'netcdf', 374 )
    13911395
    13921396!
    13931397!--       Define the two z-axes (zu and zw)
    13941398          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'zu', nz+2, id_dim_zu_xz(av) )
    1395           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 153 )
     1399          CALL handle_netcdf_error( 'netcdf', 153 )
    13961400
    13971401          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'zu', NF90_DOUBLE, &
    13981402                                  id_dim_zu_xz(av), id_var_zu_xz(av) )
    1399           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 154 )
     1403          CALL handle_netcdf_error( 'netcdf', 154 )
    14001404
    14011405          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_zu_xz(av), 'units', &
    14021406                                  'meters' )
    1403           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 155 )
     1407          CALL handle_netcdf_error( 'netcdf', 155 )
    14041408
    14051409          nc_stat = NF90_DEF_DIM( id_set_xz(av), 'zw', nz+2, id_dim_zw_xz(av) )
    1406           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 156 )
     1410          CALL handle_netcdf_error( 'netcdf', 156 )
    14071411
    14081412          nc_stat = NF90_DEF_VAR( id_set_xz(av), 'zw', NF90_DOUBLE, &
    14091413                                  id_dim_zw_xz(av), id_var_zw_xz(av) )
    1410           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 157 )
     1414          CALL handle_netcdf_error( 'netcdf', 157 )
    14111415
    14121416          nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_zw_xz(av), 'units', &
    14131417                                  'meters' )
    1414           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 158 )
     1418          CALL handle_netcdf_error( 'netcdf', 158 )
    14151419
    14161420
     
    15021506                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
    15031507
    1504                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 159 )
     1508                CALL handle_netcdf_error( 'netcdf', 159 )
    15051509!
    15061510!--             Store the 'real' name of the variable (with *, for example)
     
    15091513                nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_do2d(av,i), &
    15101514                                        'long_name', do2d(av,i) )
    1511                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 160 )
     1515                CALL handle_netcdf_error( 'netcdf', 160 )
    15121516!
    15131517!--             Define the variable's unit
    15141518                nc_stat = NF90_PUT_ATT( id_set_xz(av), id_var_do2d(av,i), &
    15151519                                        'units', TRIM( do2d_unit(av,i) ) )
    1516                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 355 )
     1520                CALL handle_netcdf_error( 'netcdf', 355 )
    15171521             ENDIF
    15181522
     
    15301534          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', &
    15311535                                  var_list )
    1532           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 161 )
     1536          CALL handle_netcdf_error( 'netcdf', 161 )
    15331537
    15341538!
    15351539!--       Leave NetCDF define mode
    15361540          nc_stat = NF90_ENDDEF( id_set_xz(av) )
    1537           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 162 )
     1541          CALL handle_netcdf_error( 'netcdf', 162 )
    15381542
    15391543!
     
    15521556          nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_y_xz(av), netcdf_data, &
    15531557                                  start = (/ 1 /), count = (/ ns /) )
    1554           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 163 )
     1558          CALL handle_netcdf_error( 'netcdf', 163 )
    15551559
    15561560!
     
    15661570                                  netcdf_data, start = (/ 1 /),    &
    15671571                                  count = (/ ns /) )
    1568           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 375 )
     1572          CALL handle_netcdf_error( 'netcdf', 375 )
    15691573
    15701574!
     
    15741578                                  netcdf_data, start = (/ 1 /),       &
    15751579                                  count = (/ ns /) )
    1576           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 164 )
     1580          CALL handle_netcdf_error( 'netcdf', 164 )
     1581
    15771582
    15781583          DEALLOCATE( netcdf_data )
     
    15881593          nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_x_xz(av), netcdf_data, &
    15891594                                  start = (/ 1 /), count = (/ nx+2 /) )
    1590           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 165 )
     1595          CALL handle_netcdf_error( 'netcdf', 165 )
    15911596
    15921597          DO  i = 0, nx+1
     
    15971602                                  netcdf_data, start = (/ 1 /),    &
    15981603                                  count = (/ nx+2 /) )
    1599           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 376 )
     1604          CALL handle_netcdf_error( 'netcdf', 377 )
    16001605
    16011606          DEALLOCATE( netcdf_data )
     
    16091614                                  netcdf_data, start = (/ 1 /),    &
    16101615                                  count = (/ nz+2 /) )
    1611           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 166 )
     1616          CALL handle_netcdf_error( 'netcdf', 166 )
    16121617
    16131618          netcdf_data(0:nz+1) = zw(nzb:nzt+1)
     
    16151620                                  netcdf_data, start = (/ 1 /),    &
    16161621                                  count = (/ nz+2 /) )
    1617           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 167 )
     1622          CALL handle_netcdf_error( 'netcdf', 167 )
    16181623
    16191624          DEALLOCATE( netcdf_data )
     
    16291634          nc_stat = NF90_GET_ATT( id_set_xz(av), NF90_GLOBAL, 'VAR_LIST', &
    16301635                                  var_list_old )
    1631           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 168 )
     1636          CALL handle_netcdf_error( 'netcdf', 168 )
    16321637
    16331638          var_list = ';'
     
    16701675!--       Get and compare the number of vertical cross sections
    16711676          nc_stat = NF90_INQ_VARID( id_set_xz(av), 'y_xz', id_var_y_xz(av) )
    1672           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 169 )
     1677          CALL handle_netcdf_error( 'netcdf', 169 )
    16731678
    16741679          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_y_xz(av), &
    16751680                                           dimids = id_dim_y_xz_old )
    1676           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 170 )
     1681          CALL handle_netcdf_error( 'netcdf', 170 )
    16771682          id_dim_y_xz(av) = id_dim_y_xz_old(1)
    16781683
    16791684          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_y_xz(av), &
    16801685                                            len = ns_old )
    1681           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 171 )
     1686          CALL handle_netcdf_error( 'netcdf', 171 )
    16821687
    16831688          IF ( ns /= ns_old )  THEN
     
    16981703
    16991704          nc_stat = NF90_GET_VAR( id_set_xz(av), id_var_y_xz(av), netcdf_data )
    1700           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 172 )
     1705          CALL handle_netcdf_error( 'netcdf', 172 )
    17011706
    17021707          DO  i = 1, ns
     
    17361741!--       on the file.
    17371742          nc_stat = NF90_INQ_VARID( id_set_xz(av), 'time', id_var_time_xz(av) )
    1738           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 173 )
     1743          CALL handle_netcdf_error( 'netcdf', 173 )
    17391744
    17401745          nc_stat = NF90_INQUIRE_VARIABLE( id_set_xz(av), id_var_time_xz(av), &
    17411746                                           dimids = id_dim_time_old )
    1742           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 174 )
     1747          CALL handle_netcdf_error( 'netcdf', 174 )
    17431748          id_dim_time_xz(av) = id_dim_time_old(1)
    17441749
    17451750          nc_stat = NF90_INQUIRE_DIMENSION( id_set_xz(av), id_dim_time_xz(av), &
    17461751                                            len = do2d_xz_time_count(av) )
    1747           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 175 )
     1752          CALL handle_netcdf_error( 'netcdf', 175 )
    17481753
    17491754          nc_stat = NF90_GET_VAR( id_set_xz(av), id_var_time_xz(av),    &
     
    17511756                                  start = (/ do2d_xz_time_count(av) /), &
    17521757                                  count = (/ 1 /) )
    1753           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 176 )
     1758          CALL handle_netcdf_error( 'netcdf', 176 )
    17541759
    17551760          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    17771782                nc_stat = NF90_INQ_VARID( id_set_xz(av), netcdf_var_name, &
    17781783                                          id_var_do2d(av,i) )
    1779                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 177 )
     1784                CALL handle_netcdf_error( 'netcdf', 177 )
    17801785             ENDIF
    17811786             i = i + 1
     
    17861791          nc_stat = NF90_PUT_ATT( id_set_xz(av), NF90_GLOBAL, 'title', &
    17871792                                  TRIM( run_description_header ) )
    1788           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 178 )
     1793          CALL handle_netcdf_error( 'netcdf', 178 )
    17891794          message_string = 'NetCDF file for cross-sections ' //           &
    17901795                            TRIM( var ) // ' from previous run found.' // &
     
    17991804          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'Conventions', &
    18001805                                  'COARDS' )
    1801           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 179 )
     1806          CALL handle_netcdf_error( 'netcdf', 179 )
    18021807
    18031808          IF ( av == 0 )  THEN
     
    18101815                                  TRIM( run_description_header ) //    &
    18111816                                  TRIM( time_average_text ) )
    1812           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 180 )
     1817          CALL handle_netcdf_error( 'netcdf', 180 )
    18131818          IF ( av == 1 )  THEN
    18141819             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval
    18151820             nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'time_avg', &
    18161821                                     TRIM( time_average_text ) )
    1817              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 180 )
     1822             CALL handle_netcdf_error( 'netcdf', 180 )
    18181823          ENDIF
    18191824
     
    18221827          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'time', NF90_UNLIMITED, &
    18231828                                  id_dim_time_yz(av) )
    1824           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 181 )
     1829          CALL handle_netcdf_error( 'netcdf', 181 )
    18251830
    18261831          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'time', NF90_DOUBLE, &
    18271832                                  id_dim_time_yz(av), id_var_time_yz(av) )
    1828           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 182 )
     1833          CALL handle_netcdf_error( 'netcdf', 182 )
    18291834
    18301835          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_time_yz(av), 'units', &
    18311836                                  'seconds')
    1832           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 183 )
     1837          CALL handle_netcdf_error( 'netcdf', 183 )
    18331838
    18341839!
     
    18481853!--       Define x axis (for scalar position)
    18491854          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'x_yz', ns, id_dim_x_yz(av) )
    1850           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 184 )
     1855          CALL handle_netcdf_error( 'netcdf', 184 )
    18511856
    18521857          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'x_yz', NF90_DOUBLE, &
    18531858                                  id_dim_x_yz(av), id_var_x_yz(av) )
    1854           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 185 )
     1859          CALL handle_netcdf_error( 'netcdf', 185 )
    18551860
    18561861          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_x_yz(av), 'units', &
    18571862                                  'meters' )
    1858           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 186 )
     1863          CALL handle_netcdf_error( 'netcdf', 186 )
    18591864
    18601865!
    18611866!--       Define x axis (for u position)
    18621867          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'xu_yz', ns, id_dim_xu_yz(av) )
    1863           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 377 )
     1868          CALL handle_netcdf_error( 'netcdf', 377 )
    18641869
    18651870          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'xu_yz', NF90_DOUBLE, &
    18661871                                  id_dim_xu_yz(av), id_var_xu_yz(av) )
    1867           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 378 )
     1872          CALL handle_netcdf_error( 'netcdf', 378 )
    18681873
    18691874          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_xu_yz(av), 'units', &
    18701875                                  'meters' )
    1871           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 379 )
     1876          CALL handle_netcdf_error( 'netcdf', 379 )
    18721877
    18731878!
     
    18761881          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'ind_x_yz', NF90_DOUBLE, &
    18771882                                  id_dim_x_yz(av), id_var_ind_x_yz(av) )
    1878           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 187 )
     1883          CALL handle_netcdf_error( 'netcdf', 187 )
    18791884
    18801885          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_ind_x_yz(av), 'units', &
    18811886                                  'gridpoints')
    1882           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 188 )
     1887          CALL handle_netcdf_error( 'netcdf', 188 )
    18831888
    18841889!
    18851890!--       Define y-axis (for scalar position)
    18861891          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'y', ny+2, id_dim_y_yz(av) )
    1887           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 189 )
     1892          CALL handle_netcdf_error( 'netcdf', 189 )
    18881893
    18891894          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'y', NF90_DOUBLE, &
    18901895                                  id_dim_y_yz(av), id_var_y_yz(av) )
    1891           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 190 )
     1896          CALL handle_netcdf_error( 'netcdf', 190 )
    18921897
    18931898          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_y_yz(av), 'units', &
    18941899                                  'meters' )
    1895           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 191 )
     1900          CALL handle_netcdf_error( 'netcdf', 191 )
    18961901
    18971902!
    18981903!--       Define y-axis (for v position)
    18991904          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'yv', ny+2, id_dim_yv_yz(av) )
    1900           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 380 )
     1905          CALL handle_netcdf_error( 'netcdf', 380 )
    19011906
    19021907          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'yv', NF90_DOUBLE, &
    19031908                                  id_dim_yv_yz(av), id_var_yv_yz(av) )
    1904           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 381 )
     1909          CALL handle_netcdf_error( 'netcdf', 381 )
    19051910
    19061911          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_yv_yz(av), 'units', &
    19071912                                  'meters' )
    1908           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 382 )
     1913          CALL handle_netcdf_error( 'netcdf', 382 )
    19091914
    19101915!
    19111916!--       Define the two z-axes (zu and zw)
    19121917          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'zu', nz+2, id_dim_zu_yz(av) )
    1913           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 192 )
     1918          CALL handle_netcdf_error( 'netcdf', 192 )
    19141919
    19151920          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'zu', NF90_DOUBLE, &
    19161921                                  id_dim_zu_yz(av), id_var_zu_yz(av) )
    1917           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 193 )
     1922          CALL handle_netcdf_error( 'netcdf', 193 )
    19181923
    19191924          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_zu_yz(av), 'units', &
    19201925                                  'meters' )
    1921           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 194 )
     1926          CALL handle_netcdf_error( 'netcdf', 194 )
    19221927
    19231928          nc_stat = NF90_DEF_DIM( id_set_yz(av), 'zw', nz+2, id_dim_zw_yz(av) )
    1924           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 195 )
     1929          CALL handle_netcdf_error( 'netcdf', 195 )
    19251930
    19261931          nc_stat = NF90_DEF_VAR( id_set_yz(av), 'zw', NF90_DOUBLE, &
    19271932                                  id_dim_zw_yz(av), id_var_zw_yz(av) )
    1928           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 196 )
     1933          CALL handle_netcdf_error( 'netcdf', 196 )
    19291934
    19301935          nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_zw_yz(av), 'units', &
    19311936                                  'meters' )
    1932           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 197 )
     1937          CALL handle_netcdf_error( 'netcdf', 197 )
    19331938
    19341939
     
    20202025                var_list = TRIM( var_list ) // TRIM( do2d(av,i) ) // ';'
    20212026
    2022                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 198 )
     2027                CALL handle_netcdf_error( 'netcdf', 198 )
    20232028!
    20242029!--             Store the 'real' name of the variable (with *, for example)
     
    20272032                nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_do2d(av,i), &
    20282033                                        'long_name', do2d(av,i) )
    2029                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 199 )
     2034                CALL handle_netcdf_error( 'netcdf', 199 )
    20302035!
    20312036!--             Define the variable's unit
    20322037                nc_stat = NF90_PUT_ATT( id_set_yz(av), id_var_do2d(av,i), &
    20332038                                        'units', TRIM( do2d_unit(av,i) ) )
    2034                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 356 )
     2039                CALL handle_netcdf_error( 'netcdf', 356 )
    20352040             ENDIF
    20362041
     
    20482053          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', &
    20492054                                  var_list )
    2050           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 200 )
     2055          CALL handle_netcdf_error( 'netcdf', 200 )
    20512056
    20522057!
    20532058!--       Leave NetCDF define mode
    20542059          nc_stat = NF90_ENDDEF( id_set_yz(av) )
    2055           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 201 )
     2060          CALL handle_netcdf_error( 'netcdf', 201 )
    20562061
    20572062!
     
    20702075          nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_x_yz(av), netcdf_data, &
    20712076                                  start = (/ 1 /), count = (/ ns /) )
    2072           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 202 )
     2077          CALL handle_netcdf_error( 'netcdf', 202 )
    20732078
    20742079!
     
    20832088          nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_xu_yz(av), netcdf_data, &
    20842089                                  start = (/ 1 /), count = (/ ns /) )
    2085           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 383 )
     2090          CALL handle_netcdf_error( 'netcdf', 383 )
    20862091
    20872092!
     
    20912096                                  netcdf_data, start = (/ 1 /),       &
    20922097                                  count = (/ ns /) )
    2093           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 203 )
     2098          CALL handle_netcdf_error( 'netcdf', 203 )
    20942099
    20952100          DEALLOCATE( netcdf_data )
     
    21052110          nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_y_yz(av), netcdf_data, &
    21062111                                  start = (/ 1 /), count = (/ ny+2 /) )
    2107           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 204 )
     2112           CALL handle_netcdf_error( 'netcdf', 204 )
    21082113
    21092114          DO  j = 0, ny+1
     
    21142119                                  netcdf_data, start = (/ 1 /),    &
    21152120                                  count = (/ ny+2 /) )
    2116           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 384 )
     2121          CALL handle_netcdf_error( 'netcdf', 384 )
    21172122
    21182123          DEALLOCATE( netcdf_data )
     
    21262131                                  netcdf_data, start = (/ 1 /),    &
    21272132                                  count = (/ nz+2 /) )
    2128           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 205 )
     2133          CALL handle_netcdf_error( 'netcdf', 205 )
    21292134
    21302135          netcdf_data(0:nz+1) = zw(nzb:nzt+1)
     
    21322137                                  netcdf_data, start = (/ 1 /),    &
    21332138                                  count = (/ nz+2 /) )
    2134           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 206 )
     2139          CALL handle_netcdf_error( 'netcdf', 206 )
    21352140
    21362141          DEALLOCATE( netcdf_data )
     
    21462151          nc_stat = NF90_GET_ATT( id_set_yz(av), NF90_GLOBAL, 'VAR_LIST', &
    21472152                                  var_list_old )
    2148           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 207 )
     2153          CALL handle_netcdf_error( 'netcdf', 207 )
    21492154
    21502155          var_list = ';'
     
    21872192!--       Get and compare the number of vertical cross sections
    21882193          nc_stat = NF90_INQ_VARID( id_set_yz(av), 'x_yz', id_var_x_yz(av) )
    2189           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 208 )
     2194          CALL handle_netcdf_error( 'netcdf', 208 )
    21902195
    21912196          nc_stat = NF90_INQUIRE_VARIABLE( id_set_yz(av), id_var_x_yz(av), &
    21922197                                           dimids = id_dim_x_yz_old )
    2193           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 209 )
     2198          CALL handle_netcdf_error( 'netcdf', 209 )
    21942199          id_dim_x_yz(av) = id_dim_x_yz_old(1)
    21952200
    21962201          nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_x_yz(av), &
    21972202                                            len = ns_old )
    2198           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 210 )
     2203          CALL handle_netcdf_error( 'netcdf', 210 )
    21992204
    22002205          IF ( ns /= ns_old )  THEN
     
    22152220
    22162221          nc_stat = NF90_GET_VAR( id_set_yz(av), id_var_x_yz(av), netcdf_data )
    2217           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 211 )
     2222          CALL handle_netcdf_error( 'netcdf', 211 )
    22182223
    22192224          DO  i = 1, ns
     
    22532258!--       on the file.
    22542259          nc_stat = NF90_INQ_VARID( id_set_yz(av), 'time', id_var_time_yz(av) )
    2255           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 212 )
     2260          CALL handle_netcdf_error( 'netcdf', 212 )
    22562261
    22572262          nc_stat = NF90_INQUIRE_VARIABLE( id_set_yz(av), id_var_time_yz(av), &
    22582263                                           dimids = id_dim_time_old )
    2259           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 213 )
     2264          CALL handle_netcdf_error( 'netcdf', 213 )
    22602265          id_dim_time_yz(av) = id_dim_time_old(1)
    22612266
    22622267          nc_stat = NF90_INQUIRE_DIMENSION( id_set_yz(av), id_dim_time_yz(av), &
    22632268                                            len = do2d_yz_time_count(av) )
    2264           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 214 )
     2269          CALL handle_netcdf_error( 'netcdf', 214 )
    22652270
    22662271          nc_stat = NF90_GET_VAR( id_set_yz(av), id_var_time_yz(av),    &
     
    22682273                                  start = (/ do2d_yz_time_count(av) /), &
    22692274                                  count = (/ 1 /) )
    2270           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 215 )
     2275          CALL handle_netcdf_error( 'netcdf', 215 )
    22712276
    22722277          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    22942299                nc_stat = NF90_INQ_VARID( id_set_yz(av), netcdf_var_name, &
    22952300                                          id_var_do2d(av,i) )
    2296                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 216 )
     2301                CALL handle_netcdf_error( 'netcdf', 216 )
    22972302             ENDIF
    22982303             i = i + 1
     
    23032308          nc_stat = NF90_PUT_ATT( id_set_yz(av), NF90_GLOBAL, 'title', &
    23042309                                  TRIM( run_description_header ) )
    2305           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 217 )
     2310          CALL handle_netcdf_error( 'netcdf', 217 )
    23062311          message_string = 'NetCDF file for cross-sections ' //           &
    23072312                            TRIM( var ) // ' from previous run found.' // &
     
    23202325                                     TRIM( run_description_header ) //  &
    23212326                                     TRIM( time_average_text ) )
    2322              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 218 )
     2327             CALL handle_netcdf_error( 'netcdf', 218 )
    23232328
    23242329             WRITE ( time_average_text,'(F7.1,'' s avg'')' ) averaging_interval_pr
     
    23292334                                     TRIM( run_description_header ) )
    23302335          ENDIF
    2331           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 219 )
     2336          CALL handle_netcdf_error( 'netcdf', 219 )
    23322337
    23332338!
     
    23352340          nc_stat = NF90_DEF_DIM( id_set_pr, 'time', NF90_UNLIMITED, &
    23362341                                  id_dim_time_pr )
    2337           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 220 )
     2342          CALL handle_netcdf_error( 'netcdf', 220 )
    23382343
    23392344          nc_stat = NF90_DEF_VAR( id_set_pr, 'time', NF90_DOUBLE, &
    23402345                                  id_dim_time_pr, id_var_time_pr )
    2341           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 221 )
     2346          CALL handle_netcdf_error( 'netcdf', 221 )
    23422347
    23432348          nc_stat = NF90_PUT_ATT( id_set_pr, id_var_time_pr, 'units', 'seconds')
    2344           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 222 )
     2349          CALL handle_netcdf_error( 'netcdf', 222 )
    23452350
    23462351!
     
    23592364                nc_stat = NF90_DEF_DIM( id_set_pr, 'z'//TRIM(netcdf_var_name), &
    23602365                                        nzt+2-nzb, id_dim_z_pr(i,0) )
    2361                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 223 )
     2366                CALL handle_netcdf_error( 'netcdf', 223 )
    23622367
    23632368                nc_stat = NF90_DEF_VAR( id_set_pr, 'z'//TRIM(netcdf_var_name), &
    23642369                                        NF90_DOUBLE, id_dim_z_pr(i,0),         &
    23652370                                        id_var_z_pr(i,0) )
    2366                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 224 )
     2371                CALL handle_netcdf_error( 'netcdf', 224 )
    23672372
    23682373                nc_stat = NF90_PUT_ATT( id_set_pr, id_var_z_pr(i,0), 'units', &
    23692374                                        'meters' )
    2370                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 225 )
    2371 
     2375                CALL handle_netcdf_error( 'netcdf', 225 )
    23722376!
    23732377!--             Define the variable
     
    23752379                                        nc_precision(5), (/ id_dim_z_pr(i,0), &
    23762380                                        id_dim_time_pr /), id_var_dopr(i,0) )
    2377                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 226 )
     2381                CALL handle_netcdf_error( 'netcdf', 226 )
    23782382
    23792383                nc_stat = NF90_PUT_ATT( id_set_pr, id_var_dopr(i,0), &
    23802384                                        'long_name', TRIM( data_output_pr(i) ) )
    2381                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 227 )
     2385                CALL handle_netcdf_error( 'netcdf', 227 )
    23822386
    23832387                nc_stat = NF90_PUT_ATT( id_set_pr, id_var_dopr(i,0), &
    23842388                                        'units', TRIM( dopr_unit(i) ) )
    2385                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 228 )
     2389                CALL handle_netcdf_error( 'netcdf', 228 )
    23862390
    23872391                var_list = TRIM(var_list) // TRIM(netcdf_var_name) // ';'
     
    23992403                                           'z'//TRIM(netcdf_var_name)//suffix, &
    24002404                                           nzt+2-nzb, id_dim_z_pr(i,j) )
    2401                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 229 )
     2405                   CALL handle_netcdf_error( 'netcdf', 229 )
    24022406
    24032407                   nc_stat = NF90_DEF_VAR( id_set_pr,                          &
     
    24052409                                           nc_precision(5), id_dim_z_pr(i,j),  &
    24062410                                           id_var_z_pr(i,j) )
    2407                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 230 )
     2411                   CALL handle_netcdf_error( 'netcdf', 230 )
    24082412
    24092413                   nc_stat = NF90_PUT_ATT( id_set_pr, id_var_z_pr(i,j), &
    24102414                                           'units', 'meters' )
    2411                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 231 )
     2415                   CALL handle_netcdf_error( 'netcdf', 231 )
    24122416
    24132417!
     
    24182422                                           (/ id_dim_z_pr(i,j),               &
    24192423                                           id_dim_time_pr /), id_var_dopr(i,j) )
    2420                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 232 )
     2424                   CALL handle_netcdf_error( 'netcdf', 232 )
    24212425
    24222426                   nc_stat = NF90_PUT_ATT( id_set_pr, id_var_dopr(i,j),        &
     
    24242428                                           TRIM( data_output_pr(i) ) // ' SR ' &
    24252429                                           // suffix(2:2) )
    2426                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 233 )
     2430                   CALL handle_netcdf_error( 'netcdf', 233 )
    24272431
    24282432                   nc_stat = NF90_PUT_ATT( id_set_pr, id_var_dopr(i,j), &
    24292433                                           'units', TRIM( dopr_unit(i) ) )
    2430                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 234 )
     2434                   CALL handle_netcdf_error( 'netcdf', 234 )
    24312435
    24322436                   var_list = TRIM(var_list) // TRIM(netcdf_var_name) // &
     
    24432447!--       restart runs)
    24442448          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', var_list )
    2445           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 235 )
     2449          CALL handle_netcdf_error( 'netcdf', 235 )
    24462450
    24472451!
     
    24532457                                     nc_precision(5), (/ id_dim_time_pr /), &
    24542458                                     id_var_norm_dopr(i) )
    2455              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 236 )
     2459             CALL handle_netcdf_error( 'netcdf', 236 )
    24562460
    24572461             nc_stat = NF90_PUT_ATT( id_set_pr, id_var_norm_dopr(i), &
    24582462                                     'long_name',                    &
    24592463                                     TRIM( dopr_norm_longnames(i) ) )
    2460              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 237 )
     2464             CALL handle_netcdf_error( 'netcdf', 237 )
    24612465
    24622466          ENDDO
     
    24652469!--       Leave NetCDF define mode
    24662470          nc_stat = NF90_ENDDEF( id_set_pr )
    2467           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 238 )
     2471          CALL handle_netcdf_error( 'netcdf', 238 )
    24682472
    24692473!
     
    24762480                                        start = (/ 1 /),                  &
    24772481                                        count = (/ nzt-nzb+2 /) )
    2478                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 239 )
     2482                CALL handle_netcdf_error( 'netcdf', 239 )
    24792483
    24802484             ENDDO
     
    24912495          nc_stat = NF90_GET_ATT( id_set_pr, NF90_GLOBAL, 'VAR_LIST', &
    24922496                                  var_list_old )
    2493           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 240 )
     2497          CALL handle_netcdf_error( 'netcdf', 240 )
    24942498
    24952499          var_list = ';'
     
    25282532!--       on the file.
    25292533          nc_stat = NF90_INQ_VARID( id_set_pr, 'time', id_var_time_pr )
    2530           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 241 )
     2534          CALL handle_netcdf_error( 'netcdf', 241 )
    25312535
    25322536          nc_stat = NF90_INQUIRE_VARIABLE( id_set_pr, id_var_time_pr, &
    25332537                                           dimids = id_dim_time_old )
    2534           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 242 )
     2538          CALL handle_netcdf_error( 'netcdf', 242 )
    25352539          id_dim_time_pr = id_dim_time_old(1)
    25362540
    25372541          nc_stat = NF90_INQUIRE_DIMENSION( id_set_pr, id_dim_time_pr, &
    25382542                                            len = dopr_time_count )
    2539           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 243 )
     2543          CALL handle_netcdf_error( 'netcdf', 243 )
    25402544
    25412545          nc_stat = NF90_GET_VAR( id_set_pr, id_var_time_pr,        &
     
    25432547                                  start = (/ dopr_time_count /), &
    25442548                                  count = (/ 1 /) )
    2545           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 244 )
     2549          CALL handle_netcdf_error( 'netcdf', 244 )
    25462550
    25472551          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    25712575                nc_stat = NF90_INQ_VARID( id_set_pr, netcdf_var_name_base, &
    25722576                                          id_var_dopr(i,0) )
    2573                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 245 )
     2577                CALL handle_netcdf_error( 'netcdf', 245 )
    25742578             ELSE
    25752579                DO  j = 0, statistic_regions
     
    25782582                   nc_stat = NF90_INQ_VARID( id_set_pr, netcdf_var_name, &
    25792583                                             id_var_dopr(i,j) )
    2580                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 246 )
     2584                   CALL handle_netcdf_error( 'netcdf', 246 )
    25812585                ENDDO
    25822586             ENDIF
     
    25902594                                       'NORM_' // TRIM( dopr_norm_names(i) ), &
    25912595                                       id_var_norm_dopr(i) )
    2592              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 247 )
     2596             CALL handle_netcdf_error( 'netcdf', 247 )
    25932597          ENDDO
    25942598
     
    25972601          nc_stat = NF90_PUT_ATT( id_set_pr, NF90_GLOBAL, 'title', &
    25982602                                  TRIM( run_description_header ) )
    2599           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 248 )
     2603          CALL handle_netcdf_error( 'netcdf', 248 )
    26002604          message_string = 'NetCDF file for vertical profiles ' // &
    26012605                           'from previous run found.' //           &
     
    26102614          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title', &
    26112615                                  TRIM( run_description_header ) )
    2612           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 249 )
     2616          CALL handle_netcdf_error( 'netcdf', 249 )
    26132617
    26142618!
     
    26162620          nc_stat = NF90_DEF_DIM( id_set_ts, 'time', NF90_UNLIMITED, &
    26172621                                  id_dim_time_ts )
    2618           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 250 )
     2622          CALL handle_netcdf_error( 'netcdf', 250 )
    26192623
    26202624          nc_stat = NF90_DEF_VAR( id_set_ts, 'time', NF90_DOUBLE, &
    26212625                                  id_dim_time_ts, id_var_time_ts )
    2622           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 251 )
     2626          CALL handle_netcdf_error( 'netcdf', 251 )
    26232627
    26242628          nc_stat = NF90_PUT_ATT( id_set_ts, id_var_time_ts, 'units', 'seconds')
    2625           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 252 )
     2629          CALL handle_netcdf_error( 'netcdf', 252 )
    26262630
    26272631!
     
    26392643                                        nc_precision(6), (/ id_dim_time_ts /), &
    26402644                                        id_var_dots(i,0) )
    2641                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 253 )
     2645                CALL handle_netcdf_error( 'netcdf', 253 )
    26422646
    26432647                nc_stat = NF90_PUT_ATT( id_set_ts, id_var_dots(i,0), &
    26442648                                        'long_name', TRIM( dots_label(i) ) )
    2645                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 254 )
     2649                CALL handle_netcdf_error( 'netcdf', 254 )
    26462650
    26472651                nc_stat = NF90_PUT_ATT( id_set_ts, id_var_dots(i,0), &
    26482652                                        'units', TRIM( dots_unit(i) ) )
    2649                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 255 )
     2653                CALL handle_netcdf_error( 'netcdf', 255 )
    26502654
    26512655                var_list = TRIM(var_list) // TRIM(netcdf_var_name) // ';'
     
    26632667                                           (/ id_dim_time_ts /),              &
    26642668                                           id_var_dots(i,j) )
    2665                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 256 )
     2669                   CALL handle_netcdf_error( 'netcdf', 256 )
    26662670
    26672671                   nc_stat = NF90_PUT_ATT( id_set_ts, id_var_dots(i,j),       &
     
    26692673                                           TRIM( dots_label(i) ) // ' SR ' // &
    26702674                                           suffix(2:2) )
    2671                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 257 )
     2675                   CALL handle_netcdf_error( 'netcdf', 257 )
    26722676
    26732677                   var_list = TRIM(var_list) // TRIM(netcdf_var_name) // &
     
    26842688!--       restart runs)
    26852689          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', var_list )
    2686           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 258 )
     2690          CALL handle_netcdf_error( 'netcdf', 258 )
    26872691
    26882692!
    26892693!--       Leave NetCDF define mode
    26902694          nc_stat = NF90_ENDDEF( id_set_ts )
    2691           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 259 )
     2695          CALL handle_netcdf_error( 'netcdf', 259 )
    26922696
    26932697
     
    27012705          nc_stat = NF90_GET_ATT( id_set_ts, NF90_GLOBAL, 'VAR_LIST', &
    27022706                                  var_list_old )
    2703           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 260 )
     2707          CALL handle_netcdf_error( 'netcdf', 260 )
    27042708
    27052709          var_list = ';'
     
    27392743!--       on the file.
    27402744          nc_stat = NF90_INQ_VARID( id_set_ts, 'time', id_var_time_ts )
    2741           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 261 )
     2745          CALL handle_netcdf_error( 'netcdf', 261 )
    27422746
    27432747          nc_stat = NF90_INQUIRE_VARIABLE( id_set_ts, id_var_time_ts, &
    27442748                                           dimids = id_dim_time_old )
    2745           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 262 )
     2749          CALL handle_netcdf_error( 'netcdf', 262 )
    27462750          id_dim_time_ts = id_dim_time_old(1)
    27472751
    27482752          nc_stat = NF90_INQUIRE_DIMENSION( id_set_ts, id_dim_time_ts, &
    27492753                                            len = dots_time_count )
    2750           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 263 )
     2754          CALL handle_netcdf_error( 'netcdf', 263 )
    27512755
    27522756          nc_stat = NF90_GET_VAR( id_set_ts, id_var_time_ts,        &
     
    27542758                                  start = (/ dots_time_count /), &
    27552759                                  count = (/ 1 /) )
    2756           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 264 )
     2760          CALL handle_netcdf_error( 'netcdf', 264 )
    27572761
    27582762          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    27822786                nc_stat = NF90_INQ_VARID( id_set_ts, netcdf_var_name_base, &
    27832787                                          id_var_dots(i,0) )
    2784                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 265 )
     2788                CALL handle_netcdf_error( 'netcdf', 265 )
    27852789             ELSE
    27862790                DO  j = 0, statistic_regions
     
    27892793                   nc_stat = NF90_INQ_VARID( id_set_ts, netcdf_var_name, &
    27902794                                             id_var_dots(i,j) )
    2791                    IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 266 )
     2795                   CALL handle_netcdf_error( 'netcdf', 266 )
    27922796                ENDDO
    27932797             ENDIF
     
    27992803          nc_stat = NF90_PUT_ATT( id_set_ts, NF90_GLOBAL, 'title', &
    28002804                                  TRIM( run_description_header ) )
    2801           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 267 )
     2805          CALL handle_netcdf_error( 'netcdf', 267 )
    28022806          message_string = 'NetCDF file for time series ' // &
    28032807                           'from previous run found.' //     &
     
    28162820                                     TRIM( run_description_header ) // &
    28172821                                     TRIM( time_average_text ) )
    2818              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 268 )
     2822             CALL handle_netcdf_error( 'netcdf', 268 )
    28192823
    28202824             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval_sp
     
    28252829                                     TRIM( run_description_header ) )
    28262830          ENDIF
    2827           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 269 )
     2831          CALL handle_netcdf_error( 'netcdf', 269 )
    28282832
    28292833!
     
    28312835          nc_stat = NF90_DEF_DIM( id_set_sp, 'time', NF90_UNLIMITED, &
    28322836                                  id_dim_time_sp )
    2833           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 270 )
     2837          CALL handle_netcdf_error( 'netcdf', 270 )
    28342838
    28352839          nc_stat = NF90_DEF_VAR( id_set_sp, 'time', NF90_DOUBLE, &
    28362840                                  id_dim_time_sp, id_var_time_sp )
    2837           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 271 )
     2841          CALL handle_netcdf_error( 'netcdf', 271 )
    28382842
    28392843          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_time_sp, 'units', 'seconds')
    2840           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 272 )
     2844          CALL handle_netcdf_error( 'netcdf', 272 )
    28412845
    28422846!
     
    28532857!--       Define vertical coordinate grid (zu grid)
    28542858          nc_stat = NF90_DEF_DIM( id_set_sp, 'zu_sp', ns, id_dim_zu_sp )
    2855           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 273 )
     2859          CALL handle_netcdf_error( 'netcdf', 273 )
    28562860
    28572861          nc_stat = NF90_DEF_VAR( id_set_sp, 'zu_sp', NF90_DOUBLE, &
    28582862                                  id_dim_zu_sp, id_var_zu_sp )
    2859           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 274 )
     2863          CALL handle_netcdf_error( 'netcdf', 274 )
    28602864
    28612865          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_zu_sp, 'units', 'meters' )
    2862           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 275 )
     2866          CALL handle_netcdf_error( 'netcdf', 275 )
    28632867
    28642868!
    28652869!--       Define vertical coordinate grid (zw grid)
    28662870          nc_stat = NF90_DEF_DIM( id_set_sp, 'zw_sp', ns, id_dim_zw_sp )
    2867           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 276 )
     2871          CALL handle_netcdf_error( 'netcdf', 276 )
    28682872
    28692873          nc_stat = NF90_DEF_VAR( id_set_sp, 'zw_sp', NF90_DOUBLE, &
    28702874                                  id_dim_zw_sp, id_var_zw_sp )
    2871           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 277 )
     2875          CALL handle_netcdf_error( 'netcdf', 277 )
    28722876
    28732877          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_zw_sp, 'units', 'meters' )
    2874           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 278 )
     2878          CALL handle_netcdf_error( 'netcdf', 278 )
    28752879
    28762880!
    28772881!--       Define x-axis
    28782882          nc_stat = NF90_DEF_DIM( id_set_sp, 'k_x', nx/2, id_dim_x_sp )
    2879           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 279 )
     2883          CALL handle_netcdf_error( 'netcdf', 279 )
    28802884
    28812885          nc_stat = NF90_DEF_VAR( id_set_sp, 'k_x', NF90_DOUBLE, id_dim_x_sp, &
    28822886                                  id_var_x_sp )
    2883           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 280 )
     2887          CALL handle_netcdf_error( 'netcdf', 280 )
    28842888
    28852889          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_x_sp, 'units', 'm-1' )
    2886           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 281 )
     2890          CALL handle_netcdf_error( 'netcdf', 281 )
    28872891
    28882892!
    28892893!--       Define y-axis
    28902894          nc_stat = NF90_DEF_DIM( id_set_sp, 'k_y', ny/2, id_dim_y_sp )
    2891           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 282 )
     2895          CALL handle_netcdf_error( 'netcdf', 282 )
    28922896
    28932897          nc_stat = NF90_DEF_VAR( id_set_sp, 'k_y', NF90_DOUBLE, id_dim_y_sp, &
    28942898                                  id_var_y_sp )
    2895           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 283 )
     2899          CALL handle_netcdf_error( 'netcdf', 283 )
    28962900
    28972901          nc_stat = NF90_PUT_ATT( id_set_sp, id_var_y_sp, 'units', 'm-1' )
    2898           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 284 )
     2902          CALL handle_netcdf_error( 'netcdf', 284 )
    28992903
    29002904!
     
    29452949                                           id_var_dospx(i) )
    29462950                ENDIF
    2947                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 285 )
     2951                CALL handle_netcdf_error( 'netcdf', 285 )
    29482952
    29492953                nc_stat = NF90_PUT_ATT( id_set_sp, id_var_dospx(i), &
    29502954                                        'long_name', netcdf_var_name )
    2951                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 286 )
     2955                CALL handle_netcdf_error( 'netcdf', 286 )
    29522956
    29532957                nc_stat = NF90_PUT_ATT( id_set_sp, id_var_dospx(i), &
    29542958                                        'units', 'unknown' )
    2955                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 287 )
     2959                CALL handle_netcdf_error( 'netcdf', 287 )
    29562960
    29572961                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
     
    29762980                                           id_var_dospy(i) )
    29772981                ENDIF
    2978                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 288 )
     2982                CALL handle_netcdf_error( 'netcdf', 288 )
    29792983
    29802984                nc_stat = NF90_PUT_ATT( id_set_sp, id_var_dospy(i), &
    29812985                                        'long_name', netcdf_var_name )
    2982                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 289 )
     2986                CALL handle_netcdf_error( 'netcdf', 289 )
    29832987
    29842988                nc_stat = NF90_PUT_ATT( id_set_sp, id_var_dospy(i), &
    29852989                                        'units', 'unknown' )
    2986                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 290 )
     2990                CALL handle_netcdf_error( 'netcdf', 290 )
    29872991
    29882992                var_list = TRIM( var_list ) // TRIM( netcdf_var_name ) // ';'
     
    29983002!--       restart runs)
    29993003          nc_stat = NF90_PUT_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', var_list )
    3000           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 291 )
     3004          CALL handle_netcdf_error( 'netcdf', 291 )
    30013005
    30023006!
    30033007!--       Leave NetCDF define mode
    30043008          nc_stat = NF90_ENDDEF( id_set_sp )
    3005           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 292 )
     3009          CALL handle_netcdf_error( 'netcdf', 292 )
    30063010
    30073011!
     
    30143018          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zu_sp, netcdf_data, &
    30153019                                  start = (/ 1 /), count = (/ ns /) )
    3016           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 293 )
     3020          CALL handle_netcdf_error( 'netcdf', 293 )
    30173021
    30183022!
     
    30213025          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_zw_sp, netcdf_data, &
    30223026                                  start = (/ 1 /), count = (/ ns /) )
    3023           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 294 )
     3027          CALL handle_netcdf_error( 'netcdf', 294 )
    30243028
    30253029          DEALLOCATE( netcdf_data )
     
    30343038          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_x_sp, netcdf_data, &
    30353039                                  start = (/ 1 /), count = (/ nx/2 /) )
    3036           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 295 )
     3040          CALL handle_netcdf_error( 'netcdf', 295 )
    30373041
    30383042          DEALLOCATE( netcdf_data )
     
    30453049          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_y_sp, netcdf_data, &
    30463050                                  start = (/ 1 /), count = (/ ny/2 /) )
    3047           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 296 )
     3051          CALL handle_netcdf_error( 'netcdf', 296 )
    30483052
    30493053          DEALLOCATE( netcdf_data )
     
    30593063          nc_stat = NF90_GET_ATT( id_set_sp, NF90_GLOBAL, 'VAR_LIST', &
    30603064                                  var_list_old )
    3061           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 297 )
    3062 
     3065          CALL handle_netcdf_error( 'netcdf', 297 )
    30633066          var_list = ';'
    30643067          i = 1
     
    31023105!--       Get and compare the number of vertical levels
    31033106          nc_stat = NF90_INQ_VARID( id_set_sp, 'zu_sp', id_var_zu_sp )
    3104           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 298 )
     3107          CALL handle_netcdf_error( 'netcdf', 298 )
    31053108
    31063109          nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_zu_sp, &
    31073110                                           dimids = id_dim_zu_sp_old )
    3108           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 299 )
     3111          CALL handle_netcdf_error( 'netcdf', 299 )
    31093112          id_dim_zu_sp = id_dim_zu_sp_old(1)
    31103113
    31113114          nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_zu_sp, &
    31123115                                            len = ns_old )
    3113           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 300 )
     3116          CALL handle_netcdf_error( 'netcdf', 300 )
    31143117
    31153118          IF ( ns /= ns_old )  THEN
     
    31303133
    31313134          nc_stat = NF90_GET_VAR( id_set_sp, id_var_zu_sp, netcdf_data )
    3132           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 301 )
     3135          CALL handle_netcdf_error( 'netcdf', 301 )
    31333136
    31343137          DO  i = 1, ns
     
    31543157!--       on the file.
    31553158          nc_stat = NF90_INQ_VARID( id_set_sp, 'time', id_var_time_sp )
    3156           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 302 )
     3159          CALL handle_netcdf_error( 'netcdf', 302 )
    31573160
    31583161          nc_stat = NF90_INQUIRE_VARIABLE( id_set_sp, id_var_time_sp, &
    31593162                                           dimids = id_dim_time_old )
    3160           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 303 )
     3163          CALL handle_netcdf_error( 'netcdf', 303 )
    31613164          id_dim_time_sp = id_dim_time_old(1)
    31623165
    31633166          nc_stat = NF90_INQUIRE_DIMENSION( id_set_sp, id_dim_time_sp, &
    31643167                                            len = dosp_time_count )
    3165           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 304 )
     3168          CALL handle_netcdf_error( 'netcdf', 304 )
    31663169
    31673170          nc_stat = NF90_GET_VAR( id_set_sp, id_var_time_sp,        &
     
    31693172                                  start = (/ dosp_time_count /), &
    31703173                                  count = (/ 1 /) )
    3171           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 305 )
     3174          CALL handle_netcdf_error( 'netcdf', 305 )
    31723175
    31733176          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    31953198                nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, &
    31963199                                          id_var_dospx(i) )
    3197                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 306 )
     3200                CALL handle_netcdf_error( 'netcdf', 306 )
    31983201             ENDIF
    31993202
     
    32023205                nc_stat = NF90_INQ_VARID( id_set_sp, netcdf_var_name, &
    32033206                                          id_var_dospy(i) )
    3204                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 307 )
     3207                CALL handle_netcdf_error( 'netcdf', 307 )
    32053208             ENDIF
    32063209
     
    32173220                                     TRIM( run_description_header ) // &
    32183221                                     TRIM( time_average_text ) )
    3219              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 308 )
     3222             CALL handle_netcdf_error( 'netcdf', 308 )
    32203223
    32213224             WRITE ( time_average_text,'(F7.1,'' s avg'')' )  averaging_interval_sp
     
    32263229                                     TRIM( run_description_header ) )
    32273230          ENDIF
    3228           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 309 )
     3231          CALL handle_netcdf_error( 'netcdf', 309 )
    32293232          message_string = 'NetCDF file for spectra ' //     &
    32303233                           'from previous run found.' //     &
     
    32393242          nc_stat = NF90_PUT_ATT( id_set_prt, NF90_GLOBAL, 'title', &
    32403243                                  TRIM( run_description_header ) )
    3241           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 310 )
     3244          CALL handle_netcdf_error( 'netcdf', 310 )
    32423245
    32433246!
     
    32453248          nc_stat = NF90_DEF_DIM( id_set_prt, 'time', NF90_UNLIMITED, &
    32463249                                  id_dim_time_prt )
    3247           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 311 )
     3250          CALL handle_netcdf_error( 'netcdf', 311 )
    32483251
    32493252          nc_stat = NF90_DEF_VAR( id_set_prt, 'time', NF90_DOUBLE, &
    32503253                                  id_dim_time_prt, id_var_time_prt )
    3251           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 312 )
     3254          CALL handle_netcdf_error( 'netcdf', 312 )
    32523255
    32533256          nc_stat = NF90_PUT_ATT( id_set_prt, id_var_time_prt, 'units', &
    32543257                                  'seconds' )
    3255           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 313 )
     3258          CALL handle_netcdf_error( 'netcdf', 313 )
    32563259
    32573260!
     
    32593262          nc_stat = NF90_DEF_DIM( id_set_prt, 'particle_number', &
    32603263                                  maximum_number_of_particles, id_dim_prtnum )
    3261           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 314 )
     3264          CALL handle_netcdf_error( 'netcdf', 314 )
    32623265
    32633266          nc_stat = NF90_DEF_VAR( id_set_prt, 'particle_number', NF90_DOUBLE, &
    32643267                                  id_dim_prtnum, id_var_prtnum )
    3265           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 315 )
     3268          CALL handle_netcdf_error( 'netcdf', 315 )
    32663269
    32673270          nc_stat = NF90_PUT_ATT( id_set_prt, id_var_prtnum, 'units', &
    32683271                                  'particle number' )
    3269           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 316 )
     3272          CALL handle_netcdf_error( 'netcdf', 316 )
    32703273
    32713274!
     
    32733276          nc_stat = NF90_DEF_VAR( id_set_prt, 'real_num_of_prt', NF90_INT, &
    32743277                                  id_dim_time_prt, id_var_rnop_prt )
    3275           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 317 )
     3278          CALL handle_netcdf_error( 'netcdf', 317 )
    32763279
    32773280          nc_stat = NF90_PUT_ATT( id_set_prt, id_var_rnop_prt, 'units', &
    32783281                                  'particle number' )
    3279           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 318 )
     3282          CALL handle_netcdf_error( 'netcdf', 318 )
    32803283
    32813284!
     
    32873290                                     (/ id_dim_prtnum, id_dim_time_prt /), &
    32883291                                     id_var_prt(i) )
    3289              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 319 )
     3292             CALL handle_netcdf_error( 'netcdf', 319 )
    32903293
    32913294             nc_stat = NF90_PUT_ATT( id_set_prt, id_var_prt(i), &
    32923295                                     'long_name', TRIM( prt_var_names(i) ) )
    3293              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 320 )
     3296             CALL handle_netcdf_error( 'netcdf', 320 )
    32943297
    32953298             nc_stat = NF90_PUT_ATT( id_set_prt, id_var_prt(i), &
    32963299                                     'units', TRIM( prt_var_units(i) ) )
    3297              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 321 )
     3300             CALL handle_netcdf_error( 'netcdf', 321 )
    32983301
    32993302          ENDDO
     
    33023305!--       Leave NetCDF define mode
    33033306          nc_stat = NF90_ENDDEF( id_set_prt )
    3304           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 322 )
     3307          CALL handle_netcdf_error( 'netcdf', 322 )
    33053308
    33063309
     
    33133316!--       on the file.
    33143317          nc_stat = NF90_INQ_VARID( id_set_prt, 'time', id_var_time_prt )
    3315           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 323 )
     3318          CALL handle_netcdf_error( 'netcdf', 323 )
    33163319
    33173320          nc_stat = NF90_INQUIRE_VARIABLE( id_set_prt, id_var_time_prt, &
    33183321                                           dimids = id_dim_time_old )
    3319           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 324 )
     3322          CALL handle_netcdf_error( 'netcdf', 324 )
    33203323          id_dim_time_prt = id_dim_time_old(1)
    33213324
    33223325          nc_stat = NF90_INQUIRE_DIMENSION( id_set_prt, id_dim_time_prt, &
    33233326                                            len = prt_time_count )
    3324           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 325 )
     3327          CALL handle_netcdf_error( 'netcdf', 325 )
    33253328
    33263329          nc_stat = NF90_GET_VAR( id_set_prt, id_var_time_prt,  &
     
    33283331                                  start = (/ prt_time_count /), &
    33293332                                  count = (/ 1 /) )
    3330           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 326 )
     3333          CALL handle_netcdf_error( 'netcdf', 326 )
    33313334
    33323335          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    33493352          nc_stat = NF90_INQ_VARID( id_set_prt, 'real_num_of_prt', &
    33503353                                    id_var_rnop_prt )
    3351           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 327 )
     3354          CALL handle_netcdf_error( 'netcdf', 327 )
    33523355
    33533356          DO  i = 1, 17
     
    33553358             nc_stat = NF90_INQ_VARID( id_set_prt, prt_var_names(i), &
    33563359                                       id_var_prt(i) )
    3357              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 328 )
     3360             CALL handle_netcdf_error( 'netcdf', 328 )
    33583361
    33593362          ENDDO
     
    33723375          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title', &
    33733376                                  TRIM( run_description_header ) )
    3374           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 396 )
     3377          CALL handle_netcdf_error( 'netcdf', 396 )
    33753378
    33763379!
     
    33783381          nc_stat = NF90_DEF_DIM( id_set_pts, 'time', NF90_UNLIMITED, &
    33793382                                  id_dim_time_pts )
    3380           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 397 )
     3383          CALL handle_netcdf_error( 'netcdf', 397 )
    33813384
    33823385          nc_stat = NF90_DEF_VAR( id_set_pts, 'time', NF90_DOUBLE, &
    33833386                                  id_dim_time_pts, id_var_time_pts )
    3384           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 398 )
     3387          CALL handle_netcdf_error( 'netcdf', 398 )
    33853388
    33863389          nc_stat = NF90_PUT_ATT( id_set_pts, id_var_time_pts, 'units', &
    33873390                                  'seconds')
    3388           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 399 )
     3391          CALL handle_netcdf_error( 'netcdf', 399 )
    33893392
    33903393!
     
    34123415                                        (/ id_dim_time_pts /),              &
    34133416                                        id_var_dopts(i,j) )
    3414                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 400 )
     3417                CALL handle_netcdf_error( 'netcdf', 400 )
    34153418
    34163419                IF ( j == 0 )  THEN
     
    34243427                                           suffix1(2:3) )
    34253428                ENDIF
    3426                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 401 )
     3429                CALL handle_netcdf_error( 'netcdf', 401 )
    34273430
    34283431                nc_stat = NF90_PUT_ATT( id_set_pts, id_var_dopts(i,j), &
    34293432                                        'units', TRIM( dopts_unit(i) ) )
    3430                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 402 )
     3433                CALL handle_netcdf_error( 'netcdf', 402 )
    34313434
    34323435                var_list = TRIM(var_list) // TRIM(netcdf_var_name) // &
     
    34443447          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', &
    34453448                                  var_list )
    3446           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 403 )
     3449          CALL handle_netcdf_error( 'netcdf', 403 )
     3450
    34473451
    34483452!
    34493453!--       Leave NetCDF define mode
    34503454          nc_stat = NF90_ENDDEF( id_set_pts )
    3451           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 404 )
     3455          CALL handle_netcdf_error( 'netcdf', 404 )
    34523456
    34533457
     
    34613465          nc_stat = NF90_GET_ATT( id_set_pts, NF90_GLOBAL, 'VAR_LIST', &
    34623466                                  var_list_old )
    3463           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 405 )
     3467          CALL handle_netcdf_error( 'netcdf', 405 )
    34643468
    34653469          var_list = ';'
     
    35043508!--       on the file.
    35053509          nc_stat = NF90_INQ_VARID( id_set_pts, 'time', id_var_time_pts )
    3506           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 406 )
     3510          CALL handle_netcdf_error( 'netcdf', 406 )
    35073511
    35083512          nc_stat = NF90_INQUIRE_VARIABLE( id_set_pts, id_var_time_pts, &
    35093513                                           dimids = id_dim_time_old )
    3510           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 407 )
     3514          CALL handle_netcdf_error( 'netcdf', 407 )
    35113515          id_dim_time_pts = id_dim_time_old(1)
    35123516
    35133517          nc_stat = NF90_INQUIRE_DIMENSION( id_set_pts, id_dim_time_pts, &
    35143518                                            len = dopts_time_count )
    3515           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 408 )
     3519          CALL handle_netcdf_error( 'netcdf', 408 )
    35163520
    35173521          nc_stat = NF90_GET_VAR( id_set_pts, id_var_time_pts,    &
     
    35193523                                  start = (/ dopts_time_count /), &
    35203524                                  count = (/ 1 /) )
    3521           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 409 )
     3525          CALL handle_netcdf_error( 'netcdf', 409 )
    35223526
    35233527          IF ( last_time_coordinate(1) >= simulated_time )  THEN
     
    35563560                nc_stat = NF90_INQ_VARID( id_set_pts, netcdf_var_name, &
    35573561                                          id_var_dopts(i,j) )
    3558                 IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 410 )
     3562                CALL handle_netcdf_error( 'netcdf', 410 )
    35593563
    35603564                IF ( number_of_particle_groups == 1 )  EXIT
     
    35683572          nc_stat = NF90_PUT_ATT( id_set_pts, NF90_GLOBAL, 'title', &
    35693573                                  TRIM( run_description_header ) )
    3570           IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 411 )
     3574          CALL handle_netcdf_error( 'netcdf', 411 )
    35713575          message_string = 'NetCDF file for particle time series ' // &
    35723576                           'from previous run found.' //              &
     
    35863590
    35873591
    3588 
    3589  SUBROUTINE handle_netcdf_error( errno )
     3592SUBROUTINE handle_netcdf_error( routine_name, errno )
    35903593#if defined( __netcdf )
    35913594
     
    35973600!------------------------------------------------------------------------------!
    35983601
     3602    USE control_parameters
    35993603    USE netcdf
    36003604    USE netcdf_control
     
    36033607    IMPLICIT NONE
    36043608
     3609    CHARACTER(LEN=6) ::  message_identifier
     3610    CHARACTER(LEN=*) ::  routine_name
     3611
    36053612    INTEGER ::  errno
    36063613
    36073614    IF ( nc_stat /= NF90_NOERR )  THEN
    3608        PRINT*, '+++ netcdf error ', errno,': ', TRIM( NF90_STRERROR( nc_stat ) )
    3609 #if defined( __parallel )
    3610        CALL MPI_ABORT( comm2d, 9999, ierr )
    3611 #else
    3612        CALL local_stop
    3613 #endif
     3615
     3616       WRITE( message_identifier, '(''NC'',I4.4)' )  errno
     3617       message_string = TRIM( NF90_STRERROR( nc_stat ) )
     3618
     3619       CALL message( routine_name, message_identifier, 2, 2, 0, 6, 0 )
     3620
    36143621    ENDIF
    36153622
Note: See TracChangeset for help on using the changeset viewer.