New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 5406 for branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90 – NEMO

Ignore:
Timestamp:
2015-06-11T17:37:20+02:00 (9 years ago)
Author:
hadcv
Message:
  • Add cell area information (under ln_cfmeta namelist parameter)
  • Add depth bounds information
File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r5388 r5406  
    9898      CHARACTER(len=10) :: clname 
    9999      INTEGER           ::   ji 
    100       !!---------------------------------------------------------------------- 
     100      ! 
     101      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_bnds 
     102      !!---------------------------------------------------------------------- 
     103 
     104      ALLOCATE( z_bnds(jpk,2) ) 
    101105 
    102106      clname = cdname 
     
    122126         CALL set_grid( "V", glamv, gphiv ) 
    123127         CALL set_grid( "W", glamt, gphit ) 
     128         ! 
     129         IF( ln_cfmeta ) THEN   ! Add cell areas 
     130            CALL iom_set_domain_attr("grid_T", area = e12t(nldi:nlei, nldj:nlej)) 
     131            CALL iom_set_domain_attr("grid_U", area = e12u(nldi:nlei, nldj:nlej)) 
     132            CALL iom_set_domain_attr("grid_V", area = e12v(nldi:nlei, nldj:nlej)) 
     133            CALL iom_set_domain_attr("grid_W", area = e12t(nldi:nlei, nldj:nlej)) 
     134         ENDIF 
    124135      ENDIF 
    125136 
     
    133144          ! 
    134145         CALL dom_grid_glo   ! Return to parent grid domain 
    135       ENDIF 
    136  
    137       IF ( ln_cfmeta ) THEN   ! add cell bounds 
     146         ! 
     147         IF( ln_cfmeta ) THEN   ! Add cell areas 
     148            CALL iom_set_domain_attr("grid_T", area = e1e2t_crs(nldi:nlei, nldj:nlej)) 
     149            CALL iom_set_domain_attr("grid_U", area = e1u_crs(nldi:nlei, nldj:nlej) * e2u_crs(nldi:nlei, nldj:nlej)) 
     150            CALL iom_set_domain_attr("grid_V", area = e1v_crs(nldi:nlei, nldj:nlej) * e2v_crs(nldi:nlei, nldj:nlej)) 
     151            CALL iom_set_domain_attr("grid_W", area = e1e2t_crs(nldi:nlei, nldj:nlej)) 
     152         ENDIF 
     153      ENDIF 
     154 
     155      IF ( ln_cfmeta ) THEN   ! Add horizontal grid bounds 
    138156         CALL set_grid_bounds( "T", cdname )  
    139157         CALL set_grid_bounds( "U", cdname ) 
     
    147165      CALL iom_set_axis_attr( "depthv", gdept_1d ) 
    148166      CALL iom_set_axis_attr( "depthw", gdepw_1d ) 
     167 
     168      ! Add vertical grid bounds 
     169      z_bnds(:      ,1) = gdepw_1d(:) 
     170      z_bnds(1:jpkm1,2) = gdepw_1d(2:jpk) 
     171      z_bnds(jpk:   ,2) = gdepw_1d(jpk) + e3t_1d(jpk) 
     172      CALL iom_set_axis_attr( "deptht", bounds=z_bnds ) 
     173      CALL iom_set_axis_attr( "depthu", bounds=z_bnds ) 
     174      CALL iom_set_axis_attr( "depthv", bounds=z_bnds ) 
     175      z_bnds(:    ,2) = gdept_1d(:) 
     176      z_bnds(2:jpk,1) = gdept_1d(1:jpkm1) 
     177      z_bnds(1    ,1) = gdept_1d(1) - e3w_1d(1) 
     178      CALL iom_set_axis_attr( "depthw", bounds=z_bnds ) 
     179 
    149180# if defined key_floats 
    150181      CALL iom_set_axis_attr( "nfloat", (/ (REAL(ji,wp), ji=1,nfloat) /) ) 
     
    166197       
    167198      CALL xios_update_calendar(0) 
     199 
     200      DEALLOCATE( z_bnds ) 
     201 
    168202#endif 
    169203       
     
    11121146   SUBROUTINE iom_set_domain_attr( cdid, ni_glo, nj_glo, ibegin, jbegin, ni, nj, zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj,   & 
    11131147      &                                    data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask,     & 
    1114       &                                    nvertex, bounds_lon, bounds_lat ) 
     1148      &                                    nvertex, bounds_lon, bounds_lat, area ) 
    11151149      CHARACTER(LEN=*)                   , INTENT(in) ::   cdid 
    11161150      INTEGER                  , OPTIONAL, INTENT(in) ::   ni_glo, nj_glo, ibegin, jbegin, ni, nj 
     
    11181152      INTEGER                  , OPTIONAL, INTENT(in) ::   zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj, nvertex 
    11191153      REAL(wp), DIMENSION(:)   , OPTIONAL, INTENT(in) ::   lonvalue, latvalue 
    1120       REAL(wp), DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   bounds_lon, bounds_lat 
     1154      REAL(wp), DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   bounds_lon, bounds_lat, area 
    11211155      LOGICAL,  DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   mask 
    11221156 
     
    11251159            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
    11261160            &    zoom_ibegin=zoom_ibegin, zoom_jbegin=zoom_jbegin, zoom_ni=zoom_ni, zoom_nj=zoom_nj,                       & 
    1127             &    lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon, bounds_lat=bounds_lat ) 
     1161            &    lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon,                  & 
     1162            &    bounds_lat=bounds_lat, area=area ) 
    11281163      ENDIF 
    11291164 
     
    11321167            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
    11331168            &    zoom_ibegin=zoom_ibegin, zoom_jbegin=zoom_jbegin, zoom_ni=zoom_ni, zoom_nj=zoom_nj,                       & 
    1134             &    lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon, bounds_lat=bounds_lat ) 
     1169            &    lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon,                  & 
     1170            &    bounds_lat=bounds_lat, area=area ) 
    11351171      ENDIF 
    11361172      CALL xios_solve_inheritance() 
     
    11391175 
    11401176 
    1141    SUBROUTINE iom_set_axis_attr( cdid, paxis ) 
    1142       CHARACTER(LEN=*)      , INTENT(in) ::   cdid 
    1143       REAL(wp), DIMENSION(:), INTENT(in) ::   paxis 
    1144       IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, size=size(paxis),value=paxis ) 
    1145       IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, size=size(paxis),value=paxis ) 
     1177   SUBROUTINE iom_set_axis_attr( cdid, paxis, bounds ) 
     1178      CHARACTER(LEN=*)                  , INTENT(in) ::   cdid 
     1179      REAL(wp), DIMENSION(:)  , OPTIONAL, INTENT(in) ::   paxis 
     1180      REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(in) ::   bounds 
     1181      IF ( PRESENT(paxis) ) THEN 
     1182         IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, size=SIZE(paxis), value=paxis ) 
     1183         IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, size=SIZE(paxis), value=paxis ) 
     1184      ENDIF 
     1185      IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, bounds=bounds ) 
     1186      IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, bounds=bounds ) 
    11461187      CALL xios_solve_inheritance() 
    11471188   END SUBROUTINE iom_set_axis_attr 
     
    13461387         DO jn = 1, 4  ;  z_bnds(jn,:,nlcj,:) = z_pnt(:,nlcj,:)  ;  END DO      ! (North or jpnj = 1), no north fold 
    13471388      ENDIF 
    1348  
    1349 ! ===================================================================================================== 
    1350 !             Do we need to set zero-size cells at Mediterranean / Persian Gulf region? 
    1351 ! ===================================================================================================== 
    13521389 
    13531390      ! Rotate cells at the north fold 
Note: See TracChangeset for help on using the changeset viewer.