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.
ldfdyn_smag.F90 in branches/2011/dev_r2802_NOCL_Smagorinsky/NEMOGCM/NEMO/OPA_SRC/LDF – NEMO

source: branches/2011/dev_r2802_NOCL_Smagorinsky/NEMOGCM/NEMO/OPA_SRC/LDF/ldfdyn_smag.F90 @ 2887

Last change on this file since 2887 was 2887, checked in by hliu, 13 years ago

addition and modification of files for Smagorinsky method. for Maria Luneva

File size: 10.5 KB
Line 
1MODULE ldfdyn_smag
2   !!======================================================================
3   !!                     ***  MODULE  ldftrasmag  ***
4   !! Ocean physics:  variable eddy induced velocity coefficients
5   !!======================================================================
6#if   defined key_dynldf_smag   &&   defined key_dynldf_c3d
7   !!----------------------------------------------------------------------
8   !!   'key_dynldf_smag'      and           smagorinsky  diffusivity
9   !!   'key_dynldf_c3d'                    3D tracer lateral  mixing coef.
10   !!----------------------------------------------------------------------
11   !!   ldf_eiv      : compute the eddy induced velocity coefficients
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE oce             ! ocean dynamics and tracers
15   USE dom_oce         ! ocean space and time domain
16   USE sbc_oce         ! surface boundary condition: ocean
17   USE sbcrnf          ! river runoffs
18   USE ldfdyn_oce      ! ocean tracer   lateral physics
19   USE phycst          ! physical constants
20   USE ldfslp          ! iso-neutral slopes
21   USE in_out_manager  ! I/O manager
22   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
23   USE prtctl          ! Print control
24   USE iom
25
26   IMPLICIT NONE
27   PRIVATE
28
29   !! * Routine accessibility
30   PUBLIC ldf_dyn_smag               ! routine called by step.F90
31   !!----------------------------------------------------------------------
32   !!  OPA 9.0 , LOCEAN-IPSL (2005)
33   !! $Id: ldf_tra_smag.F90 1482 2010-06-13 15:28:06Z  $
34   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
35   !!----------------------------------------------------------------------
36   !! * Substitutions
37#  include "domzgr_substitute.h90"
38#  include "vectopt_loop_substitute.h90"
39   !!----------------------------------------------------------------------
40
41CONTAINS
42
43
44
45
46
47   !!----------------------------------------------------------------------
48   !!                        ***  ldfdyn_smag.F90  ***
49   !!----------------------------------------------------------------------
50
51   !!----------------------------------------------------------------------
52   !!  OPA 9.0 , LOCEAN-IPSL (2005)
53   !! $Id: ldfdyn_c3d.h90 1581 2009-08-05 14:53:12Z smasson $
54   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
55   !!----------------------------------------------------------------------
56
57   !!----------------------------------------------------------------------
58   !!   'key_dynldf_smag'             3D lateral eddy viscosity coefficients
59   !!----------------------------------------------------------------------
60
61   SUBROUTINE ldf_dyn_smag( kt )
62      !!----------------------------------------------------------------------
63      !!                  ***  ROUTINE ldf_dyn_smag  ***
64      !!                   
65      !! ** Purpose :   initializations of the horizontal ocean physics
66      !!
67      !! ** Method  :   3D eddy viscosity coef.
68      !!    M.Griffies, R.Hallberg AMS, 2000
69      !! for laplacian:
70      !!   Asmag=(C/pi)^2*dx*dy sqrt(D^2), C=3-4
71      !! for bilaplacian:
72      !!   Bsmag=Asmag*dx*dy/8
73      !!   D^2=(du/dx-dv/dy)^2+(dv/dx+du/dy)^2 for Cartesian coordinates
74      !!  in general case du/dx ==> e2 d(u/e2)/dx;  du/dy ==> e1 d(u/e1)/dy;
75      !!                  dv/dx ==> e2 d(v/e2)/dx;  dv/dy ==> e1 d(v/e1)/dy
76      !!
77      !!       laplacian operator   : ahm1, ahm2 defined at T- and F-points
78      !!                              ahm3, ahm4 never used
79      !!       bilaplacian operator : ahm1, ahm2 never used
80      !!                           :  ahm3, ahm4 defined at U- and V-points
81      !!       explanation of the default is missingi
82      !!  last modified : Maria Luneva, September 2011
83      !!----------------------------------------------------------------------
84      !! * Modules used
85      !! ahm0 here is a background viscosity
86      USE ldftra_oce, ONLY : aht0
87
88      REAL (wp), DIMENSION (:,:), ALLOCATABLE::    ux,uy,vx,vy     ! local variables
89      REAL (wp), DIMENSION (:,:), ALLOCATABLE::    ue1,ue2,ve1,ve2 ! local variables
90      !! * Arguments
91      INTEGER              :: kt         ! timestep
92
93      !! * local variables
94      INTEGER  ::   ji, jj, jk      ! dummy loop indices
95      REAL (wp):: deltat,deltaf,deltau,deltav 
96     
97
98      !!----------------------------------------------------------------------
99      IF(  kt == nit000 ) THEN
100
101
102      IF(lwp) WRITE(numout,*)
103      IF(lwp) WRITE(numout,*) 'ldf_dyn_smag : 3D lateral eddy viscosity coefficient'
104      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
105     
106      ENDIF
107   
108      ALLOCATE ( ux(jpi,jpj) ); ux(:,:)=0_wp
109      ALLOCATE ( uy(jpi,jpj) ); uy(:,:)=0_wp
110      ALLOCATE ( vx(jpi,jpj) ); vx(:,:)=0_wp
111      ALLOCATE ( vy(jpi,jpj) ); vy(:,:)=0_wp 
112      ALLOCATE(ue1(jpi,jpj)); ALLOCATE(ue2(jpi,jpj))
113      ALLOCATE(ve1(jpi,jpj)); ALLOCATE(ve2(jpi,jpj))
114
115     
116      ! Set ahm1 and ahm2  ( T- and F- points) (used for laplacian operators
117      ! =================                       whatever its orientation is)
118      IF( ln_dynldf_lap ) THEN
119         ! define ahm1 and ahm2 at the right grid point position
120         ! (USER: modify ahm1 and ahm2 following your desiderata)
121         
122         DO jk=1,jpk
123           ue2(:,:)=un(:,:,jk)/e2u(:,:)
124           ve1(:,:)=vn(:,:,jk)/e1v(:,:)
125           ue1(:,:)=un(:,:,jk)/e1u(:,:)
126           ve2(:,:)=vn(:,:,jk)/e2v(:,:)
127
128 
129           DO jj=2,jpj
130            DO ji=2,jpi
131            ux(ji,jj)=(ue2(ji,jj)-ue2(ji-1,jj))/e1t(ji,jj)*e2t(ji,jj)*tmask(ji,jj,jk)
132            vy(ji,jj)=(ve1(ji,jj)-ve1(ji,jj-1))/e2t(ji,jj)*e1t(ji,jj)*tmask(ji,jj,jk)
133            ENDDO
134           ENDDO
135
136           DO jj=1,jpjm1
137            DO ji=1,jpi
138            uy(ji,jj)=(ue1(ji,jj+1)-ue1(ji,jj))/e2f(ji,jj)*e1f(ji,jj)*fmask(ji,jj,jk)
139            vx(ji,jj)=(ve2(ji+1,jj)-ve2(ji,jj))/e1f(ji,jj)*e2f(ji,jj)*fmask(ji,jj,jk)
140            ENDDO
141           ENDDO
142             
143          DO jj=2,jpjm1
144           DO ji=2,jpim1
145            deltat=2./(e1t(ji,jj)**(-2)+e2t(ji,jj)**(-2))
146            deltaf=2./(e1f(ji,jj)**(-2)+e2f(ji,jj)**(-2))   
147            ahm1(ji,jj,jk)=(cmsmag1/3.14)**2*deltat*                                       &
148                            sqrt( (ux(ji,jj)-vy(ji,jj))**2+                               &
149                     0.0625*(uy(ji,jj)+uy(ji,jj-1)+uy(ji-1,jj)+uy(ji-1,jj-1)+             &
150                            vx(ji,jj)+vx(ji,jj-1)+vx(ji-1,jj)+vx(ji-1,jj-1))**2)
151
152            ahm2(ji,jj,jk)=(cmsmag1/3.14)**2*deltaf*                                       &
153                            sqrt( (uy(ji,jj)+vx(ji,jj))**2+                               &
154                     0.0625*(ux(ji,jj)+ux(ji,jj+1)+ux(ji+1,jj)+ux(ji+1,jj+1)-             &
155                             vy(ji,jj)-vy(ji,jj+1)-vy(ji+1,jj)-vy(ji+1,jj+1))**2)
156
157            ahm1(ji,jj,jk)=MAX(ahm1(ji,jj,jk),ahm0)
158            ahm2(ji,jj,jk)=MAX(ahm2(ji,jj,jk),ahm0)
159
160! stability criteria
161            ahm1(ji,jj,jk)=MIN(ahm1(ji,jj,jk),deltat**2/(16*rdt))
162            ahm2(ji,jj,jk)=MIN(ahm2(ji,jj,jk),deltaf**2/(16*rdt))
163
164            ENDDO
165           ENDDO
166
167         ENDDO ! jpk
168            ahm1(:,:,jpk) = ahm1(:,:,jpkm1)
169            ahm2(:,:,jpk) = ahm2(:,:,jpkm1)
170            IF(lwp.and.kt==nit000) WRITE(numout,'(36x," ahm ", 7x)')
171            DO jk = 1, jpk
172
173               IF(lwp.and.kt==nit000) WRITE(numout,'(30x,E10.2,8x,i3)') ahm1(jpi/2,jpj/2,jk), jk
174            END DO
175      CALL lbc_lnk( ahm1, 'T', 1. )   ! Lateral boundary conditions on ( ahtt )
176      CALL lbc_lnk( ahm2, 'F', 1. )   ! Lateral boundary conditions on ( ahtt )
177
178      ENDIF    ! ln_dynldf
179     
180
181
182      ! ahm3 and ahm4 at U- and V-points (used for bilaplacian operator
183      ! ================================  whatever its orientation is)
184      ! (USER: modify ahm3 and ahm4 following your desiderata)
185      ! Here: ahm is proportional to the cube of the maximum of the gridspacing
186      !       in the to horizontal direction
187
188      IF( ln_dynldf_bilap ) THEN
189         DO jk=1,jpk
190           ue2(:,:)=un(:,:,jk)/e2u(:,:)
191           ve1(:,:)=vn(:,:,jk)/e1v(:,:)
192           ue1(:,:)=un(:,:,jk)/e1u(:,:)
193           ve2(:,:)=vn(:,:,jk)/e2v(:,:)
194
195
196           DO jj=2,jpj
197            DO ji=2,jpi
198            ux(ji,jj)=(ue2(ji,jj)-ue2(ji-1,jj))/e1t(ji,jj)*e2t(ji,jj)*tmask(ji,jj,jk)
199            vy(ji,jj)=(ve1(ji,jj)-ve1(ji,jj-1))/e2t(ji,jj)*e1t(ji,jj)*tmask(ji,jj,jk)
200            ENDDO
201           ENDDO
202
203           DO jj=1,jpjm1
204            DO ji=1,jpim1
205            uy(ji,jj)=(ue1(ji,jj+1)-ue1(ji,jj))/e2f(ji,jj)*e1f(ji,jj)*fmask(ji,jj,jk)
206            vx(ji,jj)=(ve2(ji+1,jj)-ve2(ji,jj))/e1f(ji,jj)*e2f(ji,jj)*fmask(ji,jj,jk)
207            ENDDO
208           ENDDO
209
210
211          DO jj=2,jpjm1
212           DO ji=2,jpim1
213            deltau=2./(e1u(ji,jj)**(-2)+e2u(ji,jj)**(-2))
214            deltav=2./(e1v(ji,jj)**(-2)+e2v(ji,jj)**(-2))
215
216             ahm3(ji,jj,jk)=MIN(ahm0_blp,(cmsmag2/3.14)**2/8*deltau**2*            &
217
218                         sqrt(0.25*(ux(ji,jj)+ux(ji+1,jj)-vy(ji,jj)-vy(ji+1,jj))**2+    &
219                              0.25*(uy(ji,jj)+uy(ji,jj-1)+vx(ji,jj)+vx(ji,jj-1))**2))
220
221            ahm4(ji,jj,jk)=MIN(ahm0_blp ,(cmsmag2/3.14)**2/8*deltav**2*            &
222
223                         sqrt(0.25*(ux(ji,jj)+ux(ji,jj+1)-vy(ji,jj)-vy(ji,jj+1))**2+    &
224                              0.25*(uy(ji,jj)+uy(ji-1,jj)+vx(ji-1,jj)+vx(ji,jj))**2))
225! stability criteria
226            ahm3(ji,jj,jk)=MAX(ahm3(ji,jj,jk),-deltau**2/(16*rdt))
227            ahm4(ji,jj,jk)=MAX(ahm4(ji,jj,jk),-deltav**2/(16*rdt))
228           
229
230            ENDDO
231           ENDDO
232
233         ENDDO
234            ahm3(:,:,jpk) = ahm3(:,:,jpkm1)
235            ahm4(:,:,jpk) = ahm4(:,:,jpkm1)
236
237            DO jk = 1, jpk
238      IF(  kt == nit000 ) THEN
239
240               IF(lwp) WRITE(numout,'(30x,E10.2,8x,i3)') ahm3(jpi/2,jpj/2,jk), jk
241      ENDIF   
242            END DO
243      CALL lbc_lnk( ahm3, 'U', 1. )   ! Lateral boundary conditions
244      CALL lbc_lnk( ahm4, 'V', 1. )
245
246      ENDIF
247     DEALLOCATE ( ux ); DEALLOCATE ( uy ); DEALLOCATE ( vx ); DEALLOCATE ( vy )
248     DEALLOCATE ( ue1 ); DEALLOCATE ( ue2 ); DEALLOCATE ( ve1 ); DEALLOCATE ( ve2 )
249
250   END SUBROUTINE ldf_dyn_smag
251#else
252   !!----------------------------------------------------------------------
253   !!   Default option                                         Dummy module
254   !!----------------------------------------------------------------------
255CONTAINS
256   SUBROUTINE ldf_dyn_smag( kt )       ! Empty routine
257      WRITE(*,*) 'ldf_dyn_smag: You should not have seen this print! error? check keys ldf:c3d+smag', kt
258   END SUBROUTINE ldf_dyn_smag
259#endif
260
261   END MODULE ldfdyn_smag
262
Note: See TracBrowser for help on using the repository browser.