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 5342 for branches/2014 – NEMO

Changeset 5342 for branches/2014


Ignore:
Timestamp:
2015-06-03T19:07:18+02:00 (9 years ago)
Author:
hadcv
Message:

Addition of cell bounds in output files and other changes.

  • XIOS namelist changes:
    • Undid removal of some long_name entries in iodef_ar5.xml at last commit
    • Removed mldkz5_max definition
  • NEMO changes
    • Added set_grid_bounds subroutine to iom.F90
    • Added a new namelist parameter to the namrun namelist "ln_cfmeta"; this controls the output of grid bounds
    • Added arguments to nvertex, bounds_lon and bounds_lat in the iom.F90 XIOS interface wrappers
Location:
branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM/CONFIG/ORCA2_LIM/EXP00/iodef_ar5.xml

    r5199 r5342  
    3434     <field field_ref="sst"          name='tos'      long_name="sea_surface_temperature"                              level="2" /> 
    3535     <field field_ref="sst2"         name='tossq'    long_name="square_of_sea_surface_temperature"                    level="2" /> 
    36      <field field_ref="mldkz5_max"   name='omldamax' long_name="ocean_mixed_layer_thickness_defined_by_mixing_scheme" standard_name="ocean_mixed_layer_thickness_defined_by_mixing_scheme" level="2" /> 
     36     <field field_ref="mldkz5"       name='omldamax' long_name="ocean_mixed_layer_thickness_defined_by_mixing_scheme" standard_name="ocean_mixed_layer_thickness_defined_by_mixing_scheme" level="2" operation="maximum" /> 
    3737   </file>    
    3838      </file_group> 
     
    6262     <!-- mlotst    :           ocean_mixed_layer_thickness_defined_by_sigma_t : must be done offline --> 
    6363     <!-- mlotstsq  : square_of_ocean_mixed_layer_thickness_defined_by_sigma_t : must be done offline --> 
    64      <field field_ref="mldkz5_max"   name='omlmax'   long_name="ocean_mixed_layer_thickness_defined_by_mixing_scheme" standard_name="ocean_mixed_layer_thickness_defined_by_mixing_scheme" level="2" /> 
     64     <field field_ref="mldkz5"       name='omlmax'   long_name="ocean_mixed_layer_thickness_defined_by_mixing_scheme" standard_name="ocean_mixed_layer_thickness_defined_by_mixing_scheme" level="2" operation="maximum" /> 
    6565   </file>    
    6666    
     
    194194   <file id="file14" name_suffix="_icemod_table2.2" >         <!-- scalar --> 
    195195     <field field_ref="ice_pres" /> 
    196      <field field_ref="ice_cover"    name="sic"       long_name="sea_ice_area_fraction"                     /> 
    197      <field field_ref="icethic_cea"  name="sit"       long_name="sea_ice_thickness"                         /> 
    198      <field field_ref="subl_ai_cea"  name="evap"      long_name="water_evaporation_flux" standard_name="water_evaporation_flux" /> 
    199      <field field_ref="snowthic_cea" name="snd"       long_name="surface_snow_thickness"                    /> 
     196     <field field_ref="ice_cover"    name="sic"       long_name="sea_ice_area_fraction"                                           /> 
     197     <field field_ref="icethic_cea"  name="sit"       long_name="sea_ice_thickness"                                               /> 
     198     <field field_ref="subl_ai_cea"  name="evap"      long_name="water_evaporation_flux" standard_name="water_evaporation_flux"   /> 
     199     <field field_ref="snowthic_cea" name="snd"       long_name="surface_snow_thickness"                                          /> 
    200200     <!-- snc : surface_snow_area_fraction : same as sic --> 
    201      <field field_ref="icealb_cea"   name="ialb"      /> 
     201     <field field_ref="icealb_cea"   name="ialb"      long_name="Bare Sea Ice Albedo"                                             /> 
    202202     <!-- ssi : Sea Ice Salinity : cte = sice = 6, expect in baltic sea = 2 --> 
    203      <field field_ref="ist_cea"      name="tsice"     /> 
     203     <field field_ref="ist_cea"      name="tsice"     long_name="Surface Temperature of Sea Ice"                                  /> 
    204204     <!-- tsnint : Temperature at Interface Between Sea Ice and Snow : not available --> 
    205205     <!-- pr : Surface Rainfall Rate into the Sea Ice Portion of the Grid Cell = 0 --> 
    206      <field field_ref="snow_ai_cea"  name="prsn"      /> 
     206     <field field_ref="snow_ai_cea"  name="prsn"      long_name="Surface Snowfall Rate into the Sea Ice Portion of the Grid Cell" /> 
    207207     <!-- ageice   : Age of Sea Ice : not available ??? --> 
    208208     <!-- grFrazil : Frazil Sea Ice Growth (Leads) Rate ??? --> 
    209209     <!-- grCongel : Congelation Sea Ice Growth Rate ??? --> 
    210      <field field_ref="licepro_cea"  name="grLateral" /> 
    211      <field field_ref="sntoice_cea"  name="snoToIce"  /> 
    212      <field field_ref="snowmel_cea"  name="snomelt"   /> 
    213      <field field_ref="ticemel_cea"  name="tmelt"     /> 
    214      <field field_ref="bicemel_cea"  name="bmelt"     /> 
     210     <field field_ref="licepro_cea"  name="grLateral" long_name="Lateral Sea Ice Growth Rate"                                     /> 
     211     <field field_ref="sntoice_cea"  name="snoToIce"  long_name="Snow-Ice Formation Rate"                                         /> 
     212     <field field_ref="snowmel_cea"  name="snomelt"   long_name="Snow Melt Rate"                                                  /> 
     213     <field field_ref="ticemel_cea"  name="tmelt"     long_name="Rate of Melt at Upper Surface of Sea Ice"                        /> 
     214     <field field_ref="bicemel_cea"  name="bmelt"     long_name="Rate of Melt at Sea Ice Base"                                    /> 
    215215     <!-- hcice  : Sea Ice Total Heat Content ??? --> 
    216      <field field_ref="qsr_ai_cea"   name="rsdssi"    long_name="surface_downwelling_shortwave_flux_in_air" /> 
     216     <field field_ref="qsr_ai_cea"   name="rsdssi"    long_name="surface_downwelling_shortwave_flux_in_air"                       /> 
    217217     <!-- rsussi : surface_upwelling_shortwave_flux_in_air ??? --> 
    218218     <!-- rldssi : surface_downwelling_longwave_flux_in_air ??? --> 
     
    220220     <!-- hfssi  : surface_upward_sensible_heat_flux ??? --> 
    221221     <!-- hflssi : surface_upward_latent_heat_flux ??? --> 
    222      <field field_ref="subl_ai_cea"  name="sblsi"     long_name="surface_snow_and_ice_sublimation_flux"     /> 
    223      <field field_ref="u_imasstr"    name="transix"   /> 
    224      <field field_ref="v_imasstr"    name="transiy"   /> 
    225      <field field_ref="fram_trans"   name="transifs"  /> 
    226      <field field_ref="utau_ice"     name="strairx"   /> 
    227      <field field_ref="vtau_ice"     name="strairy"   /> 
     222     <field field_ref="subl_ai_cea"  name="sblsi"     long_name="surface_snow_and_ice_sublimation_flux"                           /> 
     223     <field field_ref="u_imasstr"    name="transix"   long_name="Eastward Sea Ice Transport"                                      /> 
     224     <field field_ref="v_imasstr"    name="transiy"   long_name="Northward Sea Ice Transport"                                     /> 
     225     <field field_ref="fram_trans"   name="transifs"  long_name="Sea Ice Mass Transport Through Fram Strait"                      /> 
     226     <field field_ref="utau_ice"     name="strairx"   long_name="Eastward Atmospheric Stress On Sea Ice"                          /> 
     227     <field field_ref="vtau_ice"     name="strairy"   long_name="Northward Atmospheric Stress On Sea Ice"                         /> 
    228228     <!-- strocnx : Eastward Ocean Stress On Sea Ice ??? --> 
    229229     <!-- strocny : Northward Ocean Stress On Sea Ice ??? --> 
  • branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM/CONFIG/SHARED/field_def.xml

    r5199 r5342  
    4848 
    4949         <field id="mldkz5"       long_name="Turbocline depth (Kz = 5e-4)"                       standard_name="ocean_mixed_layer_thickness_defined_by_vertical_tracer_diffusivity"                unit="m"          /> 
    50          <field id="mldkz5_max"   long_name="Max of Turbocline depth (Kz = 5e-4)"                field_ref="mldkz5"     operation="maximum"                                                                          /> 
    5150         <field id="mldr10_1"     long_name="Mixed Layer Depth (dsigma = 0.01 wrt 10m)"          standard_name="ocean_mixed_layer_thickness_defined_by_sigma_theta"                                unit="m"          /> 
    5251         <field id="mldr10_1max"  long_name="Max of Mixed Layer Depth (dsigma = 0.01 wrt 10m)"   field_ref="mldr10_1"   operation="maximum"                                                                          /> 
  • branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM/CONFIG/SHARED/namelist_ref

    r5120 r5342  
    4343   ln_dimgnnn  = .false.   !  DIMG file format: 1 file for all processors (F) or by processor (T) 
    4444   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
     45   ln_cfmeta   = .false.   !  output additional data to netCDF files required for compliance with the CF metadata standard 
    4546   ln_clobber  = .false.   !  clobber (overwrite) an existing file 
    4647   nn_chunksz  =       0   !  chunksize (bytes) for NetCDF file (works only with iom_nf90 routines) 
  • branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r4990 r5342  
    135135      !!---------------------------------------------------------------------- 
    136136      USE ioipsl 
    137       NAMELIST/namrun/ nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl,   & 
    138          &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   & 
    139          &             nn_write, ln_dimgnnn, ln_mskland  , ln_clobber   , nn_chunksz, nn_euler 
     137      NAMELIST/namrun/ nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,   & 
     138         &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock  ,   & 
     139         &             nn_write, ln_dimgnnn, ln_mskland  , ln_cfmeta    , ln_clobber, nn_chunksz, nn_euler 
    140140      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    141141         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,                  & 
     
    182182         WRITE(numout,*) '      multi file dimgout              ln_dimgnnn = ', ln_dimgnnn 
    183183         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland 
     184         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta  = ', ln_cfmeta 
    184185         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber 
    185186         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz 
  • branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r4990 r5342  
    4141                                                       !:                  (T): 1 file per proc 
    4242   LOGICAL       ::   ln_mskland       !: mask land points in NetCDF outputs (costly: + ~15%) 
     43   LOGICAL       ::   ln_cfmeta        !: output additional data to netCDF files required for compliance with the CF metadata standard 
    4344   LOGICAL       ::   ln_clobber       !: clobber (overwrite) an existing file 
    4445   INTEGER       ::   nn_chunksz       !: chunksize (bytes) for NetCDF file (works only with iom_nf90 routines) 
  • branches/2014/dev_r5134_UKMO4_CF_compliance/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r5199 r5342  
    6161#if defined key_iomput 
    6262   PRIVATE iom_set_domain_attr, iom_set_axis_attr, iom_set_field_attr, iom_set_file_attr, iom_get_file_attr, iom_set_grid_attr 
    63    PRIVATE set_grid, set_scalar, set_xmlatt, set_mooring, iom_update_file_name, iom_sdate 
     63   PRIVATE set_grid, set_grid_bounds, set_scalar, set_xmlatt, set_mooring, iom_update_file_name, iom_sdate 
    6464# endif 
    6565 
     
    139139      ENDIF 
    140140 
     141      IF ( ln_cfmeta ) THEN   ! add cell bounds 
     142         CALL set_grid_bounds( "T", cdname )  
     143         CALL set_grid_bounds( "U", cdname ) 
     144         CALL set_grid_bounds( "V", cdname ) 
     145         CALL set_grid_bounds( "W", cdname ) 
     146      ENDIF 
    141147 
    142148      ! vertical grid definition 
     
    11091115 
    11101116   SUBROUTINE iom_set_domain_attr( cdid, ni_glo, nj_glo, ibegin, jbegin, ni, nj, zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj,   & 
    1111       &                                    data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask ) 
    1112       CHARACTER(LEN=*)                 , INTENT(in) ::   cdid 
    1113       INTEGER                , OPTIONAL, INTENT(in) ::   ni_glo, nj_glo, ibegin, jbegin, ni, nj 
    1114       INTEGER                , OPTIONAL, INTENT(in) ::   data_dim, data_ibegin, data_ni, data_jbegin, data_nj 
    1115       INTEGER                , OPTIONAL, INTENT(in) ::   zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj 
    1116       REAL(wp), DIMENSION(:) , OPTIONAL, INTENT(in) ::   lonvalue, latvalue 
    1117       LOGICAL, DIMENSION(:,:), OPTIONAL, INTENT(in) ::   mask 
     1117      &                                    data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask,     & 
     1118      &                                    nvertex, bounds_lon, bounds_lat ) 
     1119      CHARACTER(LEN=*)                   , INTENT(in) ::   cdid 
     1120      INTEGER                  , OPTIONAL, INTENT(in) ::   ni_glo, nj_glo, ibegin, jbegin, ni, nj 
     1121      INTEGER                  , OPTIONAL, INTENT(in) ::   data_dim, data_ibegin, data_ni, data_jbegin, data_nj 
     1122      INTEGER                  , OPTIONAL, INTENT(in) ::   zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj, nvertex 
     1123      REAL(wp), DIMENSION(:)   , OPTIONAL, INTENT(in) ::   lonvalue, latvalue 
     1124      REAL(wp), DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   bounds_lon, bounds_lat 
     1125      LOGICAL,  DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   mask 
    11181126 
    11191127      IF ( xios_is_valid_domain     (cdid) ) THEN 
     
    11211129            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
    11221130            &    zoom_ibegin=zoom_ibegin, zoom_jbegin=zoom_jbegin, zoom_ni=zoom_ni, zoom_nj=zoom_nj,                       & 
    1123             &    lonvalue=lonvalue, latvalue=latvalue,mask=mask ) 
     1131            &    lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon, bounds_lat=bounds_lat ) 
    11241132      ENDIF 
    11251133 
     
    11281136            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
    11291137            &    zoom_ibegin=zoom_ibegin, zoom_jbegin=zoom_jbegin, zoom_ni=zoom_ni, zoom_nj=zoom_nj,                       & 
    1130             &    lonvalue=lonvalue, latvalue=latvalue,mask=mask ) 
     1138            &    lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon, bounds_lat=bounds_lat ) 
    11311139      ENDIF 
    11321140      CALL xios_solve_inheritance() 
     
    12531261       
    12541262   END SUBROUTINE set_grid 
     1263 
     1264 
     1265   SUBROUTINE set_grid_bounds( cdgrd, cdname ) 
     1266      !!---------------------------------------------------------------------- 
     1267      !!                   ***  ROUTINE set_grid_bounds  *** 
     1268      !! 
     1269      !! ** Purpose :   define horizontal grid corners 
     1270      !! 
     1271      !!---------------------------------------------------------------------- 
     1272      CHARACTER(LEN=1) , INTENT(in) :: cdgrd 
     1273      CHARACTER(LEN=*) , INTENT(in) :: cdname 
     1274      ! 
     1275      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:)   :: z_bnds      ! Lat/lon coordinates of the vertices of cell (i,j) 
     1276      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)     :: z_cnr       ! Lat/lon coordinates of a contiguous vertex of cell (i,j) 
     1277      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)     :: z_pnt       ! Lat/lon coordinates of the point of cell (i,j) 
     1278      REAL(wp), ALLOCATABLE, DIMENSION(:,:)       :: z_fld       ! Working array to determine where to rotate cells 
     1279      REAL(wp), ALLOCATABLE, DIMENSION(:,:)       :: z_rot       ! Lat/lon working array for rotation of cells 
     1280      ! 
     1281      INTEGER :: icnr, jcnr                                      ! Offset such that the vertex coordinate (i+icnr,j+jcnr) 
     1282      !                                                          ! represents the bottom-left corner of cell (i,j) 
     1283      INTEGER :: ji, jj, jn, ni, nj 
     1284 
     1285      ALLOCATE( z_bnds(4,jpi,jpj,2), z_cnr(jpi,jpj,2), z_pnt(jpi,jpj,2), z_fld(jpi,jpj), z_rot(4,2)  ) 
     1286 
     1287      ! Grid information 
     1288      SELECT CASE ( TRIM(cdgrd) ) 
     1289         CASE ('T', 'W') 
     1290            icnr = -1 ; jcnr = -1 
     1291            IF( TRIM(cdname) == "nemo_crs" ) THEN 
     1292               z_cnr(:,:,1) = gphif_crs ; z_cnr(:,:,2) = glamf_crs 
     1293               z_pnt(:,:,1) = gphit_crs ; z_pnt(:,:,2) = glamt_crs 
     1294            ELSE 
     1295               z_cnr(:,:,1) = gphif ; z_cnr(:,:,2) = glamf 
     1296               z_pnt(:,:,1) = gphit ; z_pnt(:,:,2) = glamt 
     1297            ENDIF 
     1298         CASE ('U') 
     1299            icnr =  0 ; jcnr = -1 
     1300            IF( TRIM(cdname) == "nemo_crs" ) THEN 
     1301               z_cnr(:,:,1) = gphiv_crs ; z_cnr(:,:,2) = glamv_crs 
     1302               z_pnt(:,:,1) = gphiu_crs ; z_pnt(:,:,2) = glamu_crs 
     1303            ELSE 
     1304               z_cnr(:,:,1) = gphiv ; z_cnr(:,:,2) = glamv 
     1305               z_pnt(:,:,1) = gphiu ; z_pnt(:,:,2) = glamu 
     1306            ENDIF 
     1307         CASE ('V') 
     1308            icnr = -1 ; jcnr =  0 
     1309            IF( TRIM(cdname) == "nemo_crs" ) THEN 
     1310               z_cnr(:,:,1) = gphiu_crs ; z_cnr(:,:,2) = glamu_crs 
     1311               z_pnt(:,:,1) = gphiv_crs ; z_pnt(:,:,2) = glamv_crs 
     1312            ELSE 
     1313               z_cnr(:,:,1) = gphiu ; z_cnr(:,:,2) = glamu 
     1314               z_pnt(:,:,1) = gphiv ; z_pnt(:,:,2) = glamv 
     1315            ENDIF 
     1316      END SELECT 
     1317 
     1318      ni = nlei-nldi+1 ; nj = nlej-nldj+1  ! Dimensions of subdomain interior 
     1319 
     1320      z_fld(:,:) = 1._wp 
     1321      CALL lbc_lnk( z_fld, cdgrd, -1. )    ! Working array for location of northfold 
     1322 
     1323      ! Cell vertices that can be defined 
     1324      DO jj = 2, jpjm1 
     1325         DO ji = 2, jpim1 
     1326            z_bnds(1,ji,jj,:) = z_cnr(ji+icnr,  jj+jcnr  ,:) ! Bottom-left 
     1327            z_bnds(2,ji,jj,:) = z_cnr(ji+icnr+1,jj+jcnr  ,:) ! Bottom-right 
     1328            z_bnds(3,ji,jj,:) = z_cnr(ji+icnr+1,jj+jcnr+1,:) ! Top-right 
     1329            z_bnds(4,ji,jj,:) = z_cnr(ji+icnr,  jj+jcnr+1,:) ! Top-left 
     1330         END DO 
     1331      END DO 
     1332 
     1333      ! Cell vertices on boundries 
     1334      DO jn = 1, 4 
     1335         CALL lbc_lnk( z_bnds(jn,:,:,1), cdgrd, 1., pval=999._wp ) 
     1336         CALL lbc_lnk( z_bnds(jn,:,:,2), cdgrd, 1., pval=999._wp ) 
     1337      END DO 
     1338 
     1339      ! Zero-size cells at closed boundaries 
     1340      IF( (nbondi == -1 .OR. nbondi == 2) .AND. .NOT. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6) ) THEN 
     1341         DO jn = 1, 4  ;  z_bnds(jn,1,:,:) = z_pnt(1,:,:)        ;  END DO      ! (West or jpni = 1), closed E-W 
     1342      ENDIF 
     1343      IF( (nbondi == 1 .OR. nbondi == 2) .AND. .NOT. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6) ) THEN 
     1344         DO jn = 1, 4  ;  z_bnds(jn,nlci,:,:) = z_pnt(nlci,:,:)  ;  END DO      ! (East or jpni = 1), closed E-W 
     1345      ENDIF 
     1346      IF( nbondj == -1 .OR. (nbondj == 2 .AND. jperio /= 2) ) THEN 
     1347         DO jn = 1, 4  ;  z_bnds(jn,:,1,:) = z_pnt(:,1,:)        ;  END DO      ! South or (jpnj = 1, not symmetric) 
     1348      ENDIF 
     1349      IF( (nbondj == 1 .OR. nbondj == 2) .AND. jperio  < 3 ) THEN 
     1350         DO jn = 1, 4  ;  z_bnds(jn,:,nlcj,:) = z_pnt(:,nlcj,:)  ;  END DO      ! (North or jpnj = 1), no north fold 
     1351      ENDIF 
     1352 
     1353! ===================================================================================================== 
     1354!             Do we need to set zero-size cells at Mediterranean / Persian Gulf region? 
     1355! ===================================================================================================== 
     1356 
     1357      ! Rotate cells at the north fold 
     1358      IF( (nbondj == 1 .OR. nbondj == 2) .AND. jperio >= 3 ) THEN 
     1359         DO jj = 1, jpj 
     1360            DO ji = 1, jpi 
     1361               IF( z_fld(ji,jj) == -1. ) THEN 
     1362                  z_rot(1,:) = z_bnds(3,ji,jj,:) ; z_rot(2,:) = z_bnds(4,ji,jj,:) 
     1363                  z_rot(3,:) = z_bnds(1,ji,jj,:) ; z_rot(4,:) = z_bnds(2,ji,jj,:) 
     1364                  z_bnds(:,ji,jj,:) = z_rot(:,:) 
     1365               ENDIF 
     1366            END DO 
     1367         END DO 
     1368 
     1369      ! Invert cells at the symmetric equator 
     1370      ELSE IF( nbondj == 2 .AND. jperio == 2 ) THEN 
     1371         DO ji = 1, jpi 
     1372            z_rot(1:2,:) = z_bnds(3:4,ji,1,:) 
     1373            z_rot(3:4,:) = z_bnds(1:2,ji,1,:) 
     1374            z_bnds(:,ji,1,:) = z_rot(:,:) 
     1375         END DO 
     1376      ENDIF 
     1377 
     1378      CALL iom_set_domain_attr("grid_"//cdgrd, bounds_lat = RESHAPE(z_bnds(:,nldi:nlei,nldj:nlej,1),(/ 4,ni*nj /)),           & 
     1379                                               bounds_lon = RESHAPE(z_bnds(:,nldi:nlei,nldj:nlej,2),(/ 4,ni*nj /)), nvertex=4 ) 
     1380 
     1381      DEALLOCATE( z_bnds, z_cnr, z_pnt, z_fld, z_rot )  
     1382 
     1383   END SUBROUTINE set_grid_bounds 
    12551384 
    12561385 
Note: See TracChangeset for help on using the changeset viewer.