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_ice_update.F90 in NEMO/releases/r4.0/r4.0.6/src/NST – NEMO

source: NEMO/releases/r4.0/r4.0.6/src/NST/agrif_ice_update.F90

Last change on this file was 13479, checked in by clem, 4 years ago

4.0-HEAD: update agrif routines so that it takes into account the pond lids (forgotten initially)

  • Property svn:keywords set to Id
File size: 10.8 KB
Line 
1#define TWO_WAY
2!!#undef TWO_WAY
3#undef DECAL_FEEDBACK  /* SEPARATION of INTERFACES*/
4
5MODULE agrif_ice_update
6   !!=====================================================================================
7   !!                       ***  MODULE agrif_ice_update ***
8   !! Nesting module :  update surface ocean boundary condition over ice from a child grid
9   !!=====================================================================================
10   !! History :  2.0   !  04-2008  (F. Dupont)               initial version
11   !!            3.4   !  08-2012  (R. Benshila, C. Herbaut) update and EVP
12   !!            4.0   !  2018     (C. Rousset)              SI3 compatibility
13   !!----------------------------------------------------------------------
14#if defined key_agrif && defined key_si3
15   !!----------------------------------------------------------------------
16   !!   'key_si3'  :                                      SI3 sea-ice model
17   !!   'key_agrif' :                                     AGRIF library
18   !!----------------------------------------------------------------------
19   !!   agrif_update_ice  : update sea-ice on boundaries or total
20   !!                        child domain for velocities and ice properties
21   !!   update_tra_ice    : sea-ice properties
22   !!   update_u_ice      : zonal      ice velocity
23   !!   update_v_ice      : meridional ice velocity
24   !!----------------------------------------------------------------------
25   USE dom_oce
26   USE sbc_oce
27   USE agrif_oce
28   USE ice
29   USE agrif_ice 
30   USE phycst , ONLY: rt0
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   agrif_update_ice   ! called by agrif_user.F90 and icestp.F90
36
37   !!----------------------------------------------------------------------
38   !! NEMO/NST 4.0 , NEMO Consortium (2018)
39   !! $Id$
40   !! Software governed by the CeCILL license (see ./LICENSE)
41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE agrif_update_ice( )
45      !!----------------------------------------------------------------------
46      !!                     *** ROUTINE agrif_update_ice ***
47      !! ** Method  :   Call the hydrostaticupdate pressure at the boundary or the entire domain
48      !!
49      !! ** Action : - Update (u_ice,v_ice) and ice tracers
50      !!----------------------------------------------------------------------
51      !
52      IF( Agrif_Root() .OR. nn_ice == 0 ) RETURN   ! do not update if inside Parent Grid or if child domain does not have ice
53      !
54!      IF( ( MOD( (kt-nit000)/nn_fsbc + 1, Agrif_irhot() * Agrif_Parent(nn_fsbc)/nn_fsbc ) /=0 ) .AND. (kt /= 0) ) RETURN   ! update only at the parent ice time step
55      IF ( MOD(Agrif_parent_nb_step(), Agrif_Parent(nn_fsbc)) /=0 ) RETURN   ! Update only at the parent ice time step
56                                                                             ! It is assumed that at such a time, there is a child ice step which is true
57                                                                             ! as long as MOD( Agrif_irhot() * Agrif_Parent(nn_fsbc), nn_fsbc )==0.
58                                                                             ! (This condition is checked in agrif_user, Agrif_InitValues_cont_ice subroutine)
59      IF (lwp.AND.lk_agrif_debug) Write(*,*) 'Update sea ice from grid Number',Agrif_Fixed(), agrif_nb_step()
60      !
61      !
62      Agrif_SpecialValueFineGrid    = -9999.
63      Agrif_UseSpecialValueInUpdate = .TRUE.
64
65# if defined TWO_WAY
66# if ! defined DECAL_FEEDBACK
67      CALL Agrif_Update_Variable( tra_ice_id , procname = update_tra_ice  )
68#else
69      CALL Agrif_Update_Variable( tra_ice_id , locupdate=(/1,0/), procname = update_tra_ice  )
70#endif
71# if ! defined DECAL_FEEDBACK
72      CALL Agrif_Update_Variable( u_ice_id   , procname = update_u_ice    )
73      CALL Agrif_Update_Variable( v_ice_id   , procname = update_v_ice    )
74#else
75      CALL Agrif_Update_Variable( u_ice_id   , locupdate1=(/0,-1/),locupdate2=(/1,-2/),procname=update_u_ice) 
76      CALL Agrif_Update_Variable( v_ice_id   , locupdate1=(/1,-2/),locupdate2=(/0,-1/),procname=update_v_ice)
77#endif
78!      CALL Agrif_Update_Variable( tra_ice_id , locupdate=(/0,2/), procname = update_tra_ice  )
79!      CALL Agrif_Update_Variable( u_ice_id   , locupdate=(/0,1/), procname = update_u_ice    )
80!      CALL Agrif_Update_Variable( v_ice_id   , locupdate=(/0,1/), procname = update_v_ice    )
81# endif
82      Agrif_SpecialValueFineGrid    = 0.
83      Agrif_UseSpecialValueInUpdate = .FALSE.
84      !
85   END SUBROUTINE agrif_update_ice
86
87
88   SUBROUTINE update_tra_ice( ptab, i1, i2, j1, j2, k1, k2, before )
89      !!-----------------------------------------------------------------------
90      !!                        *** ROUTINE update_tra_ice ***
91      !! ** Method  : Compute the mass properties on the fine grid and recover
92      !!              the properties per mass on the coarse grid
93      !!-----------------------------------------------------------------------
94      INTEGER                               , INTENT(in   ) ::   i1, i2, j1, j2, k1, k2
95      REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2), INTENT(inout) ::   ptab
96      LOGICAL                               , INTENT(in   ) ::   before
97      !!
98      INTEGER  :: ji, jj, jk, jl, jm
99      !!-----------------------------------------------------------------------
100      ! it is ok not to multiply by e1*e2 since we conserve tracers here (same as in the ocean).
101      IF( before ) THEN
102         jm = 1
103         DO jl = 1, jpl
104            ptab(i1:i2,j1:j2,jm  ) = a_i (i1:i2,j1:j2,jl)
105            ptab(i1:i2,j1:j2,jm+1) = v_i (i1:i2,j1:j2,jl)
106            ptab(i1:i2,j1:j2,jm+2) = v_s (i1:i2,j1:j2,jl)
107            ptab(i1:i2,j1:j2,jm+3) = sv_i(i1:i2,j1:j2,jl)
108            ptab(i1:i2,j1:j2,jm+4) = oa_i(i1:i2,j1:j2,jl)
109            ptab(i1:i2,j1:j2,jm+5) = a_ip(i1:i2,j1:j2,jl)
110            ptab(i1:i2,j1:j2,jm+6) = v_ip(i1:i2,j1:j2,jl)
111            ptab(i1:i2,j1:j2,jm+7) = v_il(i1:i2,j1:j2,jl)
112            ptab(i1:i2,j1:j2,jm+8) = t_su(i1:i2,j1:j2,jl)
113            jm = jm + 9
114            DO jk = 1, nlay_s
115               ptab(i1:i2,j1:j2,jm) = e_s(i1:i2,j1:j2,jk,jl)   ;   jm = jm + 1
116            END DO
117            DO jk = 1, nlay_i
118               ptab(i1:i2,j1:j2,jm) = e_i(i1:i2,j1:j2,jk,jl)   ;   jm = jm + 1
119            END DO
120         END DO
121         !
122         DO jk = k1, k2
123            WHERE( tmask(i1:i2,j1:j2,1) == 0. )   ptab(i1:i2,j1:j2,jk) = Agrif_SpecialValueFineGrid 
124         END DO
125         !
126      ELSE
127         !
128         jm = 1
129         DO jl = 1, jpl
130            !
131            DO jj = j1, j2
132               DO ji = i1, i2
133                  IF( ptab(ji,jj,jm) /= Agrif_SpecialValueFineGrid ) THEN
134                     a_i (ji,jj,jl) = ptab(ji,jj,jm  ) * tmask(ji,jj,1)
135                     v_i (ji,jj,jl) = ptab(ji,jj,jm+1) * tmask(ji,jj,1)
136                     v_s (ji,jj,jl) = ptab(ji,jj,jm+2) * tmask(ji,jj,1)
137                     sv_i(ji,jj,jl) = ptab(ji,jj,jm+3) * tmask(ji,jj,1)
138                     oa_i(ji,jj,jl) = ptab(ji,jj,jm+4) * tmask(ji,jj,1)
139                     a_ip(ji,jj,jl) = ptab(ji,jj,jm+5) * tmask(ji,jj,1)
140                     v_ip(ji,jj,jl) = ptab(ji,jj,jm+6) * tmask(ji,jj,1)
141                     v_il(ji,jj,jl) = ptab(ji,jj,jm+7) * tmask(ji,jj,1)
142                     t_su(ji,jj,jl) = ptab(ji,jj,jm+8) * tmask(ji,jj,1)
143                  ENDIF
144               END DO
145            END DO
146            jm = jm + 9
147            !
148            DO jk = 1, nlay_s
149               WHERE( ptab(i1:i2,j1:j2,jm) /= Agrif_SpecialValueFineGrid )
150                  e_s(i1:i2,j1:j2,jk,jl) = ptab(i1:i2,j1:j2,jm) * tmask(i1:i2,j1:j2,1)
151               ENDWHERE
152               jm = jm + 1
153            END DO
154            !
155            DO jk = 1, nlay_i
156               WHERE( ptab(i1:i2,j1:j2,jm) /= Agrif_SpecialValueFineGrid )
157                  e_i(i1:i2,j1:j2,jk,jl) = ptab(i1:i2,j1:j2,jm) * tmask(i1:i2,j1:j2,1)
158               ENDWHERE
159               jm = jm + 1
160            END DO
161            !
162         END DO
163         !
164         DO jl = 1, jpl
165            WHERE( tmask(i1:i2,j1:j2,1) == 0._wp )   t_su(i1:i2,j1:j2,jl) = rt0   ! to avoid a division by 0 in sbcblk.F90
166         END DO
167         
168      ENDIF
169      !
170   END SUBROUTINE update_tra_ice
171
172
173   SUBROUTINE update_u_ice( ptab, i1, i2, j1, j2, before )
174      !!-----------------------------------------------------------------------
175      !!                        *** ROUTINE update_u_ice ***
176      !! ** Method  : Update the fluxes and recover the properties (C-grid)
177      !!-----------------------------------------------------------------------
178      INTEGER                         , INTENT(in   ) ::   i1, i2, j1, j2
179      REAL(wp), DIMENSION(i1:i2,j1:j2), INTENT(inout) ::   ptab
180      LOGICAL                         , INTENT(in   ) ::   before
181      !!
182      REAL(wp) ::   zrhoy   ! local scalar
183      !!-----------------------------------------------------------------------
184      !
185      IF( before ) THEN
186         zrhoy = Agrif_Rhoy()
187         ptab(:,:) = e2u(i1:i2,j1:j2) * u_ice(i1:i2,j1:j2) * zrhoy
188         WHERE( umask(i1:i2,j1:j2,1) == 0._wp )   ptab(:,:) = Agrif_SpecialValueFineGrid
189      ELSE
190         WHERE( ptab(i1:i2,j1:j2) /= Agrif_SpecialValueFineGrid )
191            u_ice(i1:i2,j1:j2) = ptab(i1:i2,j1:j2) / e2u(i1:i2,j1:j2) * umask(i1:i2,j1:j2,1)
192         ENDWHERE
193      ENDIF
194      !
195   END SUBROUTINE update_u_ice
196
197
198   SUBROUTINE update_v_ice( ptab, i1, i2, j1, j2, before )
199      !!-----------------------------------------------------------------------
200      !!                    *** ROUTINE update_v_ice ***
201      !! ** Method  : Update the fluxes and recover the properties (C-grid)
202      !!-----------------------------------------------------------------------
203      INTEGER                         , INTENT(in   ) ::   i1, i2, j1, j2
204      REAL(wp), DIMENSION(i1:i2,j1:j2), INTENT(inout) ::   ptab
205      LOGICAL                         , INTENT(in   ) ::   before
206      !!
207      REAL(wp) ::   zrhox   ! local scalar
208      !!-----------------------------------------------------------------------
209      !
210      IF( before ) THEN
211         zrhox = Agrif_Rhox()
212         ptab(:,:) = e1v(i1:i2,j1:j2) * v_ice(i1:i2,j1:j2) * zrhox
213         WHERE( vmask(i1:i2,j1:j2,1) == 0._wp )   ptab(:,:) = Agrif_SpecialValueFineGrid
214      ELSE
215         WHERE( ptab(i1:i2,j1:j2) /= Agrif_SpecialValueFineGrid )
216            v_ice(i1:i2,j1:j2) = ptab(i1:i2,j1:j2) / e1v(i1:i2,j1:j2) * vmask(i1:i2,j1:j2,1)
217         ENDWHERE
218      ENDIF
219      !
220   END SUBROUTINE update_v_ice
221
222#else
223   !!----------------------------------------------------------------------
224   !!   Empty module                                             no sea-ice
225   !!----------------------------------------------------------------------
226CONTAINS
227   SUBROUTINE agrif_ice_update_empty
228      WRITE(*,*)  'agrif_ice_update : You should not have seen this print! error?'
229   END SUBROUTINE agrif_ice_update_empty
230#endif
231
232   !!======================================================================
233END MODULE agrif_ice_update
Note: See TracBrowser for help on using the repository browser.