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.
agrif_nolim_interp.F90 in branches/dev_005_AWL/NEMO/NST_SRC – NEMO

source: branches/dev_005_AWL/NEMO/NST_SRC/agrif_nolim_interp.F90 @ 3500

Last change on this file since 3500 was 1790, checked in by sga, 15 years ago

correct logic: no forcing in outer model is probably not good, NEMO branch dev_005_AWL

File size: 19.3 KB
Line 
1MODULE agrif_nolim
2   !!======================================================================
3   !!                       ***  MODULE  agrif_nolim_interp  ***
4   !! AGRIF   module :  interpolate fluxes from enclosing nest (or outer) 
5   !!======================================================================
6   !! History :  3.0   !  09-2009  (S Alderson)  Original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   agrif_nolim_init    : initialise required arrays
11   !!   agrif_nolim_nest    : work out size of current nest in enclosing model
12   !!   agrif_nolim_extrap  : extrapolate fluxes, removing land mask in enclosing
13   !!                         model
14   !!   agrif_nolim_flx     : ask agrif to interpolate fluxes
15   !!----------------------------------------------------------------------
16
17#if defined key_agrif && defined key_agrif_nolim
18
19   USE par_oce
20   USE oce
21   USE dom_oce     
22   USE sol_oce
23   USE in_out_manager
24   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
25   USE iom
26   USE agrif_oce
27   USE sbc_oce
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC agrif_nolim_init
33   PUBLIC agrif_nolim_flx
34   PUBLIC agrif_nolim_extrap
35
36   LOGICAL, PUBLIC                ::   lk_nolim_nst
37   INTEGER, PARAMETER             ::   jp_nst = 10  ! maximum number of grids to remember
38   INTEGER                        ::   mp_nst       ! number of grids remembered
39   INTEGER, DIMENSION(jp_nst)     ::   np_nst       ! parent of grids remembered
40   INTEGER, DIMENSION(jp_nst)     ::   nldi_nst     ! start index of nest region
41   INTEGER, DIMENSION(jp_nst)     ::   nldj_nst     ! start index of nest region
42   INTEGER, DIMENSION(jp_nst)     ::   nlei_nst     ! end index of nest region
43   INTEGER, DIMENSION(jp_nst)     ::   nlej_nst     ! end index of nest region
44
45   REAL(wp), DIMENSION(jpi,jpj)   ::   utau_nst     ! extrapolated utau
46   REAL(wp), DIMENSION(jpi,jpj)   ::   vtau_nst     ! extrapolated vtau
47   REAL(wp), DIMENSION(jpi,jpj)   ::   taum_nst     ! extrapolated taum
48   REAL(wp), DIMENSION(jpi,jpj)   ::   emp_nst      ! extrapolated emp
49   REAL(wp), DIMENSION(jpi,jpj)   ::   emps_nst     ! extrapolated emps
50   REAL(wp), DIMENSION(jpi,jpj)   ::   qsr_nst      ! extrapolated qsr
51   REAL(wp), DIMENSION(jpi,jpj)   ::   qns_nst      ! extrapolated qns
52   REAL(wp), DIMENSION(jpi,jpj)   ::   wndm_nst     ! extrapolated wndm
53   REAL(wp), DIMENSION(jpi,jpj)   ::   fri_nst      ! extrapolated ice-cover
54   REAL(wp), DIMENSION(jpi,jpj)   ::   tag_nst      ! extrapolated tag
55
56CONTAINS
57
58   SUBROUTINE agrif_nolim_init( )
59      !!---------------------------------------------------------------------
60      !!                    ***  ROUTINE agrif_nolim_init ***
61      !!
62      !! ** Purpose :   Calculation parts of current domain containing nests
63      !!
64      !! ** Method  :   
65      !!
66      !! ** Action  :   Read data from AGRIF_FixedGrids.in
67      !!             
68      !!----------------------------------------------------------------------
69
70      INTEGER               ::   inum
71      INTEGER               ::   iost
72      INTEGER               ::   jn, inn, ic
73      INTEGER               ::   inst, insti1, insti2, instj1, instj2, i1, i2, i3
74      INTEGER, DIMENSION(4) ::   iicorn, ijcorn
75      CHARACTER(len=40)     ::   clname
76      LOGICAL               ::   llok, ll_nst
77
78      !!----------------------------------------------------------------------
79
80      ! logical is always true in a nest by definition,
81      ! it is true in the outer model only if there is a nest present
82
83      lk_nolim_nst = .TRUE.
84
85      IF( .NOT. Agrif_Root() ) RETURN
86
87      inum = Agrif_Get_Unit()
88      clname = 'AGRIF_FixedGrids.in'
89
90      mp_nst = 0
91      inn = 0
92      np_nst(:) = -1
93      nldi_nst(:) = -1
94      nlei_nst(:) = -1
95      nldj_nst(:) = -1
96      nlej_nst(:) = -1
97
98      !! corner points for this processor
99      iicorn(1) = nimpp
100      ijcorn(1) = njmpp
101      iicorn(2) = nimpp + jpi - 1
102      ijcorn(2) = njmpp
103      iicorn(3) = nimpp + jpi - 1
104      ijcorn(3) = njmpp + jpj - 1
105      iicorn(4) = nimpp
106      ijcorn(4) = njmpp + jpj - 1
107
108      INQUIRE( FILE=TRIM(clname), EXIST = llok )
109
110      IF( llok ) THEN
111         iost=0
112         OPEN( UNIT=inum, FILE=TRIM(clname), ACCESS='sequential', STATUS='old', &
113               ERR=100, IOSTAT=iost)
114         inst = 1
115         DO WHILE( inst /= 0 )
116            READ( inum, * ) inst
117            IF( inst > 0 ) inn = inn + 1
118            DO jn = 1,inst
119               READ( inum, * ) insti1, insti2, instj1, instj2, i1, i2, i3
120               !! see if any corner point of this processor lies in nest
121               ll_nst = .FALSE.
122               DO ic = 1,4
123                  IF( iicorn(ic) >= insti1 .AND. iicorn(ic) <= insti2 .AND. &
124                      ijcorn(ic) >= instj1 .AND. ijcorn(ic) <= instj2 ) ll_nst = .TRUE.
125               END DO
126               IF( ll_nst ) THEN
127                  mp_nst = mp_nst + 1
128                  np_nst(mp_nst) = inn
129                  nldi_nst(mp_nst) = insti1
130                  nlei_nst(mp_nst) = insti2
131                  nldj_nst(mp_nst) = instj1
132                  nlej_nst(mp_nst) = instj2
133               ENDIF
134            END DO
135         END DO
136         CLOSE( inum )
137      ENDIF
138      IF( lwp ) THEN
139         WRITE(numout,*) ' '
140         WRITE(numout,*) 'agrif_nolim_init : read nest definitions '
141         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
142         WRITE(numout,*) 'agrif_nolim_init: found ',mp_nst
143         DO jn = 1,mp_nst
144            WRITE(numout,*) np_nst(jn), nldi_nst(jn), nlei_nst(jn), nldj_nst(jn), nlej_nst(jn) 
145         END DO
146         WRITE(numout,*) ' '
147      ENDIF
148
149  100 CONTINUE
150
151      !  unset logical if we have don't any nests to run with
152      !
153      IF( mp_nst == 0 ) lk_nolim_nst = .FALSE.
154
155   END SUBROUTINE agrif_nolim_init
156
157   SUBROUTINE agrif_nolim_extrap( kt )
158      !!---------------------------------------------------------------------
159      !!                    ***  ROUTINE agrif_nolim_extrap ***
160      !!
161      !! ** Purpose :   Extrapolation of the fluxes in the enclosing nest
162      !!
163      !! ** Method  :   Only need to unmask fields in top level model since
164      !!                all nests are contained within their parents,
165      !!                so as long as utau_nst, nstqrs, etc are not then masked,
166      !!                unmasked data should propagate down through the nests
167      !!
168      !! ** Action  :
169      !!             
170      !!----------------------------------------------------------------------
171
172      INTEGER, INTENT(in)          ::   kt
173      INTEGER                      ::   ikj, imj
174      INTEGER                      ::   ji, jj, jn, jk
175      INTEGER                      ::   ii1, ii2, ij1, ij2
176      INTEGER                      ::   ini1, ini2, inj1, inj2, iflux
177      REAL(wp)                     ::   zmskval, zval
178      REAL(wp), DIMENSION(jpi,jpj) ::   zmask_nst
179      CHARACTER(len=80)            ::   cfname
180
181      !!----------------------------------------------------------------------
182
183      IF( Agrif_Root() ) THEN
184
185         IF( kt == nit000 ) THEN
186            WRITE(numout,*) ' '
187            WRITE(numout,*) 'agrif_nolim_extrap : remove mask from flux data in outer'
188            WRITE(numout,*) '~~~~~~~~~~~~~~~~~~'
189            WRITE(numout,*) ' '
190         ENDIF
191
192         utau_nst(:,:) = utau(:,:)
193         vtau_nst(:,:) = vtau(:,:)
194         taum_nst(:,:) = taum(:,:)
195         qsr_nst(:,:) =  qsr(:,:)
196         qns_nst(:,:) =  qns(:,:)
197         emps_nst(:,:) = emps(:,:)
198         emp_nst(:,:) =  emp(:,:)
199         wndm_nst(:,:) = wndm(:,:)
200         fri_nst(:,:) = fr_i(:,:)
201         tag_nst(:,:) = tmask(:,:,1)
202
203         IF( mp_nst > 0 ) THEN
204
205            DO jn = 1, mp_nst
206
207               IF( np_nst(jn) == 1 ) THEN
208
209                  !! work out where nest lies in this grid
210                  ini1 = nldi_nst(jn)-nimpp+1
211                  inj1 = nldj_nst(jn)-njmpp+1
212                  ini2 = nlei_nst(jn)-nimpp+1
213                  inj2 = nlej_nst(jn)-njmpp+1
214
215                  !! widen it slightly to allow for U,V grids
216                  ini1 = MAX(1, ini1-1 )
217                  inj1 = MAX(1, inj1-1 )
218                  ini2 = MIN(jpi, ini2+1 )
219                  inj2 = MIN(jpj, inj2+1 )
220
221                  !! fill in masked data on T grid by crude weighted average
222                  !! over 9 point box with ji,jj at centre
223
224                  imj = 0
225                  zmask_nst(:,:) = tmask(:,:,1)
226                  DO jk = 1,100
227                    ikj = 0
228                    DO jj = inj1,inj2
229                      DO ji = ini1,ini2
230                        IF( zmask_nst(ji,jj) .EQ. 0 ) THEN
231                          ikj = ikj + 1
232                          ii1 = MAX(1,ji-1)
233                          ij1 = MAX(1,jj-1)
234                          ii2 = MIN(jpi,ji+1)
235                          ij2 = MIN(jpj,jj+1)
236                          zmskval = SUM(zmask_nst(ii1:ii2,ij1:ij2))
237                          IF (zmskval .GT. 0) THEN
238                            zval = SUM(taum_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
239                            taum_nst(ji,jj) = zval/zmskval
240                            zval = SUM(qsr_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
241                            qsr_nst(ji,jj) = zval/zmskval
242                            zval = SUM(qns_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
243                            qns_nst(ji,jj) = zval/zmskval
244                            zval = SUM(emp_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
245                            emp_nst(ji,jj) = zval/zmskval
246                            zval = SUM(emps_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
247                            emps_nst(ji,jj) = zval/zmskval
248                            zval = SUM(wndm_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
249                            wndm_nst(ji,jj) = zval/zmskval 
250                            zval = SUM(fri_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
251                            fri_nst(ji,jj) = zval/zmskval 
252                            zmask_nst(ji,jj) = 1.0
253                          ENDIF
254                        ENDIF
255                      END DO
256                    END DO
257                    imj = imj + ikj
258                    IF (ikj .EQ. 0) EXIT
259                  END DO
260                  IF( ikj > 0 ) CALL ctl_stop('failed to extrapolate on T grid in agrif_nolim_extrap')
261           
262                  !! repeat weighted average for U and V grid
263                  !! this may not be necessary if wind stress has not been masked
264
265                  imj = 0
266                  zmask_nst(:,:) = umask(:,:,1)
267                  DO jk = 1,100
268                    ikj = 0
269                    DO jj = inj1,inj2
270                      DO ji = ini1,ini2
271                        IF( zmask_nst(ji,jj) .EQ. 0 ) THEN
272                          ikj = ikj + 1
273                          ii1 = MAX(1,ji-1)
274                          ij1 = MAX(1,jj-1)
275                          ii2 = MIN(jpi,ji+1)
276                          ij2 = MIN(jpj,jj+1)
277                          zmskval = SUM(zmask_nst(ii1:ii2,ij1:ij2))
278                          IF (zmskval .GT. 0) THEN
279                            zval = SUM(utau_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
280                            utau_nst(ji,jj) = zval/zmskval
281                            zmask_nst(ji,jj) = 1.0
282                          ENDIF
283                        ENDIF
284                      END DO
285                    END DO
286                    imj = imj + ikj
287                    IF (ikj .EQ. 0) EXIT
288                  END DO
289                  IF( ikj > 0 ) CALL ctl_stop('failed to extrapolate on U grid in agrif_nolim_extrap')
290         
291                  imj = 0
292                  zmask_nst(:,:) = vmask(:,:,1)
293                  DO jk = 1,100
294                    ikj = 0
295                    DO jj = inj1,inj2
296                      DO ji = ini1,ini2
297                        IF( zmask_nst(ji,jj) .EQ. 0 ) THEN
298                          ikj = ikj + 1
299                          ii1 = MAX(1,ji-1)
300                          ij1 = MAX(1,jj-1)
301                          ii2 = MIN(jpi,ji+1)
302                          ij2 = MIN(jpj,jj+1)
303                          zmskval = SUM(zmask_nst(ii1:ii2,ij1:ij2))
304                          IF (zmskval .GT. 0) THEN
305                            zval = SUM(vtau_nst(ii1:ii2,ij1:ij2)*zmask_nst(ii1:ii2,ij1:ij2))
306                            vtau_nst(ji,jj) = zval/zmskval
307                            zmask_nst(ji,jj) = 1.0
308                          END IF
309                        ENDIF
310                      END DO
311                    END DO
312                    imj = imj + ikj
313                    IF (ikj .EQ. 0) EXIT
314                  END DO
315                  IF( ikj > 0 ) CALL ctl_stop('failed to extrapolate on V grid in agrif_nolim_extrap')
316     
317               ENDIF
318
319            END DO
320   
321         ENDIF
322
323         IF( kt == 1 ) THEN
324            cfname = "cflux000"
325            CALL iom_open( cfname, iflux, ldwrt = .TRUE., kdom=jpdom_local_full, kiolib = jprstlib )
326            CALL iom_rstput( 0, 0, iflux, 'qsr', qsr )
327            CALL iom_rstput( 0, 0, iflux, 'qsr_nst', qsr_nst )
328            CALL iom_rstput( 0, 0, iflux, 'tmask', tmask(:,:,1))
329            CALL iom_close(iflux)
330         ENDIF
331
332      ENDIF
333
334   END SUBROUTINE agrif_nolim_extrap
335
336   SUBROUTINE agrif_nolim_flx( kt )
337      !!---------------------------------------------------------------------
338      !!                    ***  ROUTINE agrif_nolim_flx ***
339      !!
340      !! ** Purpose :   Interpolation of the ocean surface boundary computation
341      !!
342      !! ** Method  :   
343      !!
344      !! ** Action  :
345      !!             
346      !!----------------------------------------------------------------------
347
348#  include "domzgr_substitute.h90" 
349     
350      INTEGER, INTENT(in)          :: kt
351      INTEGER                      :: ji, jj, jk, itij
352      INTEGER                      :: iflux
353      INTEGER                      :: itroot, infsbcroot
354      REAL(wp)                     :: zcoeff                  ! local value of timecoeff
355      REAL(wp), DIMENSION(jpi,jpj) :: ztmp
356      CHARACTER(len=80)            :: cfname
357      CHARACTER(len=10)            :: cfnum
358
359      IF (Agrif_Root()) RETURN
360
361      !! need to know whether the outer model has just done an ice step
362      !! agrif_parent_fixed gives 0 if parent is root, 1 for first nest, etc
363      !! should work for 1 or 2 level nesting, not sure about higher orders
364
365      itroot = (kt-1)/INT(Agrif_Rhot()) + 1
366      itij = Agrif_Parent_Fixed()
367      DO jk = 1,itij
368        CALL Agrif_ChildGrid_To_ParentGrid()
369        itroot = (itroot-1)/INT(Agrif_Rhot()) + 1
370      END DO
371      infsbcroot = Agrif_Parent(nn_fsbc)
372      DO jk = 1,itij
373        CALL Agrif_ParentGrid_To_ChildGrid()
374      END DO
375
376      !! only need to create new nest flux arrays if we're at the first
377      !! timestep after the root code has run its ice model
378
379      IF( lwp ) THEN
380         WRITE(numout,*) 'kt =         ',kt
381         WRITE(numout,*) 'itij =       ',itij
382         WRITE(numout,*) 'infsbcroot = ',infsbcroot
383         WRITE(numout,*) 'itroot =     ',itroot
384         WRITE(numout,*) 'NbStep =     ',Agrif_NbStepint()
385      ENDIF
386      IF ( MOD(itroot-1,infsbcroot) /= 0 .OR. Agrif_NbStepint() /= 0) RETURN
387
388      IF (lwp) WRITE(numout,*)  &
389         'Agrif_flx: interpolation of parent fluxes, kt = ',kt
390
391      zcoeff = REAL(Agrif_NbStepint(),wp)/Agrif_rhot()
392      zcoeff = 1.0
393
394      Agrif_SpecialValue=0.
395      Agrif_UseSpecialValue = .TRUE.
396
397      ztmp(:,:) = 0.0
398      CALL Agrif_Interp_variable(ztmp, utau_nst)
399      CALL Agrif_Bc_variable(ztmp, utau_nst, calledweight=zcoeff)
400      utau_nst(:,:) = ztmp(:,:)
401
402      ztmp(:,:) = 0.0
403      CALL Agrif_Interp_variable(ztmp, vtau_nst)
404      CALL Agrif_Bc_variable(ztmp, vtau_nst, calledweight=zcoeff)
405      vtau_nst(:,:) = ztmp(:,:)
406
407      ztmp(:,:) = 0.0
408      CALL Agrif_Interp_variable(ztmp, taum_nst)
409      CALL Agrif_Bc_variable(ztmp, taum_nst, calledweight=zcoeff)
410      taum_nst(:,:) = ztmp(:,:)
411
412      ztmp(:,:) = 0.0
413      CALL Agrif_Interp_variable(ztmp, qsr_nst)
414      CALL Agrif_Bc_variable(ztmp, qsr_nst, calledweight=zcoeff)
415      qsr_nst(:,:) = ztmp(:,:)
416
417      ztmp(:,:) = 0.0
418      CALL Agrif_Interp_variable(ztmp, qns_nst)
419      CALL Agrif_Bc_variable(ztmp, qns_nst, calledweight=zcoeff)
420      qns_nst(:,:) = ztmp(:,:)
421
422      ztmp(:,:) = 0.0
423      CALL Agrif_Interp_variable(ztmp, emps_nst)
424      CALL Agrif_Bc_variable(ztmp, emps_nst, calledweight=zcoeff)
425      emps_nst(:,:) = ztmp(:,:)
426
427      ztmp(:,:) = 0.0
428      CALL Agrif_Interp_variable(ztmp, emp_nst)
429      CALL Agrif_Bc_variable(ztmp, emp_nst, calledweight=zcoeff)
430      emp_nst(:,:) = ztmp(:,:)
431
432      ztmp(:,:) = 0.0
433      CALL Agrif_Interp_variable(ztmp, wndm_nst)
434      CALL Agrif_Bc_variable(ztmp, wndm_nst, calledweight=zcoeff)
435      wndm_nst(:,:) = ztmp(:,:)
436
437      ztmp(:,:) = 0.0
438      CALL Agrif_Interp_variable(ztmp, fri_nst)
439      CALL Agrif_Bc_variable(ztmp, fri_nst, calledweight=zcoeff)
440      fri_nst(:,:) = ztmp(:,:)
441
442      Agrif_UseSpecialValue = .FALSE.
443
444!! never mask the tag
445
446      ztmp(:,:) = 0.0
447      CALL Agrif_Interp_variable(ztmp, tag_nst)
448      CALL Agrif_Bc_variable(ztmp, tag_nst, calledweight=zcoeff)
449      tag_nst(:,:) = ztmp(:,:)
450
451      utau(:,:) = utau_nst(:,:)
452      vtau(:,:) = vtau_nst(:,:)
453      taum(:,:) = taum_nst(:,:) * tmask(:,:,1)
454      qsr(:,:) =  qsr_nst(:,:) * tmask(:,:,1)
455      qns(:,:) =  qns_nst(:,:) * tmask(:,:,1)
456      emps(:,:) = emps_nst(:,:) * tmask(:,:,1)
457      emp(:,:) =  emp_nst(:,:) * tmask(:,:,1)
458      wndm(:,:) = wndm_nst(:,:) * tmask(:,:,1)
459      fr_i(:,:) = fri_nst(:,:) * tmask(:,:,1)
460
461      CALL lbc_lnk(utau, 'U', -1.0)
462      CALL lbc_lnk(vtau, 'V', -1.0)
463      CALL lbc_lnk(taum, 'T', 1.0)
464      CALL lbc_lnk(qsr, 'T', 1.0)
465      CALL lbc_lnk(qns, 'T', 1.0)
466      CALL lbc_lnk(emps, 'T', 1.0)
467      CALL lbc_lnk(emp, 'T', 1.0)
468      CALL lbc_lnk(wndm, 'T', 1.0)
469      CALL lbc_lnk(fr_i, 'T', 1.0)
470
471      CALL lbc_lnk(tag_nst, 'T', 1.0)
472
473      IF( kt == 1 ) THEN
474         cfname = "cflux000"
475         CALL iom_open( cfname, iflux, ldwrt = .TRUE., kdom=jpdom_local_full, kiolib = jprstlib )
476         CALL iom_rstput( 0, 0, iflux, 'qsr', qsr )
477         CALL iom_rstput( 0, 0, iflux, 'qsr_nst', qsr_nst )
478         CALL iom_rstput( 0, 0, iflux, 'tag_nst', tag_nst )
479         CALL iom_rstput( 0, 0, iflux, 'tmask', tmask(:,:,1))
480         CALL iom_close(iflux)
481      ENDIF
482
483   END SUBROUTINE Agrif_flx
484
485#else
486   !
487   LOGICAL, PUBLIC                ::   lk_nolim_nst = .FALSE.
488   !
489CONTAINS
490   SUBROUTINE agrif_nolim_init( )
491      !!---------------------------------------------
492      !!   *** ROUTINE agrif_nolim_init  ***
493      !!---------------------------------------------
494      WRITE(*,*)  'agrif_nolim_init : You should not have seen this print! error?'
495   END SUBROUTINE agrif_nolim_init
496   SUBROUTINE agrif_nolim_extrap( )
497      !!---------------------------------------------
498      !!   *** ROUTINE agrif_nolim_extrap  ***
499      !!---------------------------------------------
500      WRITE(*,*)  'agrif_nolim_extrap : You should not have seen this print! error?'
501   END SUBROUTINE agrif_nolim_extrap
502   SUBROUTINE agrif_nolim_flx( )
503      !!---------------------------------------------
504      !!   *** ROUTINE agrif_nolim_flx  ***
505      !!---------------------------------------------
506      WRITE(*,*)  'agrif_nolim_flx : You should not have seen this print! error?'
507   END SUBROUTINE agrif_nolim_flx
508#endif
509   !!======================================================================
510END MODULE agrif_nolim
511
Note: See TracBrowser for help on using the repository browser.