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.
crs.F90 in branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/CRS – NEMO

source: branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/CRS/crs.F90 @ 4015

Last change on this file since 4015 was 4015, checked in by cetlod, 11 years ago

2013/dev_r3940_CNRS4_IOCRS: 1st step, add new routines for outputs coarsening

File size: 18.8 KB
Line 
1MODULE crs   
2   !!======================================================================
3   !!                         ***  MODULE crs_dom  ***
4   !!        Declare the coarse grid domain and other public variables
5   !!        then allocate them if needed.
6   !!======================================================================
7   !!  History     2012-06  Editing  (J. Simeon, G. Madec, C. Ethe, C. Calone) Original code
8   !!----------------------------------------------------------------------
9   USE par_oce 
10   USE dom_oce
11   USE in_out_manager
12
13
14   IMPLICIT NONE
15   PUBLIC
16
17   
18   PUBLIC crs_dom_alloc  ! Called from crsini.F90
19   PUBLIC dom_grid_glo   
20   PUBLIC dom_grid_crs 
21
22      ! Domain variables
23      INTEGER  ::  jpiglo_crs ,   &             !: 1st dimension of global coarse grid domain
24                   jpjglo_crs                   !: 2nd dimension of global coarse grid domain
25      INTEGER  ::  jpi_crs ,   &                !: 1st dimension of local coarse grid domain
26                   jpj_crs                      !: 2nd dimension of local coarse grid domain
27      INTEGER  ::  jpi_full ,  &                !: 1st dimension of local parent grid domain
28                   jpj_full                     !: 2nd dimension of local parent grid domain
29
30      INTEGER  ::  nistr , njstr
31      INTEGER  ::  niend , njend
32
33      INTEGER  ::  jpi_crsm1, jpj_crsm1         !: loop indices     
34      INTEGER  ::  jpiglo_crsm1, jpjglo_crsm1   !: loop indices     
35      INTEGER  ::  nperio_full, nperio_crs      !: jperio of parent and coarse grids
36      INTEGER  ::  npolj_full, npolj_crs        !: north fold mark
37      INTEGER  ::  jpiglo_full, jpjglo_full     !: jpiglo / jpjglo
38      INTEGER  ::  npiglo, npjglo               !: jpjglo
39      INTEGER  ::  nlci_full, nlcj_full         !: i-, j-dimension of local or sub domain on parent grid
40      INTEGER  ::  nldi_full, nldj_full         !: starting indices of internal sub-domain on parent grid
41      INTEGER  ::  nlei_full, nlej_full         !: ending indices of internal sub-domain on parent grid
42      INTEGER  ::  nlci_crs, nlcj_crs           !: i-, j-dimension of local or sub domain on coarse grid
43      INTEGER  ::  nldi_crs, nldj_crs           !: starting indices of internal sub-domain on coarse grid
44      INTEGER  ::  nlei_crs, nlej_crs           !: ending indices of internal sub-domain on coarse grid
45      INTEGER  ::  narea_full, narea_crs        !: node
46      INTEGER  ::  jpnij_full, jpnij_crs        !: =jpni*jpnj, the pe decomposition
47      INTEGER  ::  jpim1_full, jpjm1_full       !:
48      INTEGER  ::  nimpp_full, njmpp_full       !: global position of point (1,1) of subdomain on parent grid
49      INTEGER  ::  nimpp_crs, njmpp_crs         !: set to 1,1 for now .  Valid only for monoproc
50      INTEGER  ::  nreci_full, nrecj_full
51      INTEGER  ::  nreci_crs, nrecj_crs
52      !cc
53      INTEGER ::   noea_full, nowe_full        !: index of the local neighboring processors in
54      INTEGER ::   noso_full, nono_full        !: east, west, south and north directions
55      INTEGER ::   npne_full, npnw_full        !: index of north east and north west processor
56      INTEGER ::   npse_full, npsw_full        !: index of south east and south west processor
57      INTEGER ::   nbne_full, nbnw_full        !: logical of north east & north west processor
58      INTEGER ::   nbse_full, nbsw_full        !: logical of south east & south west processor
59      INTEGER ::   nidom_full                  !: ???
60      INTEGER ::   nproc_full                  !:number for local processor
61      INTEGER ::   nbondi_full, nbondj_full    !: mark of i- and j-direction local boundaries
62      INTEGER ::   noea_crs, nowe_crs          !: index of the local neighboring processors in
63      INTEGER ::   noso_crs, nono_crs          !: east, west, south and north directions
64      INTEGER ::   npne_crs, npnw_crs          !: index of north east and north west processor
65      INTEGER ::   npse_crs, npsw_crs          !: index of south east and south west processor
66      INTEGER ::   nbne_crs, nbnw_crs          !: logical of north east & north west processor
67      INTEGER ::   nbse_crs, nbsw_crs          !: logical of south east & south west processor
68      INTEGER ::   nidom_crs                   !: ???
69      INTEGER ::   nproc_crs                   !:number for local processor
70      INTEGER ::   nbondi_crs, nbondj_crs      !: mark of i- and j-direction local boundaries
71     
72
73      INTEGER, DIMENSION(:), ALLOCATABLE :: mis_crs, mie_crs, mis2_crs, mie2_crs  ! starting and ending i-indices of parent subset
74      INTEGER, DIMENSION(:), ALLOCATABLE :: mjs_crs, mje_crs, mjs2_crs, mje2_crs ! starting and ending  j-indices of parent subset
75      INTEGER, DIMENSION(:), ALLOCATABLE :: mjg_crs, mig_crs
76      INTEGER  :: mxbinctr, mybinctr            ! central point in grid box
77      INTEGER, DIMENSION(:), ALLOCATABLE ::   nlcit_crs, nlcit_full  !: dimensions of every subdomain
78      INTEGER, DIMENSION(:), ALLOCATABLE ::   nldit_crs, nldit_full     !: first, last indoor index for each i-domain
79      INTEGER, DIMENSION(:), ALLOCATABLE ::   nleit_crs, nleit_full    !: first, last indoor index for each j-domain
80      INTEGER, DIMENSION(:), ALLOCATABLE ::   nimppt_crs, nimppt_full    !: first, last indoor index for each j-domain
81      INTEGER, DIMENSION(:), ALLOCATABLE ::   nlcjt_crs, nlcjt_full  !: dimensions of every subdomain
82      INTEGER, DIMENSION(:), ALLOCATABLE ::   nldjt_crs, nldjt_full     !: first, last indoor index for each i-domain
83      INTEGER, DIMENSION(:), ALLOCATABLE ::   nlejt_crs, nlejt_full    !: first, last indoor index for each j-domain
84      INTEGER, DIMENSION(:), ALLOCATABLE ::   njmppt_crs, njmppt_full    !: first, last indoor index for each j-domain
85
86 
87      ! Masks
88      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: tmask_crs, umask_crs, vmask_crs, fmask_crs
89      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE :: tmask_i_crs, rnfmsk_crs, tpol_crs, fpol_crs
90     
91  !    REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: tmask_i_crs, tpol, fpol     
92
93      ! Scale factors
94      REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: e1t_crs, e2t_crs, e1e2t_crs ! horizontal scale factors grid type T
95      REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: e1u_crs, e2u_crs ! horizontal scale factors grid type U
96      REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: e1v_crs, e2v_crs ! horizontal scale factors grid type V
97      REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: e1f_crs, e2f_crs ! horizontal scale factors grid type F
98      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: e3t_crs, e3u_crs, e3v_crs, e3f_crs, e3w_crs
99      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: e3t_max_crs, e3u_max_crs, e3v_max_crs, e3w_max_crs
100      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: fse3t_crs, fse3u_crs, fse3v_crs, fse3f_crs, fse3w_crs
101      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: fse3t_n_crs, fse3t_b_crs, fse3t_a_crs
102     
103      ! Surface
104      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: e1e2w_crs, e2e3u_crs, e1e3v_crs
105      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: e1e2w_msk, e2e3u_msk, e1e3v_msk
106                                                                  ! vertical scale factors
107      ! Coordinates
108      REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: gphit_crs, glamt_crs, gphif_crs, glamf_crs 
109      REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: gphiu_crs, glamu_crs, gphiv_crs, glamv_crs 
110      REAL(wp), DIMENSION(:,:),   ALLOCATABLE :: ff_crs
111      INTEGER,  DIMENSION(:,:),   ALLOCATABLE :: mbathy_crs, mbkt_crs, mbku_crs, mbkv_crs
112      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: gdept_crs, gdepu_crs, gdepv_crs, gdepw_crs
113
114      ! Weights
115      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: facsurfv, facsurfu, facvol_t, facvol_w
116      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: ocean_volume_crs_t, ocean_volume_crs_w, bt_crs, r1_bt_crs
117      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: crs_surfu_wgt, crs_surfv_wgt, crs_surfw_wgt, crs_volt_wgt
118
119      ! CRS Namelist
120      INTEGER           :: nn_factx   = 3       !: reduction factor of x-dimension of the parent grid
121      INTEGER           :: nn_facty   = 3       !: reduction factor of y-dimension of the parent grid
122      INTEGER           :: nn_binref  = 0       !: 0 = binning starts north fold (equator could be asymmetric)
123                                                !: 1 = binning centers at equator (north fold my have artifacts)     
124                                                !:    for even reduction factors, equator placed in bin biased south
125      INTEGER           :: nn_msh_crs = 1       !: Organization of mesh mask output
126                                                !: 0 = no mesh mask output
127                                                !: 1 = unified mesh mask output
128                                                !: 2 = 2 separate mesh mask output
129                                                !: 3 = 3 separate mesh mask output
130      INTEGER           :: nn_crs_kz    =    0       !: type of Kz coarsening ( =0->VOL ; =1->MAX ; =2->MIN)
131      LOGICAL           :: ln_crs_wn    = .FALSE.    !: coarsening wn or computation using horizontal divergence
132      !
133      INTEGER           :: nrestx, nresty       !: for determining odd or even reduction factor
134
135
136      ! Grid reduction factors
137      REAL(wp)     ::  rfactx_r                !: inverse of x-dim reduction factor
138      REAL(wp)     ::  rfacty_r                !: inverse of y-dim reduction factor
139      REAL(wp)     ::  rfactxy 
140
141      !! Horizontal grid parameters for domhgr
142      !! =====================================
143      INTEGER  ::   nphgr_msh_crs = 0   !: type of horizontal mesh
144      !                                 !  = 0 curvilinear coordinate on the sphere read in coordinate.nc
145      !                                 !  = 1 geographical mesh on the sphere with regular grid-spacing
146      !                                 !  = 2 f-plane with regular grid-spacing
147      !                                 !  = 3 beta-plane with regular grid-spacing
148      !                                 !  = 4 Mercator grid with T/U point at the equator
149     
150      ! Physical and dynamical ocean fields for output or passing to TOP, time-mean fields
151      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE      :: tsn_crs
152      REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE      :: un_crs, vn_crs, wn_crs, rke_crs
153      REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE      :: hdivn_crs   
154      REAL(wp), DIMENSION(:,:)    , ALLOCATABLE      :: sshn_crs   
155
156      !
157      ! Surface fluxes to pass to TOP
158      REAL(wp), PUBLIC, DIMENSION(:,:)  , ALLOCATABLE :: qsr_crs, emp_b_crs, fr_i_crs, wndm_crs, emp_crs
159      REAL(wp), PUBLIC, DIMENSION(:,:)  , ALLOCATABLE :: utau_crs, vtau_crs
160      REAL(wp), PUBLIC, DIMENSION(:,:)  , ALLOCATABLE :: rnf_crs
161
162      ! Vertical diffusion
163      REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)  ::  avt_crs           !: vert. diffusivity coef. [m2/s] at w-point for temp 
164# if defined key_zdfddm
165      REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)  ::  avs_crs           !: salinity vertical diffusivity coeff. [m2/s] at w-point
166# endif
167
168      ! Mixing and Mixed Layer Depth
169      INTEGER,  PUBLIC, ALLOCATABLE, DIMENSION(:,:)    ::  nmln_crs, hmld_crs, hmlp_crs, hmlpt_crs                       
170
171      ! Direction of lateral diffusion
172
173
174CONTAINS
175   
176   INTEGER FUNCTION crs_dom_alloc()
177      !!-------------------------------------------------------------------
178      !!                     *** FUNCTION crs_dom_alloc ***
179      !!  ** Purpose :   Allocate public crs arrays 
180      !!-------------------------------------------------------------------
181      !! Local variables
182      INTEGER, DIMENSION(17) :: ierr
183
184      ierr(:) = 0
185
186      ! Set up bins for coarse grid, horizontal only.
187      ALLOCATE( mis2_crs(jpiglo_crs) , mie2_crs(jpiglo_crs) , mjs2_crs(jpjglo_crs) , mje2_crs(jpjglo_crs),&
188      & mig_crs(jpi_crs), mjg_crs(jpj_crs),  STAT=ierr(1) )
189
190      ! Set up Mask and Mesh
191
192      ALLOCATE( tmask_crs(jpi_crs,jpj_crs,jpk) , fmask_crs(jpi_crs,jpj_crs,jpk) ,  &
193         &      umask_crs(jpi_crs,jpj_crs,jpk) , vmask_crs(jpi_crs,jpj_crs,jpk) , STAT=ierr(2))
194
195      ALLOCATE( tmask_i_crs(jpi_crs,jpj_crs), rnfmsk_crs(jpi_crs,jpj_crs), &
196      &     tpol_crs(jpiglo_crs,jpjglo_crs), fpol_crs(jpiglo_crs,jpjglo_crs), STAT=ierr(3) )
197
198      ALLOCATE( gphit_crs(jpi_crs,jpj_crs) , glamt_crs(jpi_crs,jpj_crs) , & 
199         &      gphiu_crs(jpi_crs,jpj_crs) , glamu_crs(jpi_crs,jpj_crs) , &
200         &      gphiv_crs(jpi_crs,jpj_crs) , glamv_crs(jpi_crs,jpj_crs) , &
201         &      gphif_crs(jpi_crs,jpj_crs) , glamf_crs(jpi_crs,jpj_crs) , &
202         &      ff_crs(jpi_crs,jpj_crs)    , STAT=ierr(4))
203
204      ALLOCATE( e1t_crs(jpi_crs,jpj_crs) , e2t_crs(jpi_crs,jpj_crs) , & 
205         &      e1u_crs(jpi_crs,jpj_crs) , e2u_crs(jpi_crs,jpj_crs) , & 
206         &      e1v_crs(jpi_crs,jpj_crs) , e2v_crs(jpi_crs,jpj_crs) , &
207         &      e1f_crs(jpi_crs,jpj_crs) , e2f_crs(jpi_crs,jpj_crs) , &
208         &      e1e2t_crs(jpi_crs,jpj_crs), STAT=ierr(5))
209
210      ALLOCATE( fse3t_crs(jpi_crs,jpj_crs,jpk)  , fse3w_crs(jpi_crs,jpj_crs,jpk) , & 
211         &      fse3u_crs(jpi_crs,jpj_crs,jpk)  , fse3v_crs(jpi_crs,jpj_crs,jpk) , & 
212         &      e3t_crs(jpi_crs,jpj_crs,jpk)    , e3w_crs(jpi_crs,jpj_crs,jpk)   , & 
213         &      e3u_crs(jpi_crs,jpj_crs,jpk)    , e3v_crs(jpi_crs,jpj_crs,jpk)   , &
214         &      e3f_crs(jpi_crs,jpj_crs,jpk)    , fse3f_crs(jpi_crs,jpj_crs,jpk) , & 
215         &      e3t_max_crs(jpi_crs,jpj_crs,jpk), e3w_max_crs(jpi_crs,jpj_crs,jpk), & 
216         &      e3u_max_crs(jpi_crs,jpj_crs,jpk), e3v_max_crs(jpi_crs,jpj_crs,jpk)   , &
217         &      fse3t_b_crs(jpi_crs,jpj_crs,jpk), fse3t_n_crs(jpi_crs,jpj_crs,jpk),&
218         &      fse3t_a_crs(jpi_crs,jpj_crs,jpk), e1e2w_msk(jpi_crs,jpj_crs,jpk) , &
219         &      e2e3u_msk(jpi_crs,jpj_crs,jpk)  , e1e3v_msk(jpi_crs,jpj_crs,jpk) , &
220         &      e1e2w_crs(jpi_crs,jpj_crs,jpk)  , e2e3u_crs(jpi_crs,jpj_crs,jpk) , &
221         &      e1e3v_crs(jpi_crs,jpj_crs,jpk)  , STAT=ierr(6))
222
223
224      ALLOCATE( facsurfv(jpi_crs,jpj_crs,jpk) , facsurfu(jpi_crs,jpj_crs,jpk) , & 
225         &      facvol_t(jpi_crs,jpj_crs,jpk) , facvol_w(jpi_crs,jpj_crs,jpk) , &
226         &      ocean_volume_crs_t(jpi_crs,jpj_crs,jpk) , ocean_volume_crs_w(jpi_crs,jpj_crs,jpk), &
227         &      bt_crs(jpi_crs,jpj_crs,jpk)   , r1_bt_crs(jpi_crs,jpj_crs,jpk) , STAT=ierr(7))
228
229
230      ALLOCATE( crs_surfu_wgt(jpi_crs,jpj_crs,jpk) , crs_surfv_wgt(jpi_crs,jpj_crs,jpk) , & 
231         &      crs_surfw_wgt(jpi_crs,jpj_crs,jpk) , crs_volt_wgt(jpi_crs,jpj_crs,jpk) , STAT=ierr(8))
232
233
234      ALLOCATE( mbathy_crs(jpi_crs,jpj_crs) , mbkt_crs(jpi_crs,jpj_crs) , &
235         &      mbku_crs(jpi_crs,jpj_crs)   , mbkv_crs(jpi_crs,jpj_crs) , STAT=ierr(9))
236
237      ALLOCATE( gdept_crs(jpi_crs,jpj_crs,jpk) , gdepu_crs(jpi_crs,jpj_crs,jpk) , &
238         &      gdepv_crs(jpi_crs,jpj_crs,jpk) , gdepw_crs(jpi_crs,jpj_crs,jpk) , STAT=ierr(10) )
239
240
241      ALLOCATE( un_crs(jpi_crs,jpj_crs,jpk) , vn_crs(jpi_crs,jpj_crs,jpk) , &
242         &      wn_crs(jpi_crs,jpj_crs,jpk) , hdivn_crs(jpi_crs,jpj_crs,jpk),&
243         &      rke_crs(jpi_crs,jpj_crs,jpk),                                STAT=ierr(11))
244
245     ALLOCATE( sshn_crs(jpi_crs,jpj_crs),  emp_crs(jpi_crs,jpj_crs) , emp_b_crs(jpi_crs,jpj_crs), &
246         &      qsr_crs(jpi_crs,jpj_crs) , wndm_crs(jpi_crs,jpj_crs), utau_crs(jpi_crs,jpj_crs) , &
247         &      vtau_crs(jpi_crs,jpj_crs), rnf_crs(jpi_crs, jpj_crs) , &
248         &      fr_i_crs(jpi_crs, jpj_crs),   STAT=ierr(12)  )
249
250     ALLOCATE( tsn_crs(jpi_crs,jpj_crs,jpk,jpts), avt_crs(jpi_crs,jpj_crs,jpk),    &
251# if defined key_zdfddm
252         &      avs_crs(jpi_crs,jpj_crs,jpk),    &
253# endif
254         &      STAT=ierr(13) )
255
256      ALLOCATE( nmln_crs(jpi_crs,jpj_crs) , hmld_crs(jpi_crs,jpj_crs) , &
257         &      hmlp_crs(jpi_crs,jpj_crs) , hmlpt_crs(jpi_crs,jpj_crs) , STAT=ierr(14) )
258         
259      ALLOCATE( nimppt_crs(jpnij) , nlcit_crs(jpnij) , nldit_crs(jpnij) , nleit_crs(jpnij), &
260       &  nimppt_full(jpnij) , nlcit_full(jpnij) , nldit_full(jpnij) , nleit_full(jpnij),   &
261                njmppt_crs(jpnij) , nlcjt_crs(jpnij) , nldjt_crs(jpnij) , nlejt_crs(jpnij), &
262       &  njmppt_full(jpnij) , nlcjt_full(jpnij) , nldjt_full(jpnij) , nlejt_full(jpnij)  , STAT=ierr(15) )
263
264         
265      crs_dom_alloc = MAXVAL(ierr)
266
267   END FUNCTION crs_dom_alloc
268   
269   INTEGER FUNCTION crs_dom_alloc2()
270      !!-------------------------------------------------------------------
271      !!                     *** FUNCTION crs_dom_alloc ***
272      !!  ** Purpose :   Allocate public crs arrays 
273      !!-------------------------------------------------------------------
274      !! Local variables
275      INTEGER, DIMENSION(1) :: ierr
276
277      ierr(:) = 0
278     
279      ALLOCATE( mjs_crs(nlej_crs) , mje_crs(nlej_crs), mis_crs(nlei_crs) , mie_crs(nlei_crs), STAT=ierr(1) )
280      crs_dom_alloc2 = MAXVAL(ierr)
281
282      END FUNCTION crs_dom_alloc2
283
284   SUBROUTINE dom_grid_glo
285      !!--------------------------------------------------------------------
286      !!                       ***  MODULE dom_grid_glo  ***
287      !!
288      !! ** Purpose : +Return back to parent grid domain
289      !!---------------------------------------------------------------------
290
291      !                         Return to parent grid domain
292      jpi    = jpi_full
293      jpj    = jpj_full
294      jpim1  = jpim1_full
295      jpjm1  = jpjm1_full
296      nperio = nperio_full
297
298      npolj  = npolj_full
299      jpiglo = jpiglo_full
300      jpjglo = jpjglo_full
301
302      nlci   = nlci_full
303      nlcj   = nlcj_full
304      nldi   = nldi_full
305      nldj   = nldj_full
306      nlei   = nlei_full
307      nlej   = nlej_full
308      nimpp  = nimpp_full
309      njmpp  = njmpp_full
310     
311      nlcit(:)  = nlcit_full(:)
312      nldit(:)  = nldit_full(:)
313      nleit(:)  = nleit_full(:)
314      nimppt(:) = nimppt_full(:)
315      nlcjt(:)  = nlcjt_full(:)
316      nldjt(:)  = nldjt_full(:)
317      nlejt(:)  = nlejt_full(:)
318      njmppt(:) = njmppt_full(:)
319
320   END SUBROUTINE dom_grid_glo
321
322   SUBROUTINE dom_grid_crs
323      !!--------------------------------------------------------------------
324      !!                       ***  MODULE dom_grid_crs  ***
325      !!
326      !! ** Purpose :  Save the parent grid information & Switch to coarse grid domain
327      !!---------------------------------------------------------------------
328
329 
330      !
331      !                        Switch to coarse grid domain
332      jpi    = jpi_crs
333      jpj    = jpj_crs
334      jpim1  = jpi_crsm1
335      jpjm1  = jpj_crsm1
336      nperio = nperio_crs
337
338      npolj  = npolj_crs
339      jpiglo = jpiglo_crs
340      jpjglo = jpjglo_crs
341
342
343      nlci   = nlci_crs
344      nlcj   = nlcj_crs
345      nldi   = nldi_crs
346      nlei   = nlei_crs
347      nlej   = nlej_crs
348      nldj   = nldj_crs
349      nimpp  = nimpp_crs
350      njmpp  = njmpp_crs
351     
352      nlcit(:)  = nlcit_crs(:)
353      nldit(:)  = nldit_crs(:)
354      nleit(:)  = nleit_crs(:)
355      nimppt(:) = nimppt_crs(:)
356      nlcjt(:)  = nlcjt_crs(:)
357      nldjt(:)  = nldjt_crs(:)
358      nlejt(:)  = nlejt_crs(:)
359      njmppt(:) = njmppt_crs(:)
360
361
362      !
363   END SUBROUTINE dom_grid_crs
364   
365     
366   !!======================================================================
367
368END MODULE crs
369
Note: See TracBrowser for help on using the repository browser.