Ignore:
Timestamp:
Oct 24, 2018 6:39:32 PM (6 years ago)
Author:
gronemeier
Message:

new surface-data output; renamed output variables (pt to theta, rho_air to rho, rho_ocean to rho_sea_water)

File:
1 edited

Legend:

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

    r3337 r3421  
    2525! -----------------
    2626! $Id$
     27! Bugfix: move ocean output variables to ocean_mod
     28! Renamed output variables
     29! Add UTM coordinates to mask, 3d, xy, xz, yz output
     30!
     31! 3337 2018-10-12 15:17:09Z kanani
    2732! (from branch resler)
    2833! Add biometeorology
     
    330335    INTEGER(iwp), PARAMETER ::  dopr_norm_num = 7, dopts_num = 29, dots_max = 100
    331336
    332     CHARACTER (LEN=6), DIMENSION(dopr_norm_num) ::  dopr_norm_names =          &
    333          (/ 'wpt0  ', 'ws2   ', 'tsw2  ', 'ws3   ', 'ws2tsw', 'wstsw2',        &
    334             'z_i   ' /)
    335 
    336     CHARACTER (LEN=6), DIMENSION(dopr_norm_num) ::  dopr_norm_longnames =      &
    337          (/ 'wpt0  ', 'w*2   ', 't*w2  ', 'w*3   ', 'w*2t*w', 'w*t*w2',        &
    338             'z_i   ' /)
     337    CHARACTER (LEN=7), DIMENSION(dopr_norm_num) ::  dopr_norm_names =          &
     338         (/ 'wtheta0', 'ws2    ', 'tsw2   ', 'ws3    ', 'ws2tsw ', 'wstsw2 ',  &
     339            'z_i    ' /)
     340
     341    CHARACTER (LEN=7), DIMENSION(dopr_norm_num) ::  dopr_norm_longnames =      &
     342         (/ 'wtheta0', 'w*2    ', 't*w2   ', 'w*3    ', 'w*2t*w ', 'w*t*w2 ',  &
     343            'z_i    ' /)
    339344
    340345    CHARACTER (LEN=7), DIMENSION(dopts_num) :: dopts_label =                   &
     
    358363    CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_label =                    &
    359364          (/ 'E            ', 'E*           ', 'dt           ',                &
    360              'u*           ', 'th*          ', 'umax         ',                &
     365             'us*          ', 'th*          ', 'umax         ',                &
    361366             'vmax         ', 'wmax         ', 'div_new      ',                &
    362              'div_old      ', 'z_i_wpt      ', 'z_i_pt       ',                &
    363              'w*           ', 'w"pt"0       ', 'w"pt"        ',                &
    364              'wpt          ', 'pt(0)        ', 'pt(z_mo)     ',                &
     367             'div_old      ', 'zi_wtheta    ', 'zi_theta     ',                &
     368             'w*           ', 'w"theta"0    ', 'w"theta"     ',                &
     369             'wtheta       ', 'theta(0)     ', 'theta(z_mo)  ',                &
    365370             'w"u"0        ', 'w"v"0        ', 'w"q"0        ',                &
    366371             'ol           ', 'q*           ', 'w"s"         ',                &
     
    456461                    id_var_zw_xy, id_var_zw_xz, id_var_zw_yz, id_var_zw_3d
    457462
     463    INTEGER(iwp), DIMENSION(0:1,0:2) ::  id_var_eutm_3d, id_var_nutm_3d, &
     464                                         id_var_eutm_xy, id_var_nutm_xy, &
     465                                         id_var_eutm_xz, id_var_nutm_xz, &
     466                                         id_var_eutm_yz, id_var_nutm_yz, &
     467                                         id_var_eutm_ma, id_var_nutm_ma
     468
    458469    INTEGER ::  netcdf_data_format = 2  !< NetCDF3 64bit offset format
    459470    INTEGER ::  netcdf_deflate = 0      !< NetCDF compression, default: no
     
    498509                   id_var_zu_mask, id_var_zw_mask, &
    499510                   id_var_zusi_mask, id_var_zwwi_mask
     511                   
     512    INTEGER(iwp), DIMENSION(1:max_masks,0:1,0:2) ::  id_var_eutm_mask, &
     513                                                     id_var_nutm_mask
    500514
    501515    INTEGER(iwp), DIMENSION(1:max_masks,0:1,100) ::  id_var_domask
     
    596610    USE land_surface_model_mod,                                                &
    597611        ONLY: lsm_define_netcdf_grid, nzb_soil, nzt_soil, nzs, zs
     612
     613    USE netcdf_data_input_mod,                                                 &
     614        ONLY: init_model
    598615
    599616    USE ocean_mod,                                                             &
     
    692709
    693710    LOGICAL, SAVE ::  init_netcdf = .FALSE.                  !<
     711
     712    REAL(wp) ::  cos_ra                                      !< cosine of rotation_angle
     713    REAL(wp) ::  shift_x                                     !< shift of x coordinate
     714    REAL(wp) ::  shift_y                                     !< shift of y coordinate
     715    REAL(wp) ::  sin_ra                                      !< sine of rotation_angle
    694716
    695717    REAL(wp), DIMENSION(1) ::  last_time_coordinate          !< last time value in file
     
    901923                                  'meters', '', 486, 487, 000 )
    902924!
     925!--       Define UTM coordinates
     926          IF ( init_model%rotation_angle == 0.0_wp )  THEN
     927             CALL netcdf_create_var( id_set_mask(mid,av), &
     928                                 (/ id_dim_x_mask(mid,av) /),      &
     929                                 'E_UTM', NF90_DOUBLE, id_var_eutm_mask(mid,av,0),  &
     930                                 'm', '', 000, 000, 000 )
     931             CALL netcdf_create_var( id_set_mask(mid,av), &
     932                                 (/ id_dim_y_mask(mid,av) /),      &
     933                                 'N_UTM', NF90_DOUBLE, id_var_nutm_mask(mid,av,0),  &
     934                                 'm', '', 000, 000, 000 )
     935             CALL netcdf_create_var( id_set_mask(mid,av), &
     936                                 (/ id_dim_xu_mask(mid,av) /),     &
     937                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_mask(mid,av,1), &
     938                                 'm', '', 000, 000, 000 )
     939             CALL netcdf_create_var( id_set_mask(mid,av), &
     940                                 (/ id_dim_y_mask(mid,av) /),     &
     941                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_mask(mid,av,1), &
     942                                 'm', '', 000, 000, 000 )
     943             CALL netcdf_create_var( id_set_mask(mid,av), &
     944                                 (/ id_dim_x_mask(mid,av) /),     &
     945                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_mask(mid,av,2), &
     946                                 'm', '', 000, 000, 000 )
     947             CALL netcdf_create_var( id_set_mask(mid,av), &
     948                                 (/ id_dim_yv_mask(mid,av) /),     &
     949                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_mask(mid,av,2), &
     950                                 'm', '', 000, 000, 000 )
     951          ELSE
     952             CALL netcdf_create_var( id_set_mask(mid,av), &
     953                                 (/ id_dim_x_mask(mid,av), id_dim_y_mask(mid,av) /),      &
     954                                 'E_UTM', NF90_DOUBLE, id_var_eutm_mask(mid,av,0),  &
     955                                 'm', '', 000, 000, 000 )
     956             CALL netcdf_create_var( id_set_mask(mid,av), &
     957                                 (/ id_dim_x_mask(mid,av), id_dim_y_mask(mid,av) /),      &
     958                                 'N_UTM', NF90_DOUBLE, id_var_nutm_mask(mid,av,0),  &
     959                                 'm', '', 000, 000, 000 )
     960             CALL netcdf_create_var( id_set_mask(mid,av), &
     961                                 (/ id_dim_xu_mask(mid,av), id_dim_y_mask(mid,av) /),     &
     962                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_mask(mid,av,1), &
     963                                 'm', '', 000, 000, 000 )
     964             CALL netcdf_create_var( id_set_mask(mid,av), &
     965                                 (/ id_dim_xu_mask(mid,av), id_dim_y_mask(mid,av) /),     &
     966                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_mask(mid,av,1), &
     967                                 'm', '', 000, 000, 000 )
     968             CALL netcdf_create_var( id_set_mask(mid,av), &
     969                                 (/ id_dim_x_mask(mid,av), id_dim_yv_mask(mid,av) /),     &
     970                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_mask(mid,av,2), &
     971                                 'm', '', 000, 000, 000 )
     972             CALL netcdf_create_var( id_set_mask(mid,av), &
     973                                 (/ id_dim_x_mask(mid,av), id_dim_yv_mask(mid,av) /),     &
     974                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_mask(mid,av,2), &
     975                                 'm', '', 000, 000, 000 )
     976          ENDIF
     977!
    903978!--       In case of non-flat topography define 2d-arrays containing the height
    904979!--       information. Only for parallel netcdf output.
     
    9541029!
    9551030!--             Most variables are defined on the scalar grid
    956                 CASE ( 'e', 'lpt', 'nc', 'nr', 'p', 'pc', 'pr', 'prr', 'pt',   &
     1031                CASE ( 'e', 'nc', 'nr', 'p', 'pc', 'pr', 'prr',                &
    9571032                       'q', 'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',   &
    958                        's', 'vpt' )
     1033                       's', 'theta', 'thetal', 'thetav' )
    9591034
    9601035                   grid_x = 'x'
     
    11441219
    11451220!
     1221!--       Write UTM coordinates
     1222          IF ( init_model%rotation_angle == 0.0_wp )  THEN
     1223!
     1224!--          1D in case of no rotation
     1225             cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     1226!
     1227!--          x coordinates
     1228             ALLOCATE( netcdf_data(mask_size(mid,1)) )
     1229             DO  k = 0, 2
     1230!           
     1231!--             Scalar grid points
     1232                IF ( k == 0 )  THEN
     1233                   shift_x = 0.5
     1234!           
     1235!--             u grid points
     1236                ELSEIF ( k == 1 )  THEN
     1237                   shift_x = 0.0
     1238!           
     1239!--             v grid points
     1240                ELSEIF ( k == 2 )  THEN
     1241                   shift_x = 0.5
     1242                ENDIF
     1243
     1244                netcdf_data = init_model%origin_x + cos_ra                     &
     1245                       * ( mask_i_global(mid,:mask_size(mid,1)) + shift_x ) * dx
     1246
     1247                nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
     1248                                        id_var_eutm_mask(mid,av,k), &
     1249                                        netcdf_data, start = (/ 1 /), &
     1250                                        count = (/ mask_size(mid,1) /) )
     1251                CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     1252
     1253             ENDDO
     1254             DEALLOCATE( netcdf_data )
     1255!
     1256!--          y coordinates
     1257             ALLOCATE( netcdf_data(mask_size(mid,2)) )
     1258             DO  k = 0, 2
     1259!
     1260!--             Scalar grid points
     1261                IF ( k == 0 )  THEN
     1262                   shift_y = 0.5
     1263!
     1264!--             u grid points
     1265                ELSEIF ( k == 1 )  THEN
     1266                   shift_y = 0.5
     1267!
     1268!--             v grid points
     1269                ELSEIF ( k == 2 )  THEN
     1270                   shift_y = 0.0
     1271                ENDIF
     1272
     1273                netcdf_data = init_model%origin_y + cos_ra                     &
     1274                       * ( mask_j_global(mid,:mask_size(mid,2)) + shift_y ) * dy
     1275
     1276                nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
     1277                                        id_var_nutm_mask(mid,av,k), &
     1278                                        netcdf_data, start = (/ 1 /), &
     1279                                        count = (/ mask_size(mid,2) /) )
     1280                CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     1281
     1282             ENDDO
     1283             DEALLOCATE( netcdf_data )
     1284
     1285          ELSE
     1286!
     1287!--          2D in case of rotation
     1288             ALLOCATE( netcdf_data_2d(mask_size(mid,1),mask_size(mid,2)) )
     1289             cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     1290             sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
     1291
     1292             DO  k = 0, 2
     1293!           
     1294!--            Scalar grid points
     1295               IF ( k == 0 )  THEN
     1296                  shift_x = 0.5 ; shift_y = 0.5
     1297!           
     1298!--            u grid points
     1299               ELSEIF ( k == 1 )  THEN
     1300                  shift_x = 0.0 ; shift_y = 0.5
     1301!           
     1302!--            v grid points
     1303               ELSEIF ( k == 2 )  THEN
     1304                  shift_x = 0.5 ; shift_y = 0.0
     1305               ENDIF
     1306
     1307               DO  j = 1, mask_size(mid,2)
     1308                  DO  i = 1, mask_size(mid,1)
     1309                     netcdf_data_2d(i,j) = init_model%origin_x                 &
     1310                           + cos_ra * ( mask_i_global(mid,i) + shift_x ) * dx  &
     1311                           + sin_ra * ( mask_j_global(mid,j) + shift_y ) * dy
     1312                  ENDDO
     1313               ENDDO
     1314
     1315               nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
     1316                                       id_var_eutm_mask(mid,av,k), &
     1317                                       netcdf_data_2d, start = (/ 1, 1 /), &
     1318                                       count = (/ mask_size(mid,1), &
     1319                                                  mask_size(mid,2) /) )
     1320               CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     1321
     1322               DO  j = 1, mask_size(mid,2)
     1323                  DO  i = 1, mask_size(mid,1)
     1324                     netcdf_data_2d(i,j) = init_model%origin_y                 &
     1325                           - sin_ra * ( mask_i_global(mid,i) + shift_x ) * dx  &
     1326                           + cos_ra * ( mask_j_global(mid,j) + shift_y ) * dy
     1327                  ENDDO
     1328               ENDDO
     1329             
     1330               nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), &
     1331                                       id_var_nutm_mask(mid,av,k), &
     1332                                       netcdf_data_2d, start = (/ 1, 1 /), &
     1333                                       count = (/ mask_size(mid,1), &
     1334                                                  mask_size(mid,2) /) )
     1335               CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     1336             
     1337             ENDDO
     1338             DEALLOCATE( netcdf_data_2d )
     1339          ENDIF
     1340
     1341!
    11461342!--       Write zu and zw data (vertical axes)
    11471343          ALLOCATE( netcdf_data(mask_size(mid,3)) )
     
    14561652                                  362, 363, 000 )
    14571653!
     1654!--       Define UTM coordinates
     1655          IF ( init_model%rotation_angle == 0.0_wp )  THEN
     1656             CALL netcdf_create_var( id_set_3d(av), &
     1657                                 (/ id_dim_x_3d(av) /),      &
     1658                                 'E_UTM', NF90_DOUBLE, id_var_eutm_3d(av,0),  &
     1659                                 'm', '', 000, 000, 000 )
     1660             CALL netcdf_create_var( id_set_3d(av), &
     1661                                 (/ id_dim_y_3d(av) /),      &
     1662                                 'N_UTM', NF90_DOUBLE, id_var_nutm_3d(av,0),  &
     1663                                 'm', '', 000, 000, 000 )
     1664             CALL netcdf_create_var( id_set_3d(av), &
     1665                                 (/ id_dim_xu_3d(av) /),     &
     1666                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_3d(av,1), &
     1667                                 'm', '', 000, 000, 000 )
     1668             CALL netcdf_create_var( id_set_3d(av), &
     1669                                 (/ id_dim_y_3d(av) /),     &
     1670                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_3d(av,1), &
     1671                                 'm', '', 000, 000, 000 )
     1672             CALL netcdf_create_var( id_set_3d(av), &
     1673                                 (/ id_dim_x_3d(av) /),     &
     1674                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_3d(av,2), &
     1675                                 'm', '', 000, 000, 000 )
     1676             CALL netcdf_create_var( id_set_3d(av), &
     1677                                 (/ id_dim_yv_3d(av) /),     &
     1678                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_3d(av,2), &
     1679                                 'm', '', 000, 000, 000 )
     1680          ELSE
     1681             CALL netcdf_create_var( id_set_3d(av), &
     1682                                 (/ id_dim_x_3d(av), id_dim_y_3d(av) /),      &
     1683                                 'E_UTM', NF90_DOUBLE, id_var_eutm_3d(av,0),  &
     1684                                 'm', '', 000, 000, 000 )
     1685             CALL netcdf_create_var( id_set_3d(av), &
     1686                                 (/ id_dim_x_3d(av), id_dim_y_3d(av) /),      &
     1687                                 'N_UTM', NF90_DOUBLE, id_var_nutm_3d(av,0),  &
     1688                                 'm', '', 000, 000, 000 )
     1689             CALL netcdf_create_var( id_set_3d(av), &
     1690                                 (/ id_dim_xu_3d(av), id_dim_y_3d(av) /),     &
     1691                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_3d(av,1), &
     1692                                 'm', '', 000, 000, 000 )
     1693             CALL netcdf_create_var( id_set_3d(av), &
     1694                                 (/ id_dim_xu_3d(av), id_dim_y_3d(av) /),     &
     1695                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_3d(av,1), &
     1696                                 'm', '', 000, 000, 000 )
     1697             CALL netcdf_create_var( id_set_3d(av), &
     1698                                 (/ id_dim_x_3d(av), id_dim_yv_3d(av) /),     &
     1699                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_3d(av,2), &
     1700                                 'm', '', 000, 000, 000 )
     1701             CALL netcdf_create_var( id_set_3d(av), &
     1702                                 (/ id_dim_x_3d(av), id_dim_yv_3d(av) /),     &
     1703                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_3d(av,2), &
     1704                                 'm', '', 000, 000, 000 )
     1705          ENDIF
     1706!
    14581707!--       In case of non-flat topography define 2d-arrays containing the height
    14591708!--       information. Only output 2d topography information in case of parallel
     
    15061755!
    15071756!--             Most variables are defined on the scalar grid
    1508                 CASE ( 'e', 'lpt', 'nc', 'nr', 'p', 'pc', 'pr', 'prr', 'pt',   &
     1757                CASE ( 'e', 'nc', 'nr', 'p', 'pc', 'pr', 'prr',   &
    15091758                       'q', 'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',   &
    1510                        'rho_ocean', 's', 'sa', 'vpt' )
     1759                       's', 'theta', 'thetal', 'thetav' )
    15111760
    15121761                   grid_x = 'x'
     
    15511800                      CALL lsm_define_netcdf_grid( do3d(av,i), found, grid_x,  &
    15521801                                                   grid_y, grid_z )
     1802                   ENDIF
     1803!
     1804!--                Check for ocean quantities
     1805                   IF ( .NOT. found  .AND.  ocean_mode )  THEN
     1806                      CALL ocean_define_netcdf_grid( do3d(av,i), found,  &
     1807                                                     grid_x, grid_y, grid_z )
    15531808                   ENDIF
    15541809
     
    17291984             DEALLOCATE( netcdf_data )
    17301985
     1986!
     1987!--          Write UTM coordinates
     1988             IF ( init_model%rotation_angle == 0.0_wp )  THEN
     1989!
     1990!--             1D in case of no rotation
     1991                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     1992!
     1993!--             x coordinates
     1994                ALLOCATE( netcdf_data(0:nx) )
     1995                DO  k = 0, 2
     1996!               
     1997!--                Scalar grid points
     1998                   IF ( k == 0 )  THEN
     1999                      shift_x = 0.5
     2000!               
     2001!--                u grid points
     2002                   ELSEIF ( k == 1 )  THEN
     2003                      shift_x = 0.0
     2004!               
     2005!--                v grid points
     2006                   ELSEIF ( k == 2 )  THEN
     2007                      shift_x = 0.5
     2008                   ENDIF
     2009               
     2010                   DO  i = 0, nx
     2011                     netcdf_data(i) = init_model%origin_x            &
     2012                                    + cos_ra * ( i + shift_x ) * dx
     2013                   ENDDO
     2014               
     2015                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(av,k),&
     2016                                           netcdf_data, start = (/ 1 /),   &
     2017                                           count = (/ nx+1 /) )
     2018                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     2019
     2020                ENDDO
     2021                DEALLOCATE( netcdf_data )
     2022!
     2023!--             y coordinates
     2024                ALLOCATE( netcdf_data(0:ny) )
     2025                DO  k = 0, 2
     2026!
     2027!--                Scalar grid points
     2028                   IF ( k == 0 )  THEN
     2029                      shift_y = 0.5
     2030!
     2031!--                u grid points
     2032                   ELSEIF ( k == 1 )  THEN
     2033                      shift_y = 0.5
     2034!
     2035!--                v grid points
     2036                   ELSEIF ( k == 2 )  THEN
     2037                      shift_y = 0.0
     2038                   ENDIF
     2039
     2040                   DO  j = 0, ny
     2041                      netcdf_data(j) = init_model%origin_y            &
     2042                                     + cos_ra * ( j + shift_y ) * dy
     2043                   ENDDO
     2044
     2045                   nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(av,k),&
     2046                                           netcdf_data, start = (/ 1 /),   &
     2047                                           count = (/ ny+1 /) )
     2048                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     2049
     2050                ENDDO
     2051                DEALLOCATE( netcdf_data )
     2052
     2053             ELSE
     2054!
     2055!--             2D in case of rotation
     2056                ALLOCATE( netcdf_data_2d(0:nx,0:ny) )
     2057                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     2058                sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
     2059               
     2060                DO  k = 0, 2
     2061!               
     2062!--               Scalar grid points
     2063                  IF ( k == 0 )  THEN
     2064                     shift_x = 0.5 ; shift_y = 0.5
     2065!               
     2066!--               u grid points
     2067                  ELSEIF ( k == 1 )  THEN
     2068                     shift_x = 0.0 ; shift_y = 0.5
     2069!               
     2070!--               v grid points
     2071                  ELSEIF ( k == 2 )  THEN
     2072                     shift_x = 0.5 ; shift_y = 0.0
     2073                  ENDIF
     2074               
     2075                  DO  j = 0, ny
     2076                     DO  i = 0, nx
     2077                        netcdf_data_2d(i,j) = init_model%origin_x            &
     2078                                            + cos_ra * ( i + shift_x ) * dx  &
     2079                                            + sin_ra * ( j + shift_y ) * dy
     2080                     ENDDO
     2081                  ENDDO
     2082               
     2083                  nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(av,k),  &
     2084                                          netcdf_data_2d, start = (/ 1, 1 /),   &
     2085                                          count = (/ nx+1, ny+1 /) )
     2086                  CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     2087               
     2088                  DO  j = 0, ny
     2089                     DO  i = 0, nx
     2090                        netcdf_data_2d(i,j) = init_model%origin_y            &
     2091                                            - sin_ra * ( i + shift_x ) * dx  &
     2092                                            + cos_ra * ( j + shift_y ) * dy
     2093                     ENDDO
     2094                  ENDDO
     2095               
     2096                  nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(av,k),  &
     2097                                          netcdf_data_2d, start = (/ 1, 1 /),   &
     2098                                          count = (/ nx+1, ny+1 /) )
     2099                  CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     2100               
     2101                ENDDO
     2102                DEALLOCATE( netcdf_data_2d )
     2103             ENDIF
    17312104!
    17322105!--          Write zu and zw data (vertical axes)
     
    22422615                                  365, 366, 000 )
    22432616!
     2617!--       Define UTM coordinates
     2618          IF ( init_model%rotation_angle == 0.0_wp )  THEN
     2619             CALL netcdf_create_var( id_set_xy(av), &
     2620                                 (/ id_dim_x_xy(av) /),      &
     2621                                 'E_UTM', NF90_DOUBLE, id_var_eutm_xy(av,0),  &
     2622                                 'm', '', 000, 000, 000 )
     2623             CALL netcdf_create_var( id_set_xy(av), &
     2624                                 (/ id_dim_y_xy(av) /),      &
     2625                                 'N_UTM', NF90_DOUBLE, id_var_nutm_xy(av,0),  &
     2626                                 'm', '', 000, 000, 000 )
     2627             CALL netcdf_create_var( id_set_xy(av), &
     2628                                 (/ id_dim_xu_xy(av) /),     &
     2629                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_xy(av,1), &
     2630                                 'm', '', 000, 000, 000 )
     2631             CALL netcdf_create_var( id_set_xy(av), &
     2632                                 (/ id_dim_y_xy(av) /),     &
     2633                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_xy(av,1), &
     2634                                 'm', '', 000, 000, 000 )
     2635             CALL netcdf_create_var( id_set_xy(av), &
     2636                                 (/ id_dim_x_xy(av) /),     &
     2637                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_xy(av,2), &
     2638                                 'm', '', 000, 000, 000 )
     2639             CALL netcdf_create_var( id_set_xy(av), &
     2640                                 (/ id_dim_yv_xy(av) /),     &
     2641                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_xy(av,2), &
     2642                                 'm', '', 000, 000, 000 )
     2643          ELSE
     2644             CALL netcdf_create_var( id_set_xy(av), &
     2645                                 (/ id_dim_x_xy(av), id_dim_y_xy(av) /),      &
     2646                                 'E_UTM', NF90_DOUBLE, id_var_eutm_xy(av,0),  &
     2647                                 'm', '', 000, 000, 000 )
     2648             CALL netcdf_create_var( id_set_xy(av), &
     2649                                 (/ id_dim_x_xy(av), id_dim_y_xy(av) /),      &
     2650                                 'N_UTM', NF90_DOUBLE, id_var_nutm_xy(av,0),  &
     2651                                 'm', '', 000, 000, 000 )
     2652             CALL netcdf_create_var( id_set_xy(av), &
     2653                                 (/ id_dim_xu_xy(av), id_dim_y_xy(av) /),     &
     2654                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_xy(av,1), &
     2655                                 'm', '', 000, 000, 000 )
     2656             CALL netcdf_create_var( id_set_xy(av), &
     2657                                 (/ id_dim_xu_xy(av), id_dim_y_xy(av) /),     &
     2658                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_xy(av,1), &
     2659                                 'm', '', 000, 000, 000 )
     2660             CALL netcdf_create_var( id_set_xy(av), &
     2661                                 (/ id_dim_x_xy(av), id_dim_yv_xy(av) /),     &
     2662                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_xy(av,2), &
     2663                                 'm', '', 000, 000, 000 )
     2664             CALL netcdf_create_var( id_set_xy(av), &
     2665                                 (/ id_dim_x_xy(av), id_dim_yv_xy(av) /),     &
     2666                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_xy(av,2), &
     2667                                 'm', '', 000, 000, 000 )
     2668          ENDIF
     2669!
    22442670!--       In case of non-flat topography define 2d-arrays containing the height
    22452671!--       information. Only for parallel netcdf output.
     
    22892715!
    22902716!--                   Most variables are defined on the zu grid
    2291                       CASE ( 'e_xy', 'lpt_xy', 'nc_xy', 'nr_xy', 'p_xy',       &
    2292                              'pc_xy', 'pr_xy', 'prr_xy', 'pt_xy', 'q_xy',      &
     2717                      CASE ( 'e_xy', 'nc_xy', 'nr_xy', 'p_xy',                 &
     2718                             'pc_xy', 'pr_xy', 'prr_xy', 'q_xy',               &
    22932719                             'qc_xy', 'ql_xy', 'ql_c_xy', 'ql_v_xy',           &
    2294                              'ql_vp_xy', 'qr_xy', 'qv_xy', 'rho_ocean_xy',     &
    2295                              's_xy', 'sa_xy', 'vpt_xy' )
     2720                             'ql_vp_xy', 'qr_xy', 'qv_xy',                     &
     2721                             's_xy',                                           &
     2722                             'theta_xy', 'thetal_xy', 'thetav_xy' )
    22962723
    22972724                         grid_x = 'x'
     
    23352762                         ENDIF
    23362763
     2764!
     2765!--                      Check for ocean quantities
     2766                         IF ( .NOT. found  .AND.  ocean_mode )  THEN
     2767                            CALL ocean_define_netcdf_grid( do2d(av,i), found,  &
     2768                                                           grid_x, grid_y,     &
     2769                                                           grid_z )
     2770                         ENDIF
    23372771!
    23382772!--                      Check for radiation quantities
     
    25913025
    25923026             DEALLOCATE( netcdf_data )
    2593 
    2594           ENDIF
    2595 
     3027!
     3028!--          Write UTM coordinates
     3029             IF ( init_model%rotation_angle == 0.0_wp )  THEN
     3030!
     3031!--             1D in case of no rotation
     3032                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     3033!
     3034!--             x coordinates
     3035                ALLOCATE( netcdf_data(0:nx) )
     3036                DO  k = 0, 2
     3037!               
     3038!--                Scalar grid points
     3039                   IF ( k == 0 )  THEN
     3040                      shift_x = 0.5
     3041!               
     3042!--                u grid points
     3043                   ELSEIF ( k == 1 )  THEN
     3044                      shift_x = 0.0
     3045!               
     3046!--                v grid points
     3047                   ELSEIF ( k == 2 )  THEN
     3048                      shift_x = 0.5
     3049                   ENDIF
     3050               
     3051                   DO  i = 0, nx
     3052                     netcdf_data(i) = init_model%origin_x            &
     3053                                    + cos_ra * ( i + shift_x ) * dx
     3054                   ENDDO
     3055               
     3056                   nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(av,k),&
     3057                                           netcdf_data, start = (/ 1 /),   &
     3058                                           count = (/ nx+1 /) )
     3059                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     3060
     3061                ENDDO
     3062                DEALLOCATE( netcdf_data )
     3063!
     3064!--             y coordinates
     3065                ALLOCATE( netcdf_data(0:ny) )
     3066                DO  k = 0, 2
     3067!
     3068!--                Scalar grid points
     3069                   IF ( k == 0 )  THEN
     3070                      shift_y = 0.5
     3071!
     3072!--                u grid points
     3073                   ELSEIF ( k == 1 )  THEN
     3074                      shift_y = 0.5
     3075!
     3076!--                v grid points
     3077                   ELSEIF ( k == 2 )  THEN
     3078                      shift_y = 0.0
     3079                   ENDIF
     3080
     3081                   DO  j = 0, ny
     3082                      netcdf_data(j) = init_model%origin_y            &
     3083                                     + cos_ra * ( j + shift_y ) * dy
     3084                   ENDDO
     3085
     3086                   nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(av,k),&
     3087                                           netcdf_data, start = (/ 1 /),   &
     3088                                           count = (/ ny+1 /) )
     3089                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     3090
     3091                ENDDO
     3092                DEALLOCATE( netcdf_data )
     3093
     3094             ELSE
     3095!
     3096!--             2D in case of rotation
     3097                ALLOCATE( netcdf_data_2d(0:nx,0:ny) )
     3098                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     3099                sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
     3100               
     3101                DO  k = 0, 2
     3102!               
     3103!--               Scalar grid points
     3104                  IF ( k == 0 )  THEN
     3105                     shift_x = 0.5 ; shift_y = 0.5
     3106!               
     3107!--               u grid points
     3108                  ELSEIF ( k == 1 )  THEN
     3109                     shift_x = 0.0 ; shift_y = 0.5
     3110!               
     3111!--               v grid points
     3112                  ELSEIF ( k == 2 )  THEN
     3113                     shift_x = 0.5 ; shift_y = 0.0
     3114                  ENDIF
     3115               
     3116                  DO  j = 0, ny
     3117                     DO  i = 0, nx
     3118                        netcdf_data_2d(i,j) = init_model%origin_x            &
     3119                                            + cos_ra * ( i + shift_x ) * dx  &
     3120                                            + sin_ra * ( j + shift_y ) * dy
     3121                     ENDDO
     3122                  ENDDO
     3123               
     3124                  nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(av,k),  &
     3125                                          netcdf_data_2d, start = (/ 1, 1 /),   &
     3126                                          count = (/ nx+1, ny+1 /) )
     3127                  CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     3128               
     3129                  DO  j = 0, ny
     3130                     DO  i = 0, nx
     3131                        netcdf_data_2d(i,j) = init_model%origin_y            &
     3132                                            - sin_ra * ( i + shift_x ) * dx  &
     3133                                            + cos_ra * ( j + shift_y ) * dy
     3134                     ENDDO
     3135                  ENDDO
     3136               
     3137                  nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(av,k),  &
     3138                                          netcdf_data_2d, start = (/ 1, 1 /),   &
     3139                                          count = (/ nx+1, ny+1 /) )
     3140                  CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     3141               
     3142                ENDDO
     3143                DEALLOCATE( netcdf_data_2d )
     3144             ENDIF
     3145
     3146          ENDIF
    25963147!
    25973148!--       In case of non-flat topography write height information. Only for
     
    29853536                                  NF90_DOUBLE, id_var_zw_xz(av), 'meters', '', &
    29863537                                  157, 158, 000 )
     3538!
     3539!--       Define UTM coordinates
     3540          IF ( init_model%rotation_angle == 0.0_wp )  THEN
     3541             CALL netcdf_create_var( id_set_xz(av), &
     3542                                 (/ id_dim_x_xz(av) /),      &
     3543                                 'E_UTM', NF90_DOUBLE, id_var_eutm_xz(av,0),  &
     3544                                 'm', '', 000, 000, 000 )
     3545             CALL netcdf_create_var( id_set_xz(av), &
     3546                                 (/ id_dim_y_xz(av) /),      &
     3547                                 'N_UTM', NF90_DOUBLE, id_var_nutm_xz(av,0),  &
     3548                                 'm', '', 000, 000, 000 )
     3549             CALL netcdf_create_var( id_set_xz(av), &
     3550                                 (/ id_dim_xu_xz(av) /),     &
     3551                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_xz(av,1), &
     3552                                 'm', '', 000, 000, 000 )
     3553             CALL netcdf_create_var( id_set_xz(av), &
     3554                                 (/ id_dim_y_xz(av) /),     &
     3555                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_xz(av,1), &
     3556                                 'm', '', 000, 000, 000 )
     3557             CALL netcdf_create_var( id_set_xz(av), &
     3558                                 (/ id_dim_x_xz(av) /),     &
     3559                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_xz(av,2), &
     3560                                 'm', '', 000, 000, 000 )
     3561             CALL netcdf_create_var( id_set_xz(av), &
     3562                                 (/ id_dim_yv_xz(av) /),     &
     3563                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_xz(av,2), &
     3564                                 'm', '', 000, 000, 000 )
     3565          ELSE
     3566             CALL netcdf_create_var( id_set_xz(av), &
     3567                                 (/ id_dim_x_xz(av), id_dim_y_xz(av) /),      &
     3568                                 'E_UTM', NF90_DOUBLE, id_var_eutm_xz(av,0),  &
     3569                                 'm', '', 000, 000, 000 )
     3570             CALL netcdf_create_var( id_set_xz(av), &
     3571                                 (/ id_dim_x_xz(av), id_dim_y_xz(av) /),      &
     3572                                 'N_UTM', NF90_DOUBLE, id_var_nutm_xz(av,0),  &
     3573                                 'm', '', 000, 000, 000 )
     3574             CALL netcdf_create_var( id_set_xz(av), &
     3575                                 (/ id_dim_xu_xz(av), id_dim_y_xz(av) /),     &
     3576                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_xz(av,1), &
     3577                                 'm', '', 000, 000, 000 )
     3578             CALL netcdf_create_var( id_set_xz(av), &
     3579                                 (/ id_dim_xu_xz(av), id_dim_y_xz(av) /),     &
     3580                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_xz(av,1), &
     3581                                 'm', '', 000, 000, 000 )
     3582             CALL netcdf_create_var( id_set_xz(av), &
     3583                                 (/ id_dim_x_xz(av), id_dim_yv_xz(av) /),     &
     3584                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_xz(av,2), &
     3585                                 'm', '', 000, 000, 000 )
     3586             CALL netcdf_create_var( id_set_xz(av), &
     3587                                 (/ id_dim_x_xz(av), id_dim_yv_xz(av) /),     &
     3588                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_xz(av,2), &
     3589                                 'm', '', 000, 000, 000 )
     3590          ENDIF
    29873591
    29883592          IF ( land_surface )  THEN
     
    30113615!
    30123616!--                Most variables are defined on the zu grid
    3013                    CASE ( 'e_xz', 'lpt_xz', 'nc_xz', 'nr_xz', 'p_xz', 'pc_xz', &
    3014                           'pr_xz', 'prr_xz', 'pt_xz', 'q_xz', 'qc_xz',         &
     3617                   CASE ( 'e_xz', 'nc_xz', 'nr_xz', 'p_xz', 'pc_xz',          &
     3618                          'pr_xz', 'prr_xz', 'q_xz', 'qc_xz',                  &
    30153619                          'ql_xz', 'ql_c_xz', 'ql_v_xz', 'ql_vp_xz', 'qr_xz',  &
    3016                           'qv_xz', 'rho_ocean_xz', 's_xz', 'sa_xz', 'vpt_xz' )
     3620                          'qv_xz', 's_xz',                                     &
     3621                          'theta_xz', 'thetal_xz', 'thetav_xz'                 )
    30173622
    30183623                      grid_x = 'x'
     
    30553660                      ENDIF
    30563661
     3662!
     3663!--                   Check for ocean quantities
     3664                      IF ( .NOT. found  .AND.  ocean_mode )  THEN
     3665                         CALL ocean_define_netcdf_grid( do2d(av,i), found,  &
     3666                                                        grid_x, grid_y, grid_z )
     3667                      ENDIF
    30573668!
    30583669!--                   Check for radiation quantities
     
    32943905             ENDIF
    32953906
    3296 
    32973907             DEALLOCATE( netcdf_data )
     3908!
     3909!--          Write UTM coordinates
     3910             IF ( init_model%rotation_angle == 0.0_wp )  THEN
     3911!
     3912!--             1D in case of no rotation
     3913                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     3914!
     3915!--             x coordinates
     3916                ALLOCATE( netcdf_data(0:nx) )
     3917                DO  k = 0, 2
     3918!               
     3919!--                Scalar grid points
     3920                   IF ( k == 0 )  THEN
     3921                      shift_x = 0.5
     3922!               
     3923!--                u grid points
     3924                   ELSEIF ( k == 1 )  THEN
     3925                      shift_x = 0.0
     3926!               
     3927!--                v grid points
     3928                   ELSEIF ( k == 2 )  THEN
     3929                      shift_x = 0.5
     3930                   ENDIF
     3931               
     3932                   DO  i = 0, nx
     3933                     netcdf_data(i) = init_model%origin_x            &
     3934                                    + cos_ra * ( i + shift_x ) * dx
     3935                   ENDDO
     3936               
     3937                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(av,k),&
     3938                                           netcdf_data, start = (/ 1 /),   &
     3939                                           count = (/ nx+1 /) )
     3940                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     3941
     3942                ENDDO
     3943                DEALLOCATE( netcdf_data )
     3944!
     3945!--             y coordinates
     3946                ALLOCATE( netcdf_data(1:ns) )
     3947                DO  k = 0, 2
     3948!
     3949!--                Scalar grid points
     3950                   IF ( k == 0 )  THEN
     3951                      shift_y = 0.5
     3952!
     3953!--                u grid points
     3954                   ELSEIF ( k == 1 )  THEN
     3955                      shift_y = 0.5
     3956!
     3957!--                v grid points
     3958                   ELSEIF ( k == 2 )  THEN
     3959                      shift_y = 0.0
     3960                   ENDIF
     3961
     3962                   DO  i = 1, ns
     3963                      IF( section(i,2) == -1 )  THEN
     3964                         netcdf_data(i) = -1.0_wp  ! section averaged along y
     3965                      ELSE
     3966                         netcdf_data(i) = init_model%origin_y &
     3967                                     + cos_ra * ( section(i,2) + shift_y ) * dy
     3968                      ENDIF
     3969                   ENDDO
     3970
     3971                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_nutm_xz(av,k),&
     3972                                           netcdf_data, start = (/ 1 /),   &
     3973                                           count = (/ ns /) )
     3974                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     3975
     3976                ENDDO
     3977                DEALLOCATE( netcdf_data )
     3978
     3979             ELSE
     3980!
     3981!--             2D in case of rotation
     3982                ALLOCATE( netcdf_data_2d(0:nx,1:ns) )
     3983                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     3984                sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
     3985               
     3986                DO  k = 0, 2
     3987!               
     3988!--                Scalar grid points
     3989                   IF ( k == 0 )  THEN
     3990                      shift_x = 0.5 ; shift_y = 0.5
     3991!                 
     3992!--                u grid points
     3993                   ELSEIF ( k == 1 )  THEN
     3994                      shift_x = 0.0 ; shift_y = 0.5
     3995!                 
     3996!--                v grid points
     3997                   ELSEIF ( k == 2 )  THEN
     3998                      shift_x = 0.5 ; shift_y = 0.0
     3999                   ENDIF
     4000
     4001                   DO  j = 1, ns
     4002                      IF( section(j,2) == -1 )  THEN
     4003                         netcdf_data_2d(:,j) = -1.0_wp  ! section averaged along y
     4004                      ELSE
     4005                         DO  i = 0, nx
     4006                            netcdf_data_2d(i,j) = init_model%origin_x          &
     4007                                    + cos_ra * ( i + shift_x ) * dx            &
     4008                                    + sin_ra * ( section(j,2) + shift_y ) * dy
     4009                         ENDDO
     4010                      ENDIF
     4011                   ENDDO
     4012                   
     4013                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(av,k),  &
     4014                                           netcdf_data_2d, start = (/ 1, 1 /),   &
     4015                                           count = (/ nx+1, ns /) )
     4016                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     4017                   
     4018                   DO  j = 1, ns
     4019                      IF( section(j,2) == -1 )  THEN
     4020                         netcdf_data_2d(:,j) = -1.0_wp  ! section averaged along y
     4021                      ELSE
     4022                         DO  i = 0, nx
     4023                            netcdf_data_2d(i,j) = init_model%origin_y          &
     4024                                    - sin_ra * ( i + shift_x ) * dx            &
     4025                                    + cos_ra * ( section(j,2) + shift_y ) * dy
     4026                         ENDDO
     4027                      ENDIF
     4028                   ENDDO
     4029                   
     4030                   nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_nutm_xz(av,k),  &
     4031                                           netcdf_data_2d, start = (/ 1, 1 /),   &
     4032                                           count = (/ nx+1, ns /) )
     4033                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     4034               
     4035                ENDDO
     4036                DEALLOCATE( netcdf_data_2d )
     4037             ENDIF
    32984038
    32994039          ENDIF
     
    36544394                                  NF90_DOUBLE, id_var_zw_yz(av), 'meters', '', &
    36554395                                  196, 197, 000 )
     4396!
     4397!--       Define UTM coordinates
     4398          IF ( init_model%rotation_angle == 0.0_wp )  THEN
     4399             CALL netcdf_create_var( id_set_yz(av), &
     4400                                 (/ id_dim_x_yz(av) /),      &
     4401                                 'E_UTM', NF90_DOUBLE, id_var_eutm_yz(av,0),  &
     4402                                 'm', '', 000, 000, 000 )
     4403             CALL netcdf_create_var( id_set_yz(av), &
     4404                                 (/ id_dim_y_yz(av) /),      &
     4405                                 'N_UTM', NF90_DOUBLE, id_var_nutm_yz(av,0),  &
     4406                                 'm', '', 000, 000, 000 )
     4407             CALL netcdf_create_var( id_set_yz(av), &
     4408                                 (/ id_dim_xu_yz(av) /),     &
     4409                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_yz(av,1), &
     4410                                 'm', '', 000, 000, 000 )
     4411             CALL netcdf_create_var( id_set_yz(av), &
     4412                                 (/ id_dim_y_yz(av) /),     &
     4413                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_yz(av,1), &
     4414                                 'm', '', 000, 000, 000 )
     4415             CALL netcdf_create_var( id_set_yz(av), &
     4416                                 (/ id_dim_x_yz(av) /),     &
     4417                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_yz(av,2), &
     4418                                 'm', '', 000, 000, 000 )
     4419             CALL netcdf_create_var( id_set_yz(av), &
     4420                                 (/ id_dim_yv_yz(av) /),     &
     4421                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_yz(av,2), &
     4422                                 'm', '', 000, 000, 000 )
     4423          ELSE
     4424             CALL netcdf_create_var( id_set_yz(av), &
     4425                                 (/ id_dim_x_yz(av), id_dim_y_yz(av) /),      &
     4426                                 'E_UTM', NF90_DOUBLE, id_var_eutm_yz(av,0),  &
     4427                                 'm', '', 000, 000, 000 )
     4428             CALL netcdf_create_var( id_set_yz(av), &
     4429                                 (/ id_dim_x_yz(av), id_dim_y_yz(av) /),      &
     4430                                 'N_UTM', NF90_DOUBLE, id_var_nutm_yz(av,0),  &
     4431                                 'm', '', 000, 000, 000 )
     4432             CALL netcdf_create_var( id_set_yz(av), &
     4433                                 (/ id_dim_xu_yz(av), id_dim_y_yz(av) /),     &
     4434                                 'Eu_UTM', NF90_DOUBLE, id_var_eutm_yz(av,1), &
     4435                                 'm', '', 000, 000, 000 )
     4436             CALL netcdf_create_var( id_set_yz(av), &
     4437                                 (/ id_dim_xu_yz(av), id_dim_y_yz(av) /),     &
     4438                                 'Nu_UTM', NF90_DOUBLE, id_var_nutm_yz(av,1), &
     4439                                 'm', '', 000, 000, 000 )
     4440             CALL netcdf_create_var( id_set_yz(av), &
     4441                                 (/ id_dim_x_yz(av), id_dim_yv_yz(av) /),     &
     4442                                 'Ev_UTM', NF90_DOUBLE, id_var_eutm_yz(av,2), &
     4443                                 'm', '', 000, 000, 000 )
     4444             CALL netcdf_create_var( id_set_yz(av), &
     4445                                 (/ id_dim_x_yz(av), id_dim_yv_yz(av) /),     &
     4446                                 'Nv_UTM', NF90_DOUBLE, id_var_nutm_yz(av,2), &
     4447                                 'm', '', 000, 000, 000 )
     4448          ENDIF
    36564449
    36574450          IF ( land_surface )  THEN
     
    36804473!
    36814474!--                Most variables are defined on the zu grid
    3682                    CASE ( 'e_yz', 'lpt_yz', 'nc_yz', 'nr_yz', 'p_yz', 'pc_yz', &
    3683                           'pr_yz','prr_yz', 'pt_yz', 'q_yz', 'qc_yz', 'ql_yz', &
     4475                   CASE ( 'e_yz', 'nc_yz', 'nr_yz', 'p_yz', 'pc_yz',          &
     4476                          'pr_yz','prr_yz', 'q_yz', 'qc_yz', 'ql_yz',          &
    36844477                          'ql_c_yz', 'ql_v_yz', 'ql_vp_yz', 'qr_yz', 'qv_yz',  &
    3685                           'rho_ocean_yz', 's_yz', 'sa_yz', 'vpt_yz' )
     4478                          's_yz',                                              &
     4479                          'theta_yz', 'thetal_yz', 'thetav_yz' )
    36864480
    36874481                      grid_x = 'x'
     
    37244518                      ENDIF
    37254519
     4520!
     4521!--                   Check for ocean quantities
     4522                      IF ( .NOT. found  .AND.  ocean_mode )  THEN
     4523                         CALL ocean_define_netcdf_grid( do2d(av,i), found,     &
     4524                                                       grid_x, grid_y, grid_z )
     4525                      ENDIF
    37264526!
    37274527!--                   Check for radiation quantities
     
    39514751
    39524752             DEALLOCATE( netcdf_data )
     4753!
     4754!--          Write UTM coordinates
     4755             IF ( init_model%rotation_angle == 0.0_wp )  THEN
     4756!
     4757!--             1D in case of no rotation
     4758                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     4759!
     4760!--             x coordinates
     4761                ALLOCATE( netcdf_data(1:ns) )
     4762                DO  k = 0, 2
     4763!               
     4764!--                Scalar grid points
     4765                   IF ( k == 0 )  THEN
     4766                      shift_x = 0.5
     4767!               
     4768!--                u grid points
     4769                   ELSEIF ( k == 1 )  THEN
     4770                      shift_x = 0.0
     4771!               
     4772!--                v grid points
     4773                   ELSEIF ( k == 2 )  THEN
     4774                      shift_x = 0.5
     4775                   ENDIF
     4776               
     4777                   DO  i = 1, ns
     4778                      IF( section(i,3) == -1 )  THEN
     4779                         netcdf_data(i) = -1.0_wp  ! section averaged along x
     4780                      ELSE
     4781                         netcdf_data(i) = init_model%origin_x &
     4782                                     + cos_ra * ( section(i,3) + shift_x ) * dx
     4783                      ENDIF
     4784                   ENDDO
     4785               
     4786                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_eutm_yz(av,k),&
     4787                                           netcdf_data, start = (/ 1 /),   &
     4788                                           count = (/ ns /) )
     4789                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     4790
     4791                ENDDO
     4792                DEALLOCATE( netcdf_data )
     4793!
     4794!--             y coordinates
     4795                ALLOCATE( netcdf_data(0:ny) )
     4796                DO  k = 0, 2
     4797!
     4798!--                Scalar grid points
     4799                   IF ( k == 0 )  THEN
     4800                      shift_y = 0.5
     4801!
     4802!--                u grid points
     4803                   ELSEIF ( k == 1 )  THEN
     4804                      shift_y = 0.5
     4805!
     4806!--                v grid points
     4807                   ELSEIF ( k == 2 )  THEN
     4808                      shift_y = 0.0
     4809                   ENDIF
     4810
     4811                   DO  i = 0, ny
     4812                     netcdf_data(i) = init_model%origin_y            &
     4813                                    + cos_ra * ( i + shift_y ) * dy
     4814                   ENDDO
     4815
     4816                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_nutm_yz(av,k),&
     4817                                           netcdf_data, start = (/ 1 /),   &
     4818                                           count = (/ ny+1 /) )
     4819                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     4820
     4821                ENDDO
     4822                DEALLOCATE( netcdf_data )
     4823
     4824             ELSE
     4825!
     4826!--             2D in case of rotation
     4827                ALLOCATE( netcdf_data_2d(1:ns,0:ny) )
     4828                cos_ra = COS( init_model%rotation_angle * pi / 180.0_wp )
     4829                sin_ra = SIN( init_model%rotation_angle * pi / 180.0_wp )
     4830
     4831                DO  k = 0, 2
     4832!               
     4833!--                Scalar grid points
     4834                   IF ( k == 0 )  THEN
     4835                      shift_x = 0.5 ; shift_y = 0.5
     4836!                 
     4837!--                u grid points
     4838                   ELSEIF ( k == 1 )  THEN
     4839                      shift_x = 0.0 ; shift_y = 0.5
     4840!                 
     4841!--                v grid points
     4842                   ELSEIF ( k == 2 )  THEN
     4843                      shift_x = 0.5 ; shift_y = 0.0
     4844                   ENDIF
     4845
     4846                   DO  j = 0, ny
     4847                      DO  i = 1, ns
     4848                         IF( section(i,3) == -1 )  THEN
     4849                            netcdf_data_2d(i,:) = -1.0_wp !section averaged along x
     4850                         ELSE
     4851                            netcdf_data_2d(i,j) = init_model%origin_x          &
     4852                                    + cos_ra * ( section(i,3) + shift_x ) * dx &
     4853                                    + sin_ra * ( j + shift_y ) * dy
     4854                         ENDIF
     4855                      ENDDO
     4856                   ENDDO
     4857                   
     4858                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_eutm_yz(av,k),  &
     4859                                           netcdf_data_2d, start = (/ 1, 1 /),   &
     4860                                           count = (/ ns, ny+1 /) )
     4861                   CALL netcdf_handle_error( 'netcdf_define_header', 555 )
     4862                   
     4863                   DO  j = 0, ny
     4864                      DO  i = 1, ns
     4865                         IF( section(i,3) == -1 )  THEN
     4866                            netcdf_data_2d(i,:) = -1.0_wp !section averaged along x
     4867                         ELSE
     4868                            netcdf_data_2d(i,j) = init_model%origin_y          &
     4869                                    - sin_ra * ( section(i,3) + shift_x ) * dx &
     4870                                    + cos_ra * ( j + shift_y ) * dy
     4871                         ENDIF
     4872                      ENDDO
     4873                   ENDDO
     4874
     4875                   nc_stat = NF90_PUT_VAR( id_set_yz(av), id_var_nutm_yz(av,k),  &
     4876                                           netcdf_data_2d, start = (/ 1, 1 /),   &
     4877                                           count = (/ ns, ny+1 /) )
     4878                   CALL netcdf_handle_error( 'netcdf_define_header', 556 )
     4879               
     4880                ENDDO
     4881                DEALLOCATE( netcdf_data_2d )
     4882             ENDIF
    39534883
    39544884          ENDIF
     
    48715801!
    48725802!--             Most variables are defined on the zu levels
    4873                 CASE ( 'e', 'lpt', 'nc', 'nr', 'p', 'pc', 'pr', 'prr', 'pt',   &
     5803                CASE ( 'e', 'nc', 'nr', 'p', 'pc', 'pr', 'prr',   &
    48745804                       'q', 'qc', 'ql', 'ql_c', 'ql_v', 'ql_vp', 'qr', 'qv',   &
    4875                        'rho_ocean', 's', 'sa', 'u', 'v', 'vpt' )
     5805                       'rho_sea_water', 's', 'sa', &
     5806                       'theta', 'thetal', 'thetav', 'u', 'v' )
    48765807
    48775808                   grid_z = 'zu'
Note: See TracChangeset for help on using the changeset viewer.