Ignore:
Timestamp:
May 30, 2017 5:47:52 PM (7 years ago)
Author:
suehring
Message:

Adjustments according new topography and surface-modelling concept implemented

File:
1 edited

Legend:

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

    r2210 r2232  
    2020! Current revisions:
    2121! ------------------
     22! Adjustments to new topography and surface concept
    2223!
    23 !
     24! Topograpyh height arrays (zu_s_inner, zw_w_inner) are defined locally, output
     25! only if parallel netcdf.
     26!
     27! Build interface for topography input:
     28! - open file in read-only mode
     29! - read global attributes
     30! - read variables
     31!
     32! Bugfix in xy output (land-surface case)
     33!
    2434! Former revisions:
    2535! -----------------
     
    198208 MODULE netcdf_interface
    199209
    200     USE control_parameters, ONLY: max_masks, fl_max, var_fl_max, varnamelength
     210    USE control_parameters,                                                    &
     211        ONLY:  max_masks, fl_max, var_fl_max, varnamelength
    201212    USE kinds
    202213#if defined( __netcdf )
     
    397408    END INTERFACE netcdf_create_dim
    398409
     410    INTERFACE netcdf_close_file
     411       MODULE PROCEDURE netcdf_close_file
     412    END INTERFACE netcdf_close_file
     413
    399414    INTERFACE netcdf_create_file
    400415       MODULE PROCEDURE netcdf_create_file
     
    409424    END INTERFACE netcdf_define_header
    410425
     426    INTERFACE netcdf_get_attribute
     427       MODULE PROCEDURE netcdf_get_attribute
     428    END INTERFACE netcdf_get_attribute
     429
     430    INTERFACE netcdf_get_variable
     431       MODULE PROCEDURE netcdf_get_variable_2d
     432       MODULE PROCEDURE netcdf_get_variable_3d
     433    END INTERFACE netcdf_get_variable
     434
    411435    INTERFACE netcdf_handle_error
    412436       MODULE PROCEDURE netcdf_handle_error
    413437    END INTERFACE netcdf_handle_error
    414438
     439    INTERFACE netcdf_open_read_file
     440       MODULE PROCEDURE netcdf_open_read_file
     441    END INTERFACE netcdf_open_read_file
     442
    415443    INTERFACE netcdf_open_write_file
    416444       MODULE PROCEDURE netcdf_open_write_file
    417445    END INTERFACE netcdf_open_write_file
    418446
    419     PUBLIC netcdf_create_file, netcdf_define_header, netcdf_handle_error,      &
    420            netcdf_open_write_file
     447    PUBLIC netcdf_create_file, netcdf_close_file, netcdf_define_header,        &
     448           netcdf_handle_error, netcdf_get_attribute, netcdf_get_variable,     &
     449           netcdf_open_read_file, netcdf_open_write_file
    421450
    422451 CONTAINS
     
    434463    USE control_parameters,                                                    &
    435464        ONLY:  averaging_interval, averaging_interval_pr,                      &
    436                data_output_pr,  domask,  dopr_n,        &
     465               data_output_pr, domask, dopr_n,                                 &
    437466               dopr_time_count, dopts_time_count, dots_time_count,             &
    438                do2d, do2d_xz_time_count, do3d,                &
     467               do2d, do2d_xz_time_count, do3d,                                 &
    439468               do2d_yz_time_count, dt_data_output_av, dt_do2d_xy, dt_do2d_xz,  &
    440469               dt_do2d_yz, dt_do3d, mask_size, do2d_xy_time_count,             &
    441                do3d_time_count, domask_time_count, end_time, mask_i_global,    &
    442                mask_j_global, mask_k_global, message_string, mid, ntdim_2d_xy, &
     470               do3d_time_count, domask_time_count, end_time, land_surface,     &
     471               lod, mask_size_l, mask_i, mask_i_global, mask_j, mask_j_global, &
     472               mask_k_global, message_string, mid, ntdim_2d_xy,                &
    443473               ntdim_2d_xz, ntdim_2d_yz, ntdim_3d, nz_do3d, prt_time_count,    &
    444474               run_description_header, section, simulated_time,                &
     
    452482
    453483    USE indices,                                                               &
    454         ONLY:  nx, ny, nz ,nzb, nzt
     484        ONLY:  nx, nxl, nxr, ny, nys, nyn, nz ,nzb, nzt
    455485
    456486    USE kinds
    457487
    458488    USE land_surface_model_mod,                                                &
    459         ONLY: land_surface, lsm_define_netcdf_grid, nzb_soil, nzt_soil, nzs, zs
     489        ONLY: lsm_define_netcdf_grid, nzb_soil, nzt_soil, nzs, zs
    460490
    461491    USE pegrid
     
    750780!
    751781!--       In case of non-flat topography define 2d-arrays containing the height
    752 !--       information
    753           IF ( TRIM( topography ) /= 'flat' )  THEN
     782!--       information. Only for parallel netcdf output.
     783          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
     784               netcdf_data_format > 4 )  THEN
    754785!
    755786!--          Define zusi = zu(nzb_s_inner)
     
    9921023!
    9931024!--       In case of non-flat topography write height information
    994           IF ( TRIM( topography ) /= 'flat' )  THEN
    995 
    996              ALLOCATE( netcdf_data_2d(mask_size(mid,1),mask_size(mid,2)) )
    997              netcdf_data_2d = zu_s_inner( mask_i_global(mid,:mask_size(mid,1)),&
    998                                           mask_j_global(mid,:mask_size(mid,2)) )
    999 
    1000              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),         &
    1001                                      id_var_zusi_mask(mid,av),    &
    1002                                      netcdf_data_2d,              &
    1003                                      start = (/ 1, 1 /),          &
    1004                                      count = (/ mask_size(mid,1), &
    1005                                                 mask_size(mid,2) /) )
     1025          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
     1026               netcdf_data_format > 4 )  THEN
     1027
     1028             ALLOCATE( netcdf_data_2d(mask_size_l(mid,1),mask_size_l(mid,2)) )
     1029             netcdf_data_2d = zu_s_inner( mask_i(mid,:mask_size_l(mid,1)),     &
     1030                                          mask_j(mid,:mask_size_l(mid,2)) )
     1031
     1032             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                      &
     1033                                     id_var_zusi_mask(mid,av),                 &
     1034                                     netcdf_data_2d,                           &
     1035                                     start = (/ 1, 1 /),                       &
     1036                                     count = (/ mask_size_l(mid,1),            &
     1037                                                mask_size_l(mid,2) /) )
    10061038             CALL netcdf_handle_error( 'netcdf_define_header', 505 )
    10071039
    1008              netcdf_data_2d = zw_w_inner( mask_i_global(mid,:mask_size(mid,1)),&
    1009                                           mask_j_global(mid,:mask_size(mid,2)) )
    1010 
    1011              nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),         &
    1012                                      id_var_zwwi_mask(mid,av),    &
    1013                                      netcdf_data_2d,              &
    1014                                      start = (/ 1, 1 /),          &
    1015                                      count = (/ mask_size(mid,1), &
    1016                                                 mask_size(mid,2) /) )
     1040             netcdf_data_2d = zw_w_inner( mask_i(mid,:mask_size_l(mid,1)),     &
     1041                                          mask_j(mid,:mask_size_l(mid,2)) )
     1042
     1043             nc_stat = NF90_PUT_VAR( id_set_mask(mid,av),                      &
     1044                                     id_var_zwwi_mask(mid,av),                 &
     1045                                     netcdf_data_2d,                           &
     1046                                     start = (/ 1, 1 /),                       &
     1047                                     count = (/ mask_size_l(mid,1),            &
     1048                                                mask_size_l(mid,2) /) )
    10171049             CALL netcdf_handle_error( 'netcdf_define_header', 506 )
    10181050
     
    12831315!
    12841316!--       In case of non-flat topography define 2d-arrays containing the height
    1285 !--       information
    1286           IF ( TRIM( topography ) /= 'flat' )  THEN
     1317!--       information. Only output 2d topography information in case of parallel
     1318!--       output.
     1319          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
     1320               netcdf_data_format > 4 )  THEN
    12871321!
    12881322!--          Define zusi = zu(nzb_s_inner)
     
    15421576             CALL netcdf_handle_error( 'netcdf_define_header', 86 )
    15431577
    1544 !
    1545 !--          In case of non-flat topography write height information
    1546              IF ( TRIM( topography ) /= 'flat' )  THEN
    1547 
    1548                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av), &
    1549                                         zu_s_inner(0:nx+1,0:ny+1), &
    1550                                         start = (/ 1, 1 /), &
    1551                                         count = (/ nx+2, ny+2 /) )
    1552                 CALL netcdf_handle_error( 'netcdf_define_header', 419 )
    1553 
    1554                 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av), &
    1555                                         zw_w_inner(0:nx+1,0:ny+1), &
    1556                                         start = (/ 1, 1 /), &
    1557                                         count = (/ nx+2, ny+2 /) )
    1558                 CALL netcdf_handle_error( 'netcdf_define_header', 420 )
    1559 
    1560              ENDIF
    1561 
    15621578             IF ( land_surface )  THEN
    15631579!
     
    15681584                CALL netcdf_handle_error( 'netcdf_define_header', 86 )
    15691585             ENDIF
     1586
     1587          ENDIF
     1588!
     1589!--       In case of non-flat topography write height information. Only for
     1590!--       parallel netcdf output.
     1591          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
     1592               netcdf_data_format > 4 )  THEN
     1593
     1594             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     1595                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
     1596                                        zu_s_inner(nxl:nxr+1,nys:nyn),         &
     1597                                        start = (/ nxl+1, nys+1 /),            &
     1598                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
     1599             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     1600                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
     1601                                        zu_s_inner(nxl:nxr,nys:nyn+1),         &
     1602                                        start = (/ nxl+1, nys+1 /),            &
     1603                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
     1604             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     1605                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
     1606                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
     1607                                        start = (/ nxl+1, nys+1 /),            &
     1608                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
     1609             ELSE
     1610                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zusi_3d(av),     &
     1611                                        zu_s_inner(nxl:nxr,nys:nyn),           &
     1612                                        start = (/ nxl+1, nys+1 /),            &
     1613                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
     1614             ENDIF
     1615             CALL netcdf_handle_error( 'netcdf_define_header', 419 )
     1616
     1617             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     1618                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
     1619                                        zw_w_inner(nxl:nxr+1,nys:nyn),         &
     1620                                        start = (/ nxl+1, nys+1 /),            &
     1621                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
     1622             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     1623                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
     1624                                        zw_w_inner(nxl:nxr,nys:nyn+1),         &
     1625                                        start = (/ nxl+1, nys+1 /),            &
     1626                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
     1627             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     1628                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
     1629                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
     1630                                        start = (/ nxl+1, nys+1 /),            &
     1631                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
     1632             ELSE
     1633                nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_zwwi_3d(av),     &
     1634                                        zw_w_inner(nxl:nxr,nys:nyn),           &
     1635                                        start = (/ nxl+1, nys+1 /),            &
     1636                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
     1637             ENDIF
     1638             CALL netcdf_handle_error( 'netcdf_define_header', 420 )
    15701639
    15711640          ENDIF
     
    18411910          IF ( land_surface )  THEN
    18421911
    1843              ns_do = 0
    1844              DO WHILE ( section(ns_do+1,1) < nzs )
     1912             ns_do = 1
     1913             DO WHILE ( section(ns_do,1) /= -9999  .AND.  ns <= nzs )
    18451914                ns_do = ns_do + 1
    18461915             ENDDO
     
    19001969!
    19011970!--       In case of non-flat topography define 2d-arrays containing the height
    1902 !--       information
    1903           IF ( TRIM( topography ) /= 'flat' )  THEN
     1971!--       information. Only for parallel netcdf output.
     1972          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
     1973               netcdf_data_format > 4  )  THEN
    19041974!
    19051975!--          Define zusi = zu(nzb_s_inner)
     
    22112281             DEALLOCATE( netcdf_data )
    22122282
    2213 !
    2214 !--          In case of non-flat topography write height information
    2215              IF ( TRIM( topography ) /= 'flat' )  THEN
    2216 
    2217                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av), &
    2218                                         zu_s_inner(0:nx+1,0:ny+1), &
    2219                                         start = (/ 1, 1 /), &
    2220                                         count = (/ nx+2, ny+2 /) )
    2221                 CALL netcdf_handle_error( 'netcdf_define_header', 427 )
    2222 
    2223                 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av), &
    2224                                         zw_w_inner(0:nx+1,0:ny+1), &
    2225                                         start = (/ 1, 1 /), &
    2226                                         count = (/ nx+2, ny+2 /) )
    2227                 CALL netcdf_handle_error( 'netcdf_define_header', 428 )
    2228 
     2283          ENDIF
     2284
     2285!
     2286!--       In case of non-flat topography write height information. Only for
     2287!--       parallel netcdf output.
     2288          IF ( TRIM( topography ) /= 'flat'  .AND.                             &
     2289               netcdf_data_format > 4  )  THEN
     2290
     2291             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     2292                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
     2293                                        zu_s_inner(nxl:nxr+1,nys:nyn),         &
     2294                                        start = (/ nxl+1, nys+1 /),            &
     2295                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
     2296             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     2297                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
     2298                                        zu_s_inner(nxl:nxr,nys:nyn+1),         &
     2299                                        start = (/ nxl+1, nys+1 /),            &
     2300                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
     2301             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     2302                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
     2303                                        zu_s_inner(nxl:nxr+1,nys:nyn+1),       &
     2304                                        start = (/ nxl+1, nys+1 /),            &
     2305                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
     2306             ELSE
     2307                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zusi_xy(av),     &
     2308                                        zu_s_inner(nxl:nxr,nys:nyn),           &
     2309                                        start = (/ nxl+1, nys+1 /),            &
     2310                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
    22292311             ENDIF
    2230 
    2231 
     2312             CALL netcdf_handle_error( 'netcdf_define_header', 427 )
     2313
     2314             IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     2315                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
     2316                                        zw_w_inner(nxl:nxr+1,nys:nyn),         &
     2317                                        start = (/ nxl+1, nys+1 /),            &
     2318                                        count = (/ nxr-nxl+2, nyn-nys+1 /) )
     2319             ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     2320                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
     2321                                        zw_w_inner(nxl:nxr,nys:nyn+1),         &
     2322                                        start = (/ nxl+1, nys+1 /),            &
     2323                                        count = (/ nxr-nxl+1, nyn-nys+2 /) )
     2324             ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     2325                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
     2326                                        zw_w_inner(nxl:nxr+1,nys:nyn+1),       &
     2327                                        start = (/ nxl+1, nys+1 /),            &
     2328                                        count = (/ nxr-nxl+2, nyn-nys+2 /) )
     2329             ELSE
     2330                nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_zwwi_xy(av),     &
     2331                                        zw_w_inner(nxl:nxr,nys:nyn),           &
     2332                                        start = (/ nxl+1, nys+1 /),            &
     2333                                        count = (/ nxr-nxl+1, nyn-nys+1 /) )
     2334             ENDIF
     2335             CALL netcdf_handle_error( 'netcdf_define_header', 428 )
    22322336
    22332337          ENDIF
     
    53375441! Description:
    53385442! ------------
     5443!> Closes an existing netCDF file.
     5444!------------------------------------------------------------------------------!
     5445 
     5446 SUBROUTINE netcdf_close_file( id, errno )
     5447#if defined( __netcdf )
     5448
     5449    USE pegrid
     5450
     5451    IMPLICIT NONE
     5452
     5453    INTEGER(iwp), INTENT(IN)           ::  errno     !< error number
     5454    INTEGER(iwp), INTENT(INOUT)        ::  id        !< file id
     5455
     5456    nc_stat = NF90_CLOSE( id )
     5457    CALL netcdf_handle_error( 'netcdf_close', errno )
     5458#endif
     5459 END SUBROUTINE netcdf_close_file
     5460
     5461!------------------------------------------------------------------------------!
     5462! Description:
     5463! ------------
     5464!> Opens an existing netCDF file for reading only and gives back the id.
     5465!------------------------------------------------------------------------------!
     5466 
     5467 SUBROUTINE netcdf_open_read_file( filename, id, errno )
     5468#if defined( __netcdf )
     5469
     5470    USE pegrid
     5471
     5472    IMPLICIT NONE
     5473
     5474    CHARACTER (LEN=*), INTENT(IN) ::  filename  !< filename
     5475    INTEGER(iwp), INTENT(IN)      ::  errno     !< error number
     5476    INTEGER(iwp), INTENT(INOUT)   ::  id        !< file id
     5477    LOGICAL                       ::  file_open = .FALSE.
     5478
     5479    nc_stat = NF90_OPEN( filename, NF90_NOWRITE, id )
     5480
     5481    CALL netcdf_handle_error( 'netcdf_open_read_file', errno )
     5482
     5483#endif
     5484 END SUBROUTINE netcdf_open_read_file
     5485
     5486!------------------------------------------------------------------------------!
     5487! Description:
     5488! ------------
     5489!> Reads the global attributes of a file
     5490!------------------------------------------------------------------------------!
     5491 
     5492 SUBROUTINE netcdf_get_attribute( id, attribute_name, value, global, errno, variable_name )
     5493#if defined( __netcdf )
     5494
     5495    USE pegrid
     5496
     5497    IMPLICIT NONE
     5498
     5499    CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
     5500    CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
     5501
     5502    INTEGER(iwp), INTENT(IN)    ::  errno            !< error number
     5503    INTEGER(iwp), INTENT(INOUT) ::  id               !< file id
     5504    INTEGER(iwp), INTENT(INOUT) ::  value            !< read value
     5505
     5506    INTEGER(iwp)                ::  id_var           !< variable id
     5507
     5508    LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attributes
     5509
     5510!
     5511!-- Read global attribute
     5512    IF ( global )  THEN
     5513       nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
     5514       CALL netcdf_handle_error( 'netcdf_get_attribute global', errno )
     5515!
     5516!-- Read attributes referring to a single variable. Therefore, first inquire
     5517!-- variable id
     5518    ELSE
     5519       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
     5520       CALL netcdf_handle_error( 'netcdf_get_attribute', errno )
     5521       nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
     5522       CALL netcdf_handle_error( 'netcdf_get_attribute', errno )       
     5523    ENDIF
     5524#endif
     5525 END SUBROUTINE netcdf_get_attribute
     5526
     5527!------------------------------------------------------------------------------!
     5528! Description:
     5529! ------------
     5530!> Reads a 2D REAL variable of a file. Reading is done processor-wise,
     5531!> i.e. each core reads its own domain, as well as in slices along x.
     5532!------------------------------------------------------------------------------!
     5533 
     5534 SUBROUTINE netcdf_get_variable_2d( id, variable_name, i, var, errno )
     5535#if defined( __netcdf )
     5536
     5537    USE indices
     5538    USE pegrid
     5539
     5540    IMPLICIT NONE
     5541
     5542    CHARACTER(LEN=*)              ::  variable_name   !< attribute name
     5543    INTEGER(iwp), INTENT(IN)      ::  errno           !< error number
     5544    INTEGER(iwp), INTENT(IN)      ::  i               !< index along x direction
     5545
     5546    INTEGER(iwp), INTENT(INOUT)   ::  id              !< file id
     5547
     5548    INTEGER(iwp)                  ::  id_var          !< variable id
     5549
     5550    REAL(wp), DIMENSION(nys:nyn), INTENT(INOUT) ::  var  !< variable to be read
     5551    REAL(wp) :: var_dum
     5552!
     5553!-- Inquire variable id
     5554    nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
     5555!
     5556!-- Get variable
     5557    nc_stat = NF90_GET_VAR( id, id_var, var(nys:nyn),                        &
     5558                            start = (/ i+1, nys+1 /),                          &
     5559                            count = (/ 1, nyn - nys + 1 /) )
     5560
     5561    CALL netcdf_handle_error( 'netcdf_get_variable', errno )
     5562#endif
     5563 END SUBROUTINE netcdf_get_variable_2d
     5564
     5565!------------------------------------------------------------------------------!
     5566! Description:
     5567! ------------
     5568!> Reads a 3D INTEGER variable of a file. Reading is done processor-wise,
     5569!> i.e. each core reads its own domain, as well as in slices along x.
     5570!------------------------------------------------------------------------------!
     5571 
     5572 SUBROUTINE netcdf_get_variable_3d( id, variable_name, i, j, var, errno )
     5573#if defined( __netcdf )
     5574
     5575    USE indices
     5576    USE pegrid
     5577
     5578    IMPLICIT NONE
     5579
     5580    CHARACTER(LEN=*)              ::  variable_name   !< attribute name
     5581    INTEGER(iwp), INTENT(IN)      ::  errno           !< error number
     5582    INTEGER(iwp), INTENT(IN)      ::  i               !< index along x direction
     5583    INTEGER(iwp), INTENT(IN)      ::  j               !< index along y direction
     5584
     5585    INTEGER(iwp), INTENT(INOUT)   ::  id              !< file id
     5586
     5587    INTEGER(iwp)                  ::  id_var          !< variable id
     5588    INTEGER(iwp)                  ::  id_z            !< id of z-dimension
     5589    INTEGER(iwp)                  ::  nz_file         !< number of grid-points in file
     5590
     5591    INTEGER(iwp), DIMENSION(nzb:nzt+1), INTENT(INOUT) ::  var  !< variable to be read
     5592!
     5593!-- Get dimension of z-axis
     5594    nc_stat = NF90_INQ_DIMID( id, "z", id_z )
     5595    nc_stat = NF90_INQUIRE_DIMENSION( id, id_z, len = nz_file )
     5596!
     5597!-- Inquire variable id
     5598    nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
     5599!
     5600!-- Get variable
     5601    nc_stat = NF90_GET_VAR( id, id_var, var(0:nz_file-1),                  &
     5602                            start = (/ i+1, j+1, 1 /),                         &
     5603                            count = (/ 1, 1, nz_file /) )
     5604
     5605    CALL netcdf_handle_error( 'netcdf_get_variable', errno )
     5606#endif
     5607 END SUBROUTINE netcdf_get_variable_3d
     5608
     5609!------------------------------------------------------------------------------!
     5610! Description:
     5611! ------------
    53395612!> Opens an existing netCDF file for writing and gives back the id.
    53405613!> The parallel flag has to be TRUE for parallel netCDF output support.
Note: See TracChangeset for help on using the changeset viewer.