Ignore:
Timestamp:
05/29/15 11:16:25 (9 years ago)
Author:
aclsce
Message:

Modifications to have correct NEMO diaptr files with mask.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • CONFIG/UNIFORM/v6_rc0/IPSLCM6/SOURCES/NEMO/iom.F90

    r2372 r2531  
    127127         CALL set_grid( "V", glamv, gphiv ) 
    128128         CALL set_grid( "W", glamt, gphit ) 
     129         CALL set_grid_znl( gphit ) 
    129130      ENDIF 
    130131 
     
    136137         CALL set_grid( "V", glamv_crs, gphiv_crs )  
    137138         CALL set_grid( "W", glamt_crs, gphit_crs )  
     139         CALL set_grid_znl( gphit_crs ) 
    138140          ! 
    139141         CALL dom_grid_glo   ! Return to parent grid domain 
     
    12121214 
    12131215 
     1216   SUBROUTINE set_grid_znl( plat ) 
     1217      !!---------------------------------------------------------------------- 
     1218      !!                     ***  ROUTINE set_grid_znl  *** 
     1219      !! 
     1220      !! ** Purpose :   define 2D grids for zonal mean 
     1221      !! 
     1222      !!---------------------------------------------------------------------- 
     1223      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   plat 
     1224      ! 
     1225      REAL(wp), DIMENSION(:), ALLOCATABLE  ::   zlon 
     1226      INTEGER  :: ni,nj, ix, iy 
     1227 
     1228       
     1229      ni=nlei-nldi+1 ; nj=nlej-nldj+1 
     1230      ALLOCATE( zlon(ni*nj) )       ;       zlon(:) = 0. 
     1231 
     1232      CALL iom_set_domain_attr("gznl", ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-1, jbegin=njmpp+nldj-1, ni=ni, nj=nj) 
     1233      CALL iom_set_domain_attr("gznl", data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj) 
     1234      CALL iom_set_domain_attr("gznl", lonvalue = zlon,   & 
     1235         &                             latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
     1236      CALL dom_ngb( 180., 90., ix, iy, 'T' ) !  i-line that passes near the North Pole : Reference latitude (used in plots) 
     1237      CALL iom_set_domain_attr ('ptr', zoom_ibegin=ix, zoom_nj=jpjglo) 
     1238      CALL iom_update_file_name('ptr') 
     1239      ! 
     1240   END SUBROUTINE set_grid_znl 
     1241 
     1242 
    12141243   SUBROUTINE set_scalar 
    12151244      !!---------------------------------------------------------------------- 
     
    12911320      zlatpira = (/ -19.0, -14.0,  -8.0, 0.0, 4.0, 8.0, 12.0, 15.0, 20.0 /) 
    12921321      CALL set_mooring( zlonpira, zlatpira ) 
    1293      
    1294       ! diaptr : zonal mean  
    1295       CALL iom_set_domain_attr ('ptr', zoom_ibegin=nxline, zoom_nj=jpjglo) 
    1296       CALL iom_update_file_name('ptr') 
    12971322      ! 
    12981323   END SUBROUTINE set_xmlatt 
Note: See TracChangeset for help on using the changeset viewer.