Ignore:
Timestamp:
Dec 14, 2017 5:12:51 PM (6 years ago)
Author:
kanani
Message:

Merge of branch palm4u into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/netcdf_interface_mod.f90

    r2512 r2696  
    11!> @file netcdf_interface_mod.f90
    22!------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    44!
    55! PALM is free software: you can redistribute it and/or modify it under the
     
    2525! -----------------
    2626! $Id$
     27! Implementation of uv exposure model (FK)
     28! Implemented checks for turbulence_closure_mod (TG)
     29! Implementation of chemistry module (FK)
     30! Bugfix in setting netcdf grids for LSM variables
     31! Enable setting of _FillValue attribute in output files (MS)
     32!
     33! 2512 2017-10-04 08:26:59Z raasch
    2734! upper bounds of cross section and 3d output changed from nx+1,ny+1 to nx,ny
    2835! no output of ghost layer data any more
     
    410417    INTEGER(iwp), DIMENSION(1:max_masks,0:1,100) ::  id_var_domask
    411418
     419    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
     420
    412421
    413422    PUBLIC  dofl_dim_label_x, dofl_dim_label_y, dofl_dim_label_z, dofl_label,  &
    414423            dofl_time_count, dofl_unit, domask_unit, dopr_unit, dopts_num,     &
    415424            dots_label, dots_max, dots_num, dots_rad, dots_soil, dots_unit,    &
    416             do2d_unit, do3d_unit, id_set_fl, id_set_mask, id_set_pr,           &
     425            do2d_unit, do3d_unit, fill_value,                                  &
     426            id_set_fl, id_set_mask, id_set_pr,                                 &
    417427            id_set_prt, id_set_pts, id_set_sp, id_set_ts, id_set_xy, id_set_xz,&
    418428            id_set_yz, id_set_3d, id_var_domask, id_var_dofl, id_var_dopr,     &
     
    432442    END INTERFACE netcdf_create_dim
    433443
    434     INTERFACE netcdf_close_file
    435        MODULE PROCEDURE netcdf_close_file
    436     END INTERFACE netcdf_close_file
    437 
    438444    INTERFACE netcdf_create_file
    439445       MODULE PROCEDURE netcdf_create_file
     
    448454    END INTERFACE netcdf_define_header
    449455
    450     INTERFACE netcdf_get_attribute
    451        MODULE PROCEDURE netcdf_get_attribute
    452     END INTERFACE netcdf_get_attribute
    453 
    454     INTERFACE netcdf_get_variable
    455        MODULE PROCEDURE netcdf_get_variable_2d
    456        MODULE PROCEDURE netcdf_get_variable_3d
    457     END INTERFACE netcdf_get_variable
    458 
    459456    INTERFACE netcdf_handle_error
    460457       MODULE PROCEDURE netcdf_handle_error
    461458    END INTERFACE netcdf_handle_error
    462459
    463     INTERFACE netcdf_open_read_file
    464        MODULE PROCEDURE netcdf_open_read_file
    465     END INTERFACE netcdf_open_read_file
    466 
    467460    INTERFACE netcdf_open_write_file
    468461       MODULE PROCEDURE netcdf_open_write_file
    469462    END INTERFACE netcdf_open_write_file
    470463
    471     PUBLIC netcdf_create_file, netcdf_close_file, netcdf_define_header,        &
    472            netcdf_handle_error, netcdf_get_attribute, netcdf_get_variable,     &
    473            netcdf_open_read_file, netcdf_open_write_file
     464    PUBLIC netcdf_create_file, netcdf_define_header,                           &
     465           netcdf_handle_error, netcdf_open_write_file
    474466
    475467 CONTAINS
     
    482474        ONLY:  zu, zw
    483475
     476#if defined( __chem )
     477    USE chemistry_model_mod,                                                   &
     478        ONLY:  chem_define_netcdf_grid
     479#endif
     480
    484481    USE constants,                                                             &
    485482        ONLY:  pi
    486483
    487484    USE control_parameters,                                                    &
    488         ONLY:  averaging_interval, averaging_interval_pr,                      &
     485        ONLY:  air_chemistry, averaging_interval, averaging_interval_pr,       &
    489486               data_output_pr, domask, dopr_n,                                 &
    490487               dopr_time_count, dopts_time_count, dots_time_count,             &
     
    493490               dt_do2d_yz, dt_do3d, mask_size, do2d_xy_time_count,             &
    494491               do3d_time_count, domask_time_count, end_time, land_surface,     &
    495                lod, mask_size_l, mask_i, mask_i_global, mask_j, mask_j_global, &
     492               mask_size_l, mask_i, mask_i_global, mask_j, mask_j_global,      &
    496493               mask_k_global, message_string, mid, ntdim_2d_xy,                &
    497494               ntdim_2d_xz, ntdim_2d_yz, ntdim_3d, nz_do3d, prt_time_count,    &
     
    500497               skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,        &
    501498               skip_time_do3d, topography, num_leg, num_var_fl,                &
    502                urban_surface
     499               urban_surface, uv_exposure
    503500
    504501    USE grid_variables,                                                        &
     
    533530        ONLY:  hom, statistic_regions
    534531
     532    USE turbulence_closure_mod,                                                &
     533        ONLY:  tcm_define_netcdf_grid
     534
    535535    USE urban_surface_mod,                                                     &
    536536        ONLY:  usm_define_netcdf_grid
     537
     538    USE uv_exposure_model_mod,                                                 &
     539        ONLY:  uvem_define_netcdf_grid
    537540
    538541
     
    894897                CASE DEFAULT
    895898
     899                   CALL tcm_define_netcdf_grid( domask(mid,av,i), found, &
     900                                                        grid_x, grid_y, grid_z )
     901
    896902!
    897903!--                Check for land surface quantities
     
    900906                                                   grid_x, grid_y, grid_z )
    901907                   ENDIF
    902                    
    903908!
    904909!--                Check for plant canopy quantities
    905                    IF ( plant_canopy )  THEN
     910                   IF ( .NOT. found  .AND.  plant_canopy )  THEN
    906911                      CALL pcm_define_netcdf_grid( domask(mid,av,i), found,    &
    907912                                                   grid_x, grid_y, grid_z )
     
    915920                                                         grid_z )
    916921                   ENDIF
     922
     923!
     924!--                Check for chemistry quantities                   
     925#if defined( __chem )
     926                   IF ( .NOT. found  .AND.  air_chemistry )  THEN
     927                      CALL chem_define_netcdf_grid( domask(mid,av,i),          &
     928                                                    found, grid_x, grid_y,     &
     929                                                    grid_z )
     930                   ENDIF
     931#endif
    917932
    918933!
     
    961976                                     id_var_domask(mid,av,i),                  &
    962977                                     TRIM( domask_unit(mid,av,i) ),            &
    963                                      domask(mid,av,i), 494, 495, 496 )
     978                                     domask(mid,av,i), 494, 495, 496, .TRUE. )
    964979
    965980             var_list = TRIM( var_list ) // TRIM( domask(mid,av,i) ) // ';'
     
    14251440                CASE DEFAULT
    14261441
     1442                   CALL tcm_define_netcdf_grid( do3d(av,i), found, &
     1443                                                   grid_x, grid_y, grid_z )
     1444
    14271445!
    14281446!--                Check for land surface quantities
     
    14341452!
    14351453!--                Check for plant canopy quantities
    1436                    IF ( plant_canopy )  THEN
     1454                   IF ( .NOT. found  .AND.  plant_canopy )  THEN
    14371455                      CALL pcm_define_netcdf_grid( do3d(av,i), found, grid_x,  &
    14381456                                                   grid_y, grid_z )
     
    14461464                                                         grid_z )
    14471465                   ENDIF
    1448                    
     1466
     1467!
     1468!--                Check for chemistry quantities                   
     1469#if defined( __chem )
     1470                   IF ( .NOT. found  .AND.  air_chemistry )  THEN
     1471                      CALL chem_define_netcdf_grid( do3d(av,i), found,         &
     1472                                                    grid_x, grid_y, grid_z )
     1473                   ENDIF
     1474#endif
     1475
    14491476!--                Check for user-defined quantities
    14501477                   IF ( .NOT. found )  THEN
     
    14901517                                     nc_precision(4), id_var_do3d(av,i),       &
    14911518                                     TRIM( do3d_unit(av,i) ), do3d(av,i), 79,  &
    1492                                      80, 357 )
     1519                                     80, 357, .TRUE. )
    14931520#if defined( __netcdf4_parallel )
    14941521             IF ( netcdf_data_format > 4 )  THEN
     
    20292056                                           nc_precision(1), id_var_do2d(av,i), &
    20302057                                           TRIM( do2d_unit(av,i) ),            &
    2031                                            do2d(av,i), 119, 120, 354 )
     2058                                           do2d(av,i), 119, 120, 354, .TRUE. )
    20322059
    20332060                ELSE
     
    20792106                         ENDIF
    20802107
     2108                         IF ( .NOT. found )  THEN
     2109                            CALL tcm_define_netcdf_grid( do2d(av,i), found,    &
     2110                                                         grid_x, grid_y,       &
     2111                                                         grid_z )
     2112                         ENDIF
     2113
    20812114!
    20822115!--                      Check for radiation quantities
     
    20852118                                                         found, grid_x, grid_y,&
    20862119                                                         grid_z )
     2120                         ENDIF
     2121
     2122!
     2123!--                      Check for chemistry quantities
     2124#if defined( __chem )
     2125                         IF ( .NOT. found  .AND.  air_chemistry )  THEN
     2126                            CALL chem_define_netcdf_grid( do2d(av,i), found,   &
     2127                                                          grid_x, grid_y,      &
     2128                                                          grid_z )
     2129                         ENDIF
     2130#endif
     2131
     2132!
     2133!--                      Check for UV exposure quantities
     2134                         IF ( .NOT. found  .AND.  uv_exposure )  THEN
     2135                            CALL uvem_define_netcdf_grid( do2d(av,i), found,    &
     2136                                                          grid_x, grid_y, grid_z )
    20872137                         ENDIF
    20882138
     
    21322182                                           nc_precision(1), id_var_do2d(av,i), &
    21332183                                           TRIM( do2d_unit(av,i) ),            &
    2134                                            do2d(av,i), 119, 120, 354 )
     2184                                           do2d(av,i), 119, 120, 354, .TRUE. )
    21352185
    21362186                ENDIF
     
    27772827                      ENDIF
    27782828
     2829                      IF ( .NOT. found )  THEN
     2830                         CALL tcm_define_netcdf_grid( do2d(av,i), found,       &
     2831                                                      grid_x, grid_y, grid_z )
     2832                      ENDIF
     2833
    27792834!
    27802835!--                   Check for radiation quantities
     
    27842839                                                            grid_z )
    27852840                      ENDIF
     2841
     2842!
     2843!--                   Check for chemistry quantities
     2844#if defined( __chem )
     2845                      IF ( .NOT. found  .AND.  air_chemistry )  THEN
     2846                         CALL chem_define_netcdf_grid( do2d(av,i), found,      &
     2847                                                       grid_x, grid_y,         &
     2848                                                       grid_z )
     2849                      ENDIF
     2850#endif
    27862851
    27872852!
     
    28292894                                        nc_precision(2), id_var_do2d(av,i),    &
    28302895                                        TRIM( do2d_unit(av,i) ), do2d(av,i),   &
    2831                                         159, 160, 355 )
     2896                                        159, 160, 355, .TRUE. )
    28322897
    28332898#if defined( __netcdf4_parallel )
     
    34313496                      ENDIF
    34323497
     3498                      IF ( .NOT. found )  THEN
     3499                         CALL tcm_define_netcdf_grid( do2d(av,i), found,       &
     3500                                                      grid_x, grid_y, grid_z )
     3501                      ENDIF
     3502
    34333503!
    34343504!--                   Check for radiation quantities
     
    34393509                      ENDIF
    34403510
     3511!
     3512!--                   Check for chemistry quantities
     3513#if defined( __chem )
     3514                      IF ( .NOT. found  .AND.  air_chemistry )  THEN
     3515                         CALL chem_define_netcdf_grid( do2d(av,i), found,      &
     3516                                                       grid_x, grid_y,         &
     3517                                                       grid_z )
     3518                      ENDIF
     3519#endif
    34413520!
    34423521!--                   Check for user-defined quantities
     
    34833562                                        nc_precision(3), id_var_do2d(av,i),    &
    34843563                                        TRIM( do2d_unit(av,i) ), do2d(av,i),   &
    3485                                         198, 199, 356 )
     3564                                        198, 199, 356, .TRUE. )
    34863565
    34873566#if defined( __netcdf4_parallel )
     
    54535532 END SUBROUTINE netcdf_create_file
    54545533
    5455 
    5456 !------------------------------------------------------------------------------!
    5457 ! Description:
    5458 ! ------------
    5459 !> Closes an existing netCDF file.
    5460 !------------------------------------------------------------------------------!
    5461  
    5462  SUBROUTINE netcdf_close_file( id, errno )
    5463 #if defined( __netcdf )
    5464 
    5465     USE pegrid
    5466 
    5467     IMPLICIT NONE
    5468 
    5469     INTEGER(iwp), INTENT(IN)           ::  errno     !< error number
    5470     INTEGER(iwp), INTENT(INOUT)        ::  id        !< file id
    5471 
    5472     nc_stat = NF90_CLOSE( id )
    5473     CALL netcdf_handle_error( 'netcdf_close', errno )
    5474 #endif
    5475  END SUBROUTINE netcdf_close_file
    5476 
    5477 !------------------------------------------------------------------------------!
    5478 ! Description:
    5479 ! ------------
    5480 !> Opens an existing netCDF file for reading only and gives back the id.
    5481 !------------------------------------------------------------------------------!
    5482  
    5483  SUBROUTINE netcdf_open_read_file( filename, id, errno )
    5484 #if defined( __netcdf )
    5485 
    5486     USE pegrid
    5487 
    5488     IMPLICIT NONE
    5489 
    5490     CHARACTER (LEN=*), INTENT(IN) ::  filename  !< filename
    5491     INTEGER(iwp), INTENT(IN)      ::  errno     !< error number
    5492     INTEGER(iwp), INTENT(INOUT)   ::  id        !< file id
    5493     LOGICAL                       ::  file_open = .FALSE.
    5494 
    5495     nc_stat = NF90_OPEN( filename, NF90_NOWRITE, id )
    5496 
    5497     CALL netcdf_handle_error( 'netcdf_open_read_file', errno )
    5498 
    5499 #endif
    5500  END SUBROUTINE netcdf_open_read_file
    5501 
    5502 !------------------------------------------------------------------------------!
    5503 ! Description:
    5504 ! ------------
    5505 !> Reads the global attributes of a file
    5506 !------------------------------------------------------------------------------!
    5507  
    5508  SUBROUTINE netcdf_get_attribute( id, attribute_name, value, global, errno, variable_name )
    5509 #if defined( __netcdf )
    5510 
    5511     USE pegrid
    5512 
    5513     IMPLICIT NONE
    5514 
    5515     CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
    5516     CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
    5517 
    5518     INTEGER(iwp), INTENT(IN)    ::  errno            !< error number
    5519     INTEGER(iwp), INTENT(INOUT) ::  id               !< file id
    5520     INTEGER(iwp), INTENT(INOUT) ::  value            !< read value
    5521 
    5522     INTEGER(iwp)                ::  id_var           !< variable id
    5523 
    5524     LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attributes
    5525 
    5526 !
    5527 !-- Read global attribute
    5528     IF ( global )  THEN
    5529        nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
    5530        CALL netcdf_handle_error( 'netcdf_get_attribute global', errno )
    5531 !
    5532 !-- Read attributes referring to a single variable. Therefore, first inquire
    5533 !-- variable id
    5534     ELSE
    5535        nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    5536        CALL netcdf_handle_error( 'netcdf_get_attribute', errno )
    5537        nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
    5538        CALL netcdf_handle_error( 'netcdf_get_attribute', errno )       
    5539     ENDIF
    5540 #endif
    5541  END SUBROUTINE netcdf_get_attribute
    5542 
    5543 !------------------------------------------------------------------------------!
    5544 ! Description:
    5545 ! ------------
    5546 !> Reads a 2D REAL variable of a file. Reading is done processor-wise,
    5547 !> i.e. each core reads its own domain, as well as in slices along x.
    5548 !------------------------------------------------------------------------------!
    5549  
    5550  SUBROUTINE netcdf_get_variable_2d( id, variable_name, i, var, errno )
    5551 #if defined( __netcdf )
    5552 
    5553     USE indices
    5554     USE pegrid
    5555 
    5556     IMPLICIT NONE
    5557 
    5558     CHARACTER(LEN=*)              ::  variable_name   !< attribute name
    5559     INTEGER(iwp), INTENT(IN)      ::  errno           !< error number
    5560     INTEGER(iwp), INTENT(IN)      ::  i               !< index along x direction
    5561 
    5562     INTEGER(iwp), INTENT(INOUT)   ::  id              !< file id
    5563 
    5564     INTEGER(iwp)                  ::  id_var          !< variable id
    5565 
    5566     REAL(wp), DIMENSION(nys:nyn), INTENT(INOUT) ::  var  !< variable to be read
    5567     REAL(wp) :: var_dum
    5568 !
    5569 !-- Inquire variable id
    5570     nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    5571 !
    5572 !-- Get variable
    5573     nc_stat = NF90_GET_VAR( id, id_var, var(nys:nyn),                        &
    5574                             start = (/ i+1, nys+1 /),                          &
    5575                             count = (/ 1, nyn - nys + 1 /) )
    5576 
    5577     CALL netcdf_handle_error( 'netcdf_get_variable', errno )
    5578 #endif
    5579  END SUBROUTINE netcdf_get_variable_2d
    5580 
    5581 !------------------------------------------------------------------------------!
    5582 ! Description:
    5583 ! ------------
    5584 !> Reads a 3D INTEGER variable of a file. Reading is done processor-wise,
    5585 !> i.e. each core reads its own domain, as well as in slices along x.
    5586 !------------------------------------------------------------------------------!
    5587  
    5588  SUBROUTINE netcdf_get_variable_3d( id, variable_name, i, j, var, errno )
    5589 #if defined( __netcdf )
    5590 
    5591     USE indices
    5592     USE pegrid
    5593 
    5594     IMPLICIT NONE
    5595 
    5596     CHARACTER(LEN=*)              ::  variable_name   !< attribute name
    5597     INTEGER(iwp), INTENT(IN)      ::  errno           !< error number
    5598     INTEGER(iwp), INTENT(IN)      ::  i               !< index along x direction
    5599     INTEGER(iwp), INTENT(IN)      ::  j               !< index along y direction
    5600 
    5601     INTEGER(iwp), INTENT(INOUT)   ::  id              !< file id
    5602 
    5603     INTEGER(iwp)                  ::  id_var          !< variable id
    5604     INTEGER(iwp)                  ::  id_z            !< id of z-dimension
    5605     INTEGER(iwp)                  ::  nz_file         !< number of grid-points in file
    5606 
    5607     INTEGER( KIND = 1 ), DIMENSION(nzb:nzt+1), INTENT(INOUT) ::  var  !< variable to be read
    5608 !
    5609 !-- Get dimension of z-axis
    5610     nc_stat = NF90_INQ_DIMID( id, "z", id_z )
    5611     nc_stat = NF90_INQUIRE_DIMENSION( id, id_z, len = nz_file )
    5612 !
    5613 !-- Inquire variable id
    5614     nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
    5615 !
    5616 !-- Get variable
    5617     nc_stat = NF90_GET_VAR( id, id_var, var(0:nz_file-1),                  &
    5618                             start = (/ i+1, j+1, 1 /),                         &
    5619                             count = (/ 1, 1, nz_file /) )
    5620 
    5621     CALL netcdf_handle_error( 'netcdf_get_variable', errno )
    5622 #endif
    5623  END SUBROUTINE netcdf_get_variable_3d
    5624 
    56255534!------------------------------------------------------------------------------!
    56265535! Description:
     
    56295538!> The parallel flag has to be TRUE for parallel netCDF output support.
    56305539!------------------------------------------------------------------------------!
    5631  
    56325540 SUBROUTINE netcdf_open_write_file( filename, id, parallel, errno )
    56335541#if defined( __netcdf )
     
    57315639 SUBROUTINE netcdf_create_var( ncid, dim_id, var_name, var_type, var_id,       &
    57325640                               unit_name, long_name, error_no1, error_no2,     &
    5733                                error_no3 )
     5641                               error_no3, fill )
    57345642
    57355643#if defined( __netcdf )
     
    57395647    CHARACTER(LEN=*), INTENT(IN) ::  unit_name
    57405648    CHARACTER(LEN=*), INTENT(IN) ::  var_name
     5649
     5650    LOGICAL, OPTIONAL ::  fill  !< indicates setting of _FillValue attribute
    57415651
    57425652    INTEGER, INTENT(IN)  ::  error_no1
     
    57775687    ENDIF
    57785688
     5689!
     5690!-- Set _FillValue for all variables, except for dimension variables.
     5691!-- Set the fill values accordingly to the corresponding output precision.
     5692    IF ( PRESENT( fill ) )  THEN
     5693       IF ( var_type == NF90_REAL4 )  THEN
     5694          nc_stat = NF90_PUT_ATT( ncid, var_id, '_FillValue',                  &
     5695                                  REAL( fill_value, KIND = 4 ) )
     5696          CALL netcdf_handle_error( 'netcdf_create_var', 0 )
     5697       ELSE
     5698          nc_stat = NF90_PUT_ATT( ncid, var_id, '_FillValue',                  &
     5699                                  REAL( fill_value, KIND = 8 ) )
     5700          CALL netcdf_handle_error( 'netcdf_create_var', 0 )
     5701       ENDIF
     5702    ENDIF
     5703
    57795704#endif
    57805705 END SUBROUTINE netcdf_create_var
Note: See TracChangeset for help on using the changeset viewer.