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 5989 for branches/2014/dev_r4650_UKMO10_Tidally_Meaned_Diagnostics/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90 – NEMO

Ignore:
Timestamp:
2015-12-03T09:10:32+01:00 (8 years ago)
Author:
deazer
Message:

Merging TMB and 25h diagnostics to head of trunk
added brief documentation

File:
1 edited

Legend:

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

    r5260 r5989  
    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 
     
    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 
    103107      IF( TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname) 
    104 # if defined key_mpp_mpi 
    105108      CALL xios_context_initialize(TRIM(clname), mpi_comm_opa) 
    106 # else 
    107       CALL xios_context_initialize(TRIM(clname), 0) 
    108 # endif 
    109109      CALL iom_swap( cdname ) 
    110110 
     
    121121      CALL set_scalar 
    122122 
    123       IF( TRIM(cdname) == "nemo" ) THEN   
     123      IF( TRIM(cdname) == TRIM(cxios_context) ) THEN   
    124124         CALL set_grid( "T", glamt, gphit )  
    125125         CALL set_grid( "U", glamu, gphiu ) 
    126126         CALL set_grid( "V", glamv, gphiv ) 
    127127         CALL set_grid( "W", glamt, gphit ) 
    128       ENDIF 
    129  
    130       IF( TRIM(cdname) == "nemo_crs" ) THEN   
     128         CALL set_grid_znl( gphit ) 
     129         ! 
     130         IF( ln_cfmeta ) THEN   ! Add additional grid metadata 
     131            CALL iom_set_domain_attr("grid_T", area = e1e2t(nldi:nlei, nldj:nlej)) 
     132            CALL iom_set_domain_attr("grid_U", area = e1e2u(nldi:nlei, nldj:nlej)) 
     133            CALL iom_set_domain_attr("grid_V", area = e1e2v(nldi:nlei, nldj:nlej)) 
     134            CALL iom_set_domain_attr("grid_W", area = e1e2t(nldi:nlei, nldj:nlej)) 
     135            CALL set_grid_bounds( "T", glamf, gphif, glamt, gphit ) 
     136            CALL set_grid_bounds( "U", glamv, gphiv, glamu, gphiu ) 
     137            CALL set_grid_bounds( "V", glamu, gphiu, glamv, gphiv ) 
     138            CALL set_grid_bounds( "W", glamf, gphif, glamt, gphit ) 
     139         ENDIF 
     140      ENDIF 
     141 
     142      IF( TRIM(cdname) == TRIM(cxios_context)//"_crs" ) THEN   
    131143         CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    132144         ! 
     
    135147         CALL set_grid( "V", glamv_crs, gphiv_crs )  
    136148         CALL set_grid( "W", glamt_crs, gphit_crs )  
     149         CALL set_grid_znl( gphit_crs ) 
    137150          ! 
    138151         CALL dom_grid_glo   ! Return to parent grid domain 
    139       ENDIF 
    140  
     152         ! 
     153         IF( ln_cfmeta ) THEN   ! Add additional grid metadata 
     154            CALL iom_set_domain_attr("grid_T", area = e1e2t_crs(nldi:nlei, nldj:nlej)) 
     155            CALL iom_set_domain_attr("grid_U", area = e1u_crs(nldi:nlei, nldj:nlej) * e2u_crs(nldi:nlei, nldj:nlej)) 
     156            CALL iom_set_domain_attr("grid_V", area = e1v_crs(nldi:nlei, nldj:nlej) * e2v_crs(nldi:nlei, nldj:nlej)) 
     157            CALL iom_set_domain_attr("grid_W", area = e1e2t_crs(nldi:nlei, nldj:nlej)) 
     158            CALL set_grid_bounds( "T", glamf_crs, gphif_crs, glamt_crs, gphit_crs ) 
     159            CALL set_grid_bounds( "U", glamv_crs, gphiv_crs, glamu_crs, gphiu_crs ) 
     160            CALL set_grid_bounds( "V", glamu_crs, gphiu_crs, glamv_crs, gphiv_crs ) 
     161            CALL set_grid_bounds( "W", glamf_crs, gphif_crs, glamt_crs, gphit_crs ) 
     162         ENDIF 
     163      ENDIF 
    141164 
    142165      ! vertical grid definition 
     
    145168      CALL iom_set_axis_attr( "depthv", gdept_1d ) 
    146169      CALL iom_set_axis_attr( "depthw", gdepw_1d ) 
     170 
     171      ! Add vertical grid bounds 
     172      z_bnds(:      ,1) = gdepw_1d(:) 
     173      z_bnds(1:jpkm1,2) = gdepw_1d(2:jpk) 
     174      z_bnds(jpk:   ,2) = gdepw_1d(jpk) + e3t_1d(jpk) 
     175      CALL iom_set_axis_attr( "deptht", bounds=z_bnds ) 
     176      CALL iom_set_axis_attr( "depthu", bounds=z_bnds ) 
     177      CALL iom_set_axis_attr( "depthv", bounds=z_bnds ) 
     178      z_bnds(:    ,2) = gdept_1d(:) 
     179      z_bnds(2:jpk,1) = gdept_1d(1:jpkm1) 
     180      z_bnds(1    ,1) = gdept_1d(1) - e3w_1d(1) 
     181      CALL iom_set_axis_attr( "depthw", bounds=z_bnds ) 
     182 
    147183# if defined key_floats 
    148184      CALL iom_set_axis_attr( "nfloat", (/ (REAL(ji,wp), ji=1,nfloat) /) ) 
     
    152188#endif 
    153189      CALL iom_set_axis_attr( "icbcla", class_num ) 
     190      CALL iom_set_axis_attr( "iax_20C", (/ REAL(20,wp) /) ) 
     191      CALL iom_set_axis_attr( "iax_28C", (/ REAL(28,wp) /) ) 
    154192       
    155193      ! automatic definitions of some of the xml attributs 
     
    162200       
    163201      CALL xios_update_calendar(0) 
     202 
     203      DEALLOCATE( z_bnds ) 
     204 
    164205#endif 
    165206       
     
    862903               IF( zofs /= 0. )   pv_r1d(:) = pv_r1d(:) + zofs 
    863904            ELSEIF( PRESENT(pv_r2d) ) THEN 
    864 !CDIR COLLAPSE 
    865905               IF( zscf /= 1.)   pv_r2d(:,:) = pv_r2d(:,:) * zscf 
    866 !CDIR COLLAPSE 
    867906               IF( zofs /= 0.)   pv_r2d(:,:) = pv_r2d(:,:) + zofs 
    868907            ELSEIF( PRESENT(pv_r3d) ) THEN 
    869 !CDIR COLLAPSE 
    870908               IF( zscf /= 1.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 
    871 !CDIR COLLAPSE 
    872909               IF( zofs /= 0.)   pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 
    873910            ENDIF 
     
    11071144 
    11081145   SUBROUTINE iom_set_domain_attr( cdid, ni_glo, nj_glo, ibegin, jbegin, ni, nj, zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj,   & 
    1109       &                                    data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask ) 
    1110       CHARACTER(LEN=*)                 , INTENT(in) ::   cdid 
    1111       INTEGER                , OPTIONAL, INTENT(in) ::   ni_glo, nj_glo, ibegin, jbegin, ni, nj 
    1112       INTEGER                , OPTIONAL, INTENT(in) ::   data_dim, data_ibegin, data_ni, data_jbegin, data_nj 
    1113       INTEGER                , OPTIONAL, INTENT(in) ::   zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj 
    1114       REAL(wp), DIMENSION(:) , OPTIONAL, INTENT(in) ::   lonvalue, latvalue 
    1115       LOGICAL, DIMENSION(:,:), OPTIONAL, INTENT(in) ::   mask 
     1146      &                                    data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask,     & 
     1147      &                                    nvertex, bounds_lon, bounds_lat, area ) 
     1148      CHARACTER(LEN=*)                   , INTENT(in) ::   cdid 
     1149      INTEGER                  , OPTIONAL, INTENT(in) ::   ni_glo, nj_glo, ibegin, jbegin, ni, nj 
     1150      INTEGER                  , OPTIONAL, INTENT(in) ::   data_dim, data_ibegin, data_ni, data_jbegin, data_nj 
     1151      INTEGER                  , OPTIONAL, INTENT(in) ::   zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj, nvertex 
     1152      REAL(wp), DIMENSION(:)   , OPTIONAL, INTENT(in) ::   lonvalue, latvalue 
     1153      REAL(wp), DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   bounds_lon, bounds_lat, area 
     1154      LOGICAL,  DIMENSION(:,:) , OPTIONAL, INTENT(in) ::   mask 
    11161155 
    11171156      IF ( xios_is_valid_domain     (cdid) ) THEN 
     
    11191158            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
    11201159            &    zoom_ibegin=zoom_ibegin, zoom_jbegin=zoom_jbegin, zoom_ni=zoom_ni, zoom_nj=zoom_nj,                       & 
    1121             &    lonvalue=lonvalue, latvalue=latvalue,mask=mask ) 
     1160            &    lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon,                  & 
     1161            &    bounds_lat=bounds_lat, area=area ) 
    11221162      ENDIF 
    11231163 
     
    11261166            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
    11271167            &    zoom_ibegin=zoom_ibegin, zoom_jbegin=zoom_jbegin, zoom_ni=zoom_ni, zoom_nj=zoom_nj,                       & 
    1128             &    lonvalue=lonvalue, latvalue=latvalue,mask=mask ) 
     1168            &    lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon,                  & 
     1169            &    bounds_lat=bounds_lat, area=area ) 
    11291170      ENDIF 
    11301171      CALL xios_solve_inheritance() 
     
    11331174 
    11341175 
    1135    SUBROUTINE iom_set_axis_attr( cdid, paxis ) 
     1176   SUBROUTINE iom_set_axis_attr( cdid, paxis, bounds ) 
    11361177      CHARACTER(LEN=*)      , INTENT(in) ::   cdid 
    1137       REAL(wp), DIMENSION(:), INTENT(in) ::   paxis 
    1138       IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, size=size(paxis),value=paxis ) 
    1139       IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, size=size(paxis),value=paxis ) 
     1178      REAL(wp), DIMENSION(:)  , OPTIONAL, INTENT(in) ::   paxis 
     1179      REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(in) ::   bounds 
     1180      IF ( PRESENT(paxis) ) THEN 
     1181         IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, size=SIZE(paxis), value=paxis ) 
     1182         IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, size=SIZE(paxis), value=paxis ) 
     1183      ENDIF 
     1184      IF ( xios_is_valid_axis     (cdid) )   CALL xios_set_axis_attr     ( cdid, bounds=bounds ) 
     1185      IF ( xios_is_valid_axisgroup(cdid) )   CALL xios_set_axisgroup_attr( cdid, bounds=bounds ) 
    11401186      CALL xios_solve_inheritance() 
    11411187   END SUBROUTINE iom_set_axis_attr 
     
    11461192      CHARACTER(LEN=*),OPTIONAL , INTENT(in) ::   freq_op 
    11471193      CHARACTER(LEN=*),OPTIONAL , INTENT(in) ::   freq_offset 
    1148       IF ( xios_is_valid_field     (cdid) )   CALL xios_set_field_attr     ( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
    1149       IF ( xios_is_valid_fieldgroup(cdid) )   CALL xios_set_fieldgroup_attr( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
     1194      IF ( xios_is_valid_field     (cdid) )   CALL xios_set_field_attr       & 
     1195    &     ( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
     1196      IF ( xios_is_valid_fieldgroup(cdid) )   CALL xios_set_fieldgroup_attr  & 
     1197    &                    ( cdid, freq_op=freq_op, freq_offset=freq_offset ) 
    11501198      CALL xios_solve_inheritance() 
    11511199   END SUBROUTINE iom_set_field_attr 
     
    12001248      CALL iom_swap( cdname )   ! swap to cdname context 
    12011249      CALL xios_update_calendar(kt) 
    1202       IF( cdname /= "nemo" ) CALL iom_swap( "nemo" )   ! return back to nemo context 
     1250      IF( cdname /= TRIM(cxios_context) ) CALL iom_swap( TRIM(cxios_context) )   ! return back to nemo context 
    12031251      ! 
    12041252   END SUBROUTINE iom_setkt 
     
    12101258         CALL iom_swap( cdname )   ! swap to cdname context 
    12111259         CALL xios_context_finalize() ! finalize the context 
    1212          IF( cdname /= "nemo" ) CALL iom_swap( "nemo" )   ! return back to nemo context 
     1260         IF( cdname /= TRIM(cxios_context) ) CALL iom_swap( TRIM(cxios_context) )   ! return back to nemo context 
    12131261      ENDIF 
    12141262      ! 
     
    12531301 
    12541302 
     1303   SUBROUTINE set_grid_bounds( cdgrd, plon_cnr, plat_cnr, plon_pnt, plat_pnt ) 
     1304      !!---------------------------------------------------------------------- 
     1305      !!                   ***  ROUTINE set_grid_bounds  *** 
     1306      !! 
     1307      !! ** Purpose :   define horizontal grid corners 
     1308      !! 
     1309      !!---------------------------------------------------------------------- 
     1310      CHARACTER(LEN=1) , INTENT(in) :: cdgrd 
     1311      ! 
     1312      REAL(wp), DIMENSION(jpi,jpj), INTENT(in)           :: plon_cnr, plat_cnr  ! Lat/lon coordinates of a contiguous vertex of cell (i,j) 
     1313      REAL(wp), DIMENSION(jpi,jpj), OPTIONAL, INTENT(in) :: plon_pnt, plat_pnt  ! Lat/lon coordinates of the point of cell (i,j) 
     1314      ! 
     1315      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:)   :: z_bnds      ! Lat/lon coordinates of the vertices of cell (i,j) 
     1316      REAL(wp), ALLOCATABLE, DIMENSION(:,:)       :: z_fld       ! Working array to determine where to rotate cells 
     1317      REAL(wp), ALLOCATABLE, DIMENSION(:,:)       :: z_rot       ! Lat/lon working array for rotation of cells 
     1318      ! 
     1319      INTEGER :: icnr, jcnr                                      ! Offset such that the vertex coordinate (i+icnr,j+jcnr) 
     1320      !                                                          ! represents the bottom-left corner of cell (i,j) 
     1321      INTEGER :: ji, jj, jn, ni, nj 
     1322 
     1323      ALLOCATE( z_bnds(4,jpi,jpj,2), z_fld(jpi,jpj), z_rot(4,2)  ) 
     1324 
     1325      ! Offset of coordinate representing bottom-left corner 
     1326      SELECT CASE ( TRIM(cdgrd) ) 
     1327         CASE ('T', 'W') 
     1328            icnr = -1 ; jcnr = -1 
     1329         CASE ('U') 
     1330            icnr =  0 ; jcnr = -1 
     1331         CASE ('V') 
     1332            icnr = -1 ; jcnr =  0 
     1333      END SELECT 
     1334 
     1335      ni = nlei-nldi+1 ; nj = nlej-nldj+1  ! Dimensions of subdomain interior 
     1336 
     1337      z_fld(:,:) = 1._wp 
     1338      CALL lbc_lnk( z_fld, cdgrd, -1. )    ! Working array for location of northfold 
     1339 
     1340      ! Cell vertices that can be defined 
     1341      DO jj = 2, jpjm1 
     1342         DO ji = 2, jpim1 
     1343            z_bnds(1,ji,jj,1) = plat_cnr(ji+icnr,  jj+jcnr  ) ! Bottom-left 
     1344            z_bnds(2,ji,jj,1) = plat_cnr(ji+icnr+1,jj+jcnr  ) ! Bottom-right 
     1345            z_bnds(3,ji,jj,1) = plat_cnr(ji+icnr+1,jj+jcnr+1) ! Top-right 
     1346            z_bnds(4,ji,jj,1) = plat_cnr(ji+icnr,  jj+jcnr+1) ! Top-left 
     1347            z_bnds(1,ji,jj,2) = plon_cnr(ji+icnr,  jj+jcnr  ) ! Bottom-left 
     1348            z_bnds(2,ji,jj,2) = plon_cnr(ji+icnr+1,jj+jcnr  ) ! Bottom-right 
     1349            z_bnds(3,ji,jj,2) = plon_cnr(ji+icnr+1,jj+jcnr+1) ! Top-right 
     1350            z_bnds(4,ji,jj,2) = plon_cnr(ji+icnr,  jj+jcnr+1) ! Top-left 
     1351         END DO 
     1352      END DO 
     1353 
     1354      ! Cell vertices on boundries 
     1355      DO jn = 1, 4 
     1356         CALL lbc_lnk( z_bnds(jn,:,:,1), cdgrd, 1., pval=999._wp ) 
     1357         CALL lbc_lnk( z_bnds(jn,:,:,2), cdgrd, 1., pval=999._wp ) 
     1358      END DO 
     1359 
     1360      ! Zero-size cells at closed boundaries if cell points provided, 
     1361      ! otherwise they are closed cells with unrealistic bounds 
     1362      IF( PRESENT(plon_pnt) .AND. PRESENT(plat_pnt) ) THEN 
     1363         IF( (nbondi == -1 .OR. nbondi == 2) .AND. .NOT. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6) ) THEN 
     1364            DO jn = 1, 4        ! (West or jpni = 1), closed E-W 
     1365               z_bnds(jn,1,:,1) = plat_pnt(1,:)  ;  z_bnds(jn,1,:,2) = plon_pnt(1,:) 
     1366            END DO 
     1367         ENDIF 
     1368         IF( (nbondi == 1 .OR. nbondi == 2) .AND. .NOT. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6) ) THEN 
     1369            DO jn = 1, 4        ! (East or jpni = 1), closed E-W 
     1370               z_bnds(jn,nlci,:,1) = plat_pnt(nlci,:)  ;  z_bnds(jn,nlci,:,2) = plon_pnt(nlci,:) 
     1371            END DO 
     1372         ENDIF 
     1373         IF( nbondj == -1 .OR. (nbondj == 2 .AND. jperio /= 2) ) THEN 
     1374            DO jn = 1, 4        ! South or (jpnj = 1, not symmetric) 
     1375               z_bnds(jn,:,1,1) = plat_pnt(:,1)  ;  z_bnds(jn,:,1,2) = plon_pnt(:,1) 
     1376            END DO 
     1377         ENDIF 
     1378         IF( (nbondj == 1 .OR. nbondj == 2) .AND. jperio  < 3 ) THEN 
     1379            DO jn = 1, 4        ! (North or jpnj = 1), no north fold 
     1380               z_bnds(jn,:,nlcj,1) = plat_pnt(:,nlcj)  ;  z_bnds(jn,:,nlcj,2) = plon_pnt(:,nlcj) 
     1381            END DO 
     1382         ENDIF 
     1383      ENDIF 
     1384 
     1385      ! Rotate cells at the north fold 
     1386      IF( (nbondj == 1 .OR. nbondj == 2) .AND. jperio >= 3 ) THEN 
     1387         DO jj = 1, jpj 
     1388            DO ji = 1, jpi 
     1389               IF( z_fld(ji,jj) == -1. ) THEN 
     1390                  z_rot(1,:) = z_bnds(3,ji,jj,:) ; z_rot(2,:) = z_bnds(4,ji,jj,:) 
     1391                  z_rot(3,:) = z_bnds(1,ji,jj,:) ; z_rot(4,:) = z_bnds(2,ji,jj,:) 
     1392                  z_bnds(:,ji,jj,:) = z_rot(:,:) 
     1393               ENDIF 
     1394            END DO 
     1395         END DO 
     1396 
     1397      ! Invert cells at the symmetric equator 
     1398      ELSE IF( nbondj == 2 .AND. jperio == 2 ) THEN 
     1399         DO ji = 1, jpi 
     1400            z_rot(1:2,:) = z_bnds(3:4,ji,1,:) 
     1401            z_rot(3:4,:) = z_bnds(1:2,ji,1,:) 
     1402            z_bnds(:,ji,1,:) = z_rot(:,:) 
     1403         END DO 
     1404      ENDIF 
     1405 
     1406      CALL iom_set_domain_attr("grid_"//cdgrd, bounds_lat = RESHAPE(z_bnds(:,nldi:nlei,nldj:nlej,1),(/ 4,ni*nj /)),           & 
     1407                                               bounds_lon = RESHAPE(z_bnds(:,nldi:nlei,nldj:nlej,2),(/ 4,ni*nj /)), nvertex=4 ) 
     1408 
     1409      DEALLOCATE( z_bnds, z_fld, z_rot )  
     1410 
     1411   END SUBROUTINE set_grid_bounds 
     1412 
     1413 
     1414   SUBROUTINE set_grid_znl( plat ) 
     1415      !!---------------------------------------------------------------------- 
     1416      !!                     ***  ROUTINE set_grid_znl  *** 
     1417      !! 
     1418      !! ** Purpose :   define grids for zonal mean 
     1419      !! 
     1420      !!---------------------------------------------------------------------- 
     1421      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   plat 
     1422      ! 
     1423      REAL(wp), DIMENSION(:), ALLOCATABLE  ::   zlon 
     1424      INTEGER  :: ni,nj, ix, iy 
     1425 
     1426       
     1427      ni=nlei-nldi+1 ; nj=nlej-nldj+1            ! define zonal mean domain (jpj*jpk) 
     1428      ALLOCATE( zlon(ni*nj) )       ;       zlon(:) = 0. 
     1429 
     1430      CALL iom_set_domain_attr("gznl", ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-1, jbegin=njmpp+nldj-1, ni=ni, nj=nj) 
     1431      CALL iom_set_domain_attr("gznl", data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj) 
     1432      CALL iom_set_domain_attr("gznl", lonvalue = zlon,   & 
     1433         &                             latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
     1434      ! 
     1435      CALL dom_ngb( 180., 90., ix, iy, 'T' ) !  i-line that passes near the North Pole : Reference latitude (used in plots) 
     1436      CALL iom_set_domain_attr ('ptr', zoom_ibegin=ix, zoom_nj=jpjglo) 
     1437      CALL iom_update_file_name('ptr') 
     1438      ! 
     1439   END SUBROUTINE set_grid_znl 
     1440 
    12551441   SUBROUTINE set_scalar 
    12561442      !!---------------------------------------------------------------------- 
     
    12601446      !! 
    12611447      !!---------------------------------------------------------------------- 
    1262       REAL(wp), DIMENSION(1) ::   zz = 1. 
     1448      REAL(wp), DIMENSION(1)   ::   zz = 1. 
    12631449      !!---------------------------------------------------------------------- 
    12641450      CALL iom_set_domain_attr('scalarpoint', ni_glo=jpnij, nj_glo=1, ibegin=narea, jbegin=1, ni=1, nj=1) 
    12651451      CALL iom_set_domain_attr('scalarpoint', data_dim=2, data_ibegin = 1, data_ni = 1, data_jbegin = 1, data_nj = 1) 
     1452       
    12661453      zz=REAL(narea,wp) 
    12671454      CALL iom_set_domain_attr('scalarpoint', lonvalue=zz, latvalue=zz) 
     
    13371524      CALL set_mooring( zlonpira, zlatpira ) 
    13381525 
    1339       ! diaptr : zonal mean  
    1340       CALL dom_ngb( 180., 90., ix, iy, 'T' ) !  i-line that passes near the North Pole : Reference latitude (used in plots) 
    1341       CALL iom_set_domain_attr ('ptr', zoom_ibegin=ix, zoom_nj=jpjglo) 
    1342       CALL iom_update_file_name('ptr') 
    1343       ! 
    13441526       
    13451527   END SUBROUTINE set_xmlatt 
     
    14891671            END DO 
    14901672 
     1673            IF( jn == 1 .AND. TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 
    14911674            IF( jn == 1 )   CALL iom_set_file_attr( cdid, name        = clname ) 
    14921675            IF( jn == 2 )   CALL iom_set_file_attr( cdid, name_suffix = clname ) 
     
    15361719      ENDIF 
    15371720       
     1721!$AGRIF_DO_NOT_TREAT       
     1722! Should be fixed in the conv 
    15381723      IF( llfull ) THEN  
    15391724         clfmt = TRIM(clfmt)//",'_',i2.2,':',i2.2,':',i2.2" 
     
    15461731         WRITE(iom_sdate, '('//TRIM(clfmt)//')') iyear, imonth, iday                          ! date of the end of run 
    15471732      ENDIF 
     1733!$AGRIF_END_DO_NOT_TREAT       
    15481734 
    15491735   END FUNCTION iom_sdate 
Note: See TracChangeset for help on using the changeset viewer.