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_user.F90 in trunk/NEMO/NST_SRC – NEMO

source: trunk/NEMO/NST_SRC/agrif_user.F90 @ 1271

Last change on this file since 1271 was 1271, checked in by rblod, 15 years ago

Addapt AGRIF routines to the new TOP organization, clean some routines and add a sponge layer for passive tracers, see ticket #293

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 12.7 KB
RevLine 
[393]1#if defined key_agrif
[1156]2   !!----------------------------------------------------------------------
3   !!   OPA 9.0 , LOCEAN-IPSL (2006)
4   !! $Id$
5   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
6   !!----------------------------------------------------------------------
7
[636]8   SUBROUTINE Agrif_InitWorkspace
9      !!------------------------------------------
10      !!   *** ROUTINE Agrif_InitWorkspace ***
11      !!------------------------------------------
12      USE par_oce
13      USE dom_oce
[390]14      USE Agrif_Util
[636]15
[390]16      IMPLICIT NONE
[636]17     
18#if defined key_mpp_dyndist
19      CHARACTER(len=20) :: namelistname
20      INTEGER nummpp
21      NAMELIST/nam_mpp_dyndist/jpni,jpnj,jpnij
[390]22
[636]23      IF (Agrif_Nbstepint() .EQ. 0) THEN
24        nummpp = Agrif_Get_Unit()
25        namelistname='namelist'
26        IF (.NOT. Agrif_Root()) namelistname=TRIM(Agrif_CFixed())//'_namelist'
27        OPEN(nummpp,file=namelistname,status='OLD',form='formatted')
28        READ (nummpp,nam_mpp_dyndist)
29        CLOSE(nummpp)
30      ENDIF
31#endif
32
33      IF( .NOT. Agrif_Root() ) THEN
[390]34         jpiglo = nbcellsx + 2 + 2*nbghostcells
35         jpjglo = nbcellsy + 2 + 2*nbghostcells
36         jpi = ( jpiglo-2*jpreci + (jpni-1+0) ) / jpni + 2*jpreci
37         jpj = ( jpjglo-2*jprecj + (jpnj-1+0) ) / jpnj + 2*jprecj
38         jpim1 = jpi-1
39         jpjm1 = jpj-1
40         jpkm1 = jpk-1                                       
41         jpij  = jpi*jpj
42         jpidta = jpiglo
43         jpjdta = jpjglo
44         jpizoom = 1
45         jpjzoom = 1
46         nperio = 0
47         jperio = 0
[636]48      ENDIF
[390]49
[636]50   END SUBROUTINE Agrif_InitWorkspace
[390]51
[636]52   !
53   SUBROUTINE Agrif_InitValues
54      !!------------------------------------------
55      !!   *** ROUTINE Agrif_InitValues ***
56      !!
57      !! ** Purpose :: Declaration of variables to
58      !!               be interpolated
59      !!------------------------------------------
[390]60      USE Agrif_Util
[636]61      USE oce 
[390]62      USE dom_oce
63      USE opa
[1271]64#if defined key_top
65      USE trc
66#endif
[636]67#if defined key_tradmp   ||   defined key_esopa
[390]68      USE tradmp
69#endif
70      USE sol_oce
71      USE in_out_manager
[888]72#if defined key_lim3 || defined key_lim2
[390]73      USE ice_oce
74#endif
[636]75      USE agrif_opa_update
76      USE agrif_opa_interp
77      USE agrif_opa_sponge
78      USE agrif_top_update
79      USE agrif_top_interp
[1271]80      USE agrif_top_sponge
[636]81
82      IMPLICIT NONE
83
84      REAL(wp) :: tabtemp(jpi,jpj,jpk)
[1200]85#if defined key_top
[636]86      REAL(wp) :: tabtrtemp(jpi,jpj,jpk,jptra)
87#endif
[390]88      LOGICAL check_namelist
[636]89
90      ! 0. Initializations
91      !-------------------
[390]92#if defined key_orca_r025 || defined key_orca_r05 || defined key_orca_r2 || defined key_orca_r4
[636]93      jp_cfg = -1    ! set special value for jp_cfg on fine grids
[390]94      cp_cfg = "default"
95#endif
96
97      Call opa_init  ! Initializations of each fine grid
[782]98      Call agrif_opa_init
[636]99
100      ! Specific fine grid Initializations
[390]101#if defined key_tradmp || defined key_esopa
[636]102      ! no tracer damping on fine grids
[390]103      lk_tradmp = .FALSE.
104#endif
[636]105      ! 1. Declaration of the type of variable which have to be interpolated
106      !---------------------------------------------------------------------
[390]107      Call Agrif_Set_type(un,(/1,2,0/),(/2,3,0/))
108      Call Agrif_Set_type(vn,(/2,1,0/),(/3,2,0/))
109
110      Call Agrif_Set_type(ua,(/1,2,0/),(/2,3,0/))
111      Call Agrif_Set_type(va,(/2,1,0/),(/3,2,0/))
112
113      Call Agrif_Set_type(e1u,(/1,2/),(/2,3/))
114      Call Agrif_Set_type(e2v,(/2,1/),(/3,2/))
[636]115
[390]116      Call Agrif_Set_type(tn,(/2,2,0/),(/3,3,0/))
117      Call Agrif_Set_type(sn,(/2,2,0/),(/3,3,0/)) 
118
119      Call Agrif_Set_type(tb,(/2,2,0/),(/3,3,0/))
120      Call Agrif_Set_type(sb,(/2,2,0/),(/3,3,0/)) 
[636]121
[390]122      Call Agrif_Set_type(ta,(/2,2,0/),(/3,3,0/))
123      Call Agrif_Set_type(sa,(/2,2,0/),(/3,3,0/))       
[636]124
[390]125      Call Agrif_Set_type(sshn,(/2,2/),(/3,3/))
126      Call Agrif_Set_type(gcb,(/2,2/),(/3,3/))
127
[1200]128#if defined key_top
[628]129      Call Agrif_Set_type(trb,(/2,2,0,0/),(/3,3,0,0/))
130      Call Agrif_Set_type(trn,(/2,2,0,0/),(/3,3,0,0/))
131      Call Agrif_Set_type(tra,(/2,2,0,0/),(/3,3,0,0/))
132#endif
[636]133     
134      ! 2. Space directions for each variables
135      !---------------------------------------
[390]136      Call Agrif_Set_raf(un,(/'x','y','N'/))
137      Call Agrif_Set_raf(vn,(/'x','y','N'/))
[636]138
[390]139      Call Agrif_Set_raf(ua,(/'x','y','N'/))
140      Call Agrif_Set_raf(va,(/'x','y','N'/))
141
142      Call Agrif_Set_raf(e1u,(/'x','y'/))
143      Call Agrif_Set_raf(e2v,(/'x','y'/))
144
145      Call Agrif_Set_raf(tn,(/'x','y','N'/))
146      Call Agrif_Set_raf(sn,(/'x','y','N'/))
[636]147
[390]148      Call Agrif_Set_raf(tb,(/'x','y','N'/))
149      Call Agrif_Set_raf(sb,(/'x','y','N'/))
[636]150
[390]151      Call Agrif_Set_raf(ta,(/'x','y','N'/))
152      Call Agrif_Set_raf(sa,(/'x','y','N'/))     
[636]153
[390]154      Call Agrif_Set_raf(sshn,(/'x','y'/))
155      Call Agrif_Set_raf(gcb,(/'x','y'/))
156
[1200]157#if defined key_top
[1271]158      Call Agrif_Set_raf(trn,(/'x','y','N','N'/))
[628]159      Call Agrif_Set_raf(trb,(/'x','y','N','N'/))
160      Call Agrif_Set_raf(tra,(/'x','y','N','N'/))
161#endif
162
[636]163      ! 3. Type of interpolation
164      !-------------------------
[390]165      Call Agrif_Set_bcinterp(tn,interp=AGRIF_linear)
166      Call Agrif_Set_bcinterp(sn,interp=AGRIF_linear)
[636]167
[390]168      Call Agrif_Set_bcinterp(ta,interp=AGRIF_linear)
169      Call Agrif_Set_bcinterp(sa,interp=AGRIF_linear)
[636]170
[390]171      Call Agrif_Set_bcinterp(un,interp1=Agrif_linear,interp2=AGRIF_ppm)
172      Call Agrif_Set_bcinterp(vn,interp1=AGRIF_ppm,interp2=Agrif_linear)
173
174      Call Agrif_Set_bcinterp(ua,interp1=Agrif_linear,interp2=AGRIF_ppm)
175      Call Agrif_Set_bcinterp(va,interp1=AGRIF_ppm,interp2=Agrif_linear)
[636]176
[390]177      Call Agrif_Set_bcinterp(e1u,interp1=Agrif_linear,interp2=AGRIF_ppm)
178      Call Agrif_Set_bcinterp(e2v,interp1=AGRIF_ppm,interp2=Agrif_linear)
179
[1200]180#if defined key_top
[628]181      Call Agrif_Set_bcinterp(trn,interp=AGRIF_linear)
182      Call Agrif_Set_bcinterp(tra,interp=AGRIF_linear)
183#endif
184
[636]185      ! 4. Location of interpolation
186      !-----------------------------
[390]187      Call Agrif_Set_bc(un,(/0,1/))
188      Call Agrif_Set_bc(vn,(/0,1/))
[636]189
[390]190      Call Agrif_Set_bc(e1u,(/0,0/))
191      Call Agrif_Set_bc(e2v,(/0,0/))
192
193      Call Agrif_Set_bc(tn,(/0,1/))
194      Call Agrif_Set_bc(sn,(/0,1/))
195
196      Call Agrif_Set_bc(ta,(/-3*Agrif_irhox(),0/))
197      Call Agrif_Set_bc(sa,(/-3*Agrif_irhox(),0/))
198
199      Call Agrif_Set_bc(ua,(/-2*Agrif_irhox(),0/))
200      Call Agrif_Set_bc(va,(/-2*Agrif_irhox(),0/))
201
[1200]202#if defined key_top
[628]203      Call Agrif_Set_bc(trn,(/0,1/))
204      Call Agrif_Set_bc(tra,(/-3*Agrif_irhox(),0/))
205#endif
206
[636]207      ! 5. Update type
208      !---------------
[390]209      Call Agrif_Set_Updatetype(tn, update = AGRIF_Update_Average)
210      Call Agrif_Set_Updatetype(sn, update = AGRIF_Update_Average)
[636]211
[390]212      Call Agrif_Set_Updatetype(tb, update = AGRIF_Update_Average)
213      Call Agrif_Set_Updatetype(sb, update = AGRIF_Update_Average)
214
215      Call Agrif_Set_Updatetype(sshn, update = AGRIF_Update_Average)
216      Call Agrif_Set_Updatetype(gcb,update = AGRIF_Update_Average)
217
[1200]218#if defined key_top
[628]219      Call Agrif_Set_Updatetype(trn, update = AGRIF_Update_Average)
220      Call Agrif_Set_Updatetype(trb, update = AGRIF_Update_Average)
221#endif
222
[390]223      Call Agrif_Set_Updatetype(un,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average)
224      Call Agrif_Set_Updatetype(vn,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy)
225
226      Call Agrif_Set_Updatetype(e1u,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average)
227      Call Agrif_Set_Updatetype(e2v,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy)
228
[636]229      ! 6. First interpolations of potentially non zero fields
230      !-------------------------------------------------------
231      Agrif_SpecialValue=0.
232      Agrif_UseSpecialValue = .TRUE.
233      Call Agrif_Bc_variable(tabtemp,tn,calledweight=1.)
234      Call Agrif_Bc_variable(tabtemp,sn,calledweight=1.)
235      Call Agrif_Bc_variable(tabtemp,un,calledweight=1.,procname=interpu)
236      Call Agrif_Bc_variable(tabtemp,vn,calledweight=1.,procname=interpv)
[390]237
[636]238      Call Agrif_Bc_variable(tabtemp,ta,calledweight=1.,procname=interptn)
239      Call Agrif_Bc_variable(tabtemp,sa,calledweight=1.,procname=interpsn)
[390]240
[636]241      Call Agrif_Bc_variable(tabtemp,ua,calledweight=1.,procname=interpun)
242      Call Agrif_Bc_variable(tabtemp,va,calledweight=1.,procname=interpvn)
[390]243
[1200]244#if defined key_top
[636]245      Call Agrif_Bc_variable(tabtrtemp,trn,calledweight=1.)
[1271]246      Call Agrif_Bc_variable(tabtrtemp,tra,calledweight=1.,procname=interptrn)
[628]247#endif
[636]248      Agrif_UseSpecialValue = .FALSE.
[628]249
[636]250      ! 7. Some controls
251      !-----------------
252      check_namelist = .true.
253           
254      IF( check_namelist ) THEN
255     
256         ! Check time steps           
257         IF( nint(Agrif_Rhot()) * nint(rdt) .ne. Agrif_Parent(rdt) ) THEN
258            WRITE(*,*) 'incompatible time step between grids'
259            WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt)
260            WRITE(*,*) 'child  grid value : ',nint(rdt)
261            WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot()
262            STOP
263         ENDIF
264         
265         ! Check run length
266         IF( Agrif_IRhot() * (Agrif_Parent(nitend)- &
267            Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN
268            WRITE(*,*) 'incompatible run length between grids'
269            WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- &
270               Agrif_Parent(nit000)+1),' time step'
271            WRITE(*,*) 'child  grid value : ', &
272               (nitend-nit000+1),' time step'
273            WRITE(*,*) 'value on child grid should be : ', &
274               Agrif_IRhot() * (Agrif_Parent(nitend)- &
275               Agrif_Parent(nit000)+1)
276            STOP
277         ENDIF
278         
279         ! Check coordinates
280         IF( ln_zps ) THEN
281            ! check parameters for partial steps
282            IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN
283               WRITE(*,*) 'incompatible e3zps_min between grids'
284               WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min)
285               WRITE(*,*) 'child grid  :',e3zps_min
286               WRITE(*,*) 'those values should be identical'
287               STOP
288            ENDIF         
289            IF( Agrif_Parent(e3zps_rat) .ne. e3zps_rat ) THEN
290               WRITE(*,*) 'incompatible e3zps_rat between grids'
291               WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat)
292               WRITE(*,*) 'child grid  :',e3zps_rat
293               WRITE(*,*) 'those values should be identical'                 
294               STOP
295            ENDIF
296         ENDIF
[1271]297#if defined key_top
298        ! Check passive tracer cell
299        IF( ndttrc .ne. 1 ) THEN
300           WRITE(*,*) 'ndttrc should be equal to 1'
301        ENDIF
302#endif
[390]303
304      ENDIF
305
[1271]306#if defined key_top
307      CALL Agrif_Update_trc(0)
308#endif
[636]309      CALL Agrif_Update_tra(0)
310      CALL Agrif_Update_dyn(0)
311
[390]312      nbcline = 0
313
[636]314   END SUBROUTINE Agrif_InitValues
315   !
316   
317SUBROUTINE Agrif_detect(g,sizex)
318      !!------------------------------------------
319      !!   *** ROUTINE Agrif_detect ***
320      !!------------------------------------------
321      USE Agrif_Types
322 
323      INTEGER, DIMENSION(2) :: sizex
324      INTEGER, DIMENSION(sizex(1),sizex(2)) :: g 
325
[390]326      Return
327
[636]328   End SUBROUTINE Agrif_detect
329
[782]330   SUBROUTINE agrif_opa_init
331      !!---------------------------------------------
332      !!   *** ROUTINE agrif_init ***
333      !!---------------------------------------------
334      USE agrif_oce 
335      USE in_out_manager
336
337      IMPLICIT NONE
338
339      NAMELIST/namagrif/ nbclineupdate, visc_tra, visc_dyn, ln_spc_dyn
340
341      REWIND ( numnam )
342      READ   ( numnam, namagrif )
343      IF(lwp) THEN
344         WRITE(numout,*)
345         WRITE(numout,*) 'agrif_opa_init : agrif parameters'
346         WRITE(numout,*) '~~~~~~~~~~~~'
347         WRITE(numout,*) '          Namelist namagrif : set agrif parameters'
348         WRITE(numout,*) '             baroclinic update frequency          =  ', nbclineupdate
349         WRITE(numout,*) '             sponge coefficient for tracers       =  ', visc_tra
350         WRITE(numout,*) '             sponge coefficient for dynamics      =  ', visc_dyn
351         WRITE(numout,*) '             use special values for dynamics      =  ', ln_spc_dyn
352         WRITE(numout,*) 
353      ENDIF
354
355    END SUBROUTINE agrif_opa_init
[390]356#if defined key_mpp_mpi
[636]357   SUBROUTINE Agrif_InvLoc(indloc,nprocloc,i,indglob)
358      !!------------------------------------------
359      !!   *** ROUTINE Agrif_detect ***
360      !!------------------------------------------
[390]361      USE dom_oce
[636]362     
363      IMPLICIT NONE
[390]364
[636]365      INTEGER :: indglob,indloc,nprocloc,i
366
[390]367      SELECT CASE(i)
368      CASE(1)
[636]369         indglob = indloc + nimppt(nprocloc+1) - 1
[390]370      CASE(2)
[636]371         indglob = indloc + njmppt(nprocloc+1) - 1 
[390]372      CASE(3)
[636]373         indglob = indloc
[390]374      CASE(4)
[636]375         indglob = indloc
376      END SELECT
[390]377
[636]378   END SUBROUTINE Agrif_InvLoc
[390]379#endif
380#else
[636]381   SUBROUTINE Subcalledbyagrif
382      !!------------------------------------------
383      !!   *** ROUTINE Subcalledbyagrif ***
384      !!------------------------------------------
385      WRITE(*,*) 'Impossible to be here'
386   END SUBROUTINE Subcalledbyagrif
[390]387#endif
Note: See TracBrowser for help on using the repository browser.