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.
sbcwave.F90 in branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90 @ 7350

Last change on this file since 7350 was 7350, checked in by emanuelaclementi, 7 years ago

ticket #1805 step 2: Add in changes from the 2015/dev_r5936_INGV1_WAVE branch

  • Property svn:keywords set to Id
File size: 16.2 KB
Line 
1MODULE sbcwave
2   !!======================================================================
3   !!                       ***  MODULE  sbcwave  ***
4   !! Wave module
5   !!======================================================================
6   !! History :  3.3  !   2011-09  (M. Adani)  Original code: Drag Coefficient
7   !!         :  3.4  !   2012-10  (M. Adani)  Stokes Drift
8   !!            3.6  !   2014-09  (E. Clementi,P. Oddo) New Stokes Drift Computation
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   sbc_wave      : wave data from wave model in netcdf files
13   !!----------------------------------------------------------------------
14   USE oce            !
15   USE sbc_oce       ! Surface boundary condition: ocean fields
16   USE bdy_oce        !
17   USE domvvl         !
18   USE iom            ! I/O manager library
19   USE in_out_manager ! I/O manager
20   USE lib_mpp        ! distribued memory computing library
21   USE fldread       ! read input fields
22   USE wrk_nemo       !
23   USE phycst         ! physical constants
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   sbc_stokes, sbc_qiao  ! routines called in sbccpl
29   PUBLIC   sbc_wave    ! routine called in sbcmod
30   
31   ! Variables checking if the wave parameters are coupled (if not, they are read from file)
32   LOGICAL, PUBLIC     ::   cpl_hsig=.FALSE.
33   LOGICAL, PUBLIC     ::   cpl_phioc=.FALSE.
34   LOGICAL, PUBLIC     ::   cpl_sdrftx=.FALSE.
35   LOGICAL, PUBLIC     ::   cpl_sdrfty=.FALSE.
36   LOGICAL, PUBLIC     ::   cpl_wper=.FALSE.
37   LOGICAL, PUBLIC     ::   cpl_wnum=.FALSE.
38   LOGICAL, PUBLIC     ::   cpl_wstrf=.FALSE.
39   LOGICAL, PUBLIC     ::   cpl_wdrag=.FALSE.
40
41   INTEGER ::   jpfld                ! number of files to read for stokes drift
42   INTEGER ::   jp_usd               ! index of stokes drift  (i-component) (m/s)    at T-point
43   INTEGER ::   jp_vsd               ! index of stokes drift  (j-component) (m/s)    at T-point
44   INTEGER ::   jp_swh               ! index of significant wave hight      (m)      at T-point
45   INTEGER ::   jp_wmp               ! index of mean wave period            (s)      at T-point
46
47   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_cd    ! structure of input fields (file informations, fields read) Drag Coefficient
48   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_sd    ! structure of input fields (file informations, fields read) Stokes Drift
49   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_wn    ! structure of input fields (file informations, fields read) wave number for Qiao
50   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_tauoc ! structure of input fields (file informations, fields read) normalized wave stress into the ocean
51   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       :: cdn_wave 
52   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       :: swh,wmp, wnum
53   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       :: tauoc_wave
54   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       :: tsd2d
55   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)       :: zusd2dt, zvsd2dt
56   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)     :: usd3d, vsd3d, wsd3d 
57   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)     :: usd3dt, vsd3dt
58
59   !! * Substitutions
60#  include "domzgr_substitute.h90"
61#  include "vectopt_loop_substitute.h90"
62   !!----------------------------------------------------------------------
63   !! NEMO/OPA 3.7 , NEMO Consortium (2014)
64   !! $Id$
65   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
66   !!----------------------------------------------------------------------
67CONTAINS
68
69   SUBROUTINE sbc_stokes( )
70      !!---------------------------------------------------------------------
71      !!                     ***  ROUTINE sbc_stokes  ***
72      !!
73      !! ** Purpose :   compute the 3d Stokes Drift according to Breivik et al.,
74      !!                2014 (DOI: 10.1175/JPO-D-14-0020.1)
75      !!
76      !! ** Method  : - Calculate Stokes transport speed
77      !!              - Calculate horizontal divergence
78      !!              - Integrate the horizontal divergenze from the bottom
79      !! ** action 
80      !!---------------------------------------------------------------------
81      INTEGER                ::   jj,ji,jk 
82      REAL(wp)                       ::  ztransp, zfac, zsp0, zk, zus, zvs
83      REAL(wp), DIMENSION(:,:,:), POINTER :: ze3hdiv   ! 3D workspace
84      !!---------------------------------------------------------------------
85      !
86
87      CALL wrk_alloc( jpi,jpj,jpk, ze3hdiv )
88      DO jk = 1, jpk
89         DO jj = 1, jpj
90            DO ji = 1, jpi
91               ! On T grid
92               ! Stokes transport speed estimated from Hs and Tmean
93               ztransp = 2.0_wp*rpi*swh(ji,jj)**2.0_wp/(16.0_wp*MAX(wmp(ji,jj),0.0000001_wp))
94               ! Stokes surface speed
95               zsp0 = SQRT( zusd2dt(ji,jj)**2 + zvsd2dt(ji,jj)**2)
96               ! Wavenumber scale
97               zk = ABS(zsp0)/MAX(ABS(5.97_wp*ztransp),0.0000001_wp)
98               ! Depth attenuation
99               zfac = EXP(-2.0_wp*zk*fsdept(ji,jj,jk))/(1.0_wp+8.0_wp*zk*fsdept(ji,jj,jk))
100               !
101               usd3dt(ji,jj,jk) = zfac * zusd2dt(ji,jj) * tmask(ji,jj,jk)
102               vsd3dt(ji,jj,jk) = zfac * zvsd2dt(ji,jj) * tmask(ji,jj,jk)
103            END DO
104         END DO
105      END DO 
106      ! Into the U and V Grid
107      DO jk = 1, jpkm1
108         DO jj = 1, jpjm1
109            DO ji = 1, fs_jpim1
110               usd3d(ji,jj,jk) = 0.5 *  umask(ji,jj,jk) *   &
111                               &  ( usd3dt(ji,jj,jk) + usd3dt(ji+1,jj,jk) )
112               vsd3d(ji,jj,jk) = 0.5 *  vmask(ji,jj,jk) *   &
113                               &  ( vsd3dt(ji,jj,jk) + vsd3dt(ji,jj+1,jk) )
114            END DO
115         END DO
116      END DO
117      !
118      CALL lbc_lnk( usd3d(:,:,:), 'U', -1. )
119      CALL lbc_lnk( vsd3d(:,:,:), 'V', -1. )
120      !
121      DO jk = 1, jpkm1               ! Horizontal divergence
122         DO jj = 2, jpj
123            DO ji = fs_2, jpi
124               ze3hdiv(ji,jj,jk) = (  e2u(ji  ,jj) * usd3d(ji  ,jj,jk)     &
125                  &                 - e2u(ji-1,jj) * usd3d(ji-1,jj,jk)     &
126                  &                 + e1v(ji,jj  ) * vsd3d(ji,jj  ,jk)     &
127                  &                 - e1v(ji,jj-1) * vsd3d(ji,jj-1,jk)   ) * r1_e1e2t(ji,jj)
128            END DO
129         END DO
130      END DO
131      !
132      IF( .NOT. AGRIF_Root() ) THEN
133         IF( nbondi ==  1 .OR. nbondi == 2 )   ze3hdiv(nlci-1,   :  ,:) = 0._wp      ! east
134         IF( nbondi == -1 .OR. nbondi == 2 )   ze3hdiv(  2   ,   :  ,:) = 0._wp      ! west
135         IF( nbondj ==  1 .OR. nbondj == 2 )   ze3hdiv(  :   ,nlcj-1,:) = 0._wp      ! north
136         IF( nbondj == -1 .OR. nbondj == 2 )   ze3hdiv(  :   ,  2   ,:) = 0._wp      ! south
137      ENDIF
138      !
139      CALL lbc_lnk( ze3hdiv, 'T', 1. )
140      !
141      DO jk = jpkm1, 1, -1                   ! integrate from the bottom the e3t * hor. divergence
142         wsd3d(:,:,jk) = wsd3d(:,:,jk+1) - fse3t_n(:,:,jk) * ze3hdiv(:,:,jk)
143      END DO
144#if defined key_bdy
145      IF( lk_bdy ) THEN
146         DO jk = 1, jpkm1
147            wsd3d(:,:,jk) = wsd3d(:,:,jk) * bdytmask(:,:)
148         END DO
149      ENDIF
150#endif
151      CALL wrk_dealloc( jpi,jpj,jpk, ze3hdiv )
152      !
153   END SUBROUTINE sbc_stokes
154
155   SUBROUTINE sbc_qiao
156      !!---------------------------------------------------------------------
157      !!                     ***  ROUTINE sbc_qiao  ***
158      !!
159      !! ** Purpose :   Qiao formulation for wave enhanced turbulence
160      !!                2010 (DOI: 10.1007/s10236-010-0326)
161      !!
162      !! ** Method  : -
163      !! ** action 
164      !!---------------------------------------------------------------------
165      INTEGER :: jj, ji
166
167      ! Calculate the module of the stokes drift on T grid
168      !-------------------------------------------------
169      DO jj = 1, jpj
170         DO ji = 1, jpi
171            tsd2d(ji,jj) = SQRT( zusd2dt(ji,jj) * zusd2dt(ji,jj) + zvsd2dt(ji,jj) * zvsd2dt(ji,jj) )
172         END DO
173      END DO
174      !
175   END SUBROUTINE sbc_qiao
176
177   SUBROUTINE sbc_wave( kt )
178      !!---------------------------------------------------------------------
179      !!                     ***  ROUTINE sbc_wave  ***
180      !!
181      !! ** Purpose :   read wave parameters from wave model  in netcdf files.
182      !!
183      !! ** Method  : - Read namelist namsbc_wave
184      !!              - Read Cd_n10 fields in netcdf files
185      !!              - Read stokes drift 2d in netcdf files
186      !!              - Read wave number in netcdf files
187      !!              - Compute 3d stokes drift using Breivik et al.,2014
188      !!                formulation
189      !! ** action 
190      !!---------------------------------------------------------------------
191      USE zdf_oce,  ONLY : ln_zdfqiao
192
193      INTEGER, INTENT( in  ) :: kt       ! ocean time step
194      !
195      INTEGER                ::   ierror   ! return error code
196      INTEGER                ::   ifpr
197      INTEGER                ::   ios      ! Local integer output status for namelist read
198      !
199      CHARACTER(len=100)     ::  cn_dir                          ! Root directory for location of drag coefficient files
200      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   slf_i     ! array of namelist informations on the fields to read
201      TYPE(FLD_N)            ::  sn_cdg, sn_usd, sn_vsd,  &
202                             &   sn_swh, sn_wmp, sn_wnum, sn_tauoc      ! informations about the fields to be read
203      !!
204      NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_swh, sn_wmp, sn_wnum, sn_tauoc
205      !!---------------------------------------------------------------------
206      !
207      !                                         ! -------------------- !
208      IF( kt == nit000 ) THEN                   ! First call kt=nit000 !
209         !                                      ! -------------------- !
210         REWIND( numnam_ref )              ! Namelist namsbc_wave in reference namelist : File for drag coeff. from wave model
211         READ  ( numnam_ref, namsbc_wave, IOSTAT = ios, ERR = 901)
212901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave in reference namelist', lwp )
213
214         REWIND( numnam_cfg )              ! Namelist namsbc_wave in configuration namelist : File for drag coeff. from wave model
215         READ  ( numnam_cfg, namsbc_wave, IOSTAT = ios, ERR = 902 )
216902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave in configuration namelist', lwp )
217         IF(lwm) WRITE ( numond, namsbc_wave )
218         !
219         IF( ln_cdgw ) THEN
220            IF( .NOT. cpl_wdrag ) THEN
221               ALLOCATE( sf_cd(1), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg
222               IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave: unable to allocate sf_wave structure' )
223               !
224                                      ALLOCATE( sf_cd(1)%fnow(jpi,jpj,1)   )
225               IF( sn_cdg%ln_tint )   ALLOCATE( sf_cd(1)%fdta(jpi,jpj,1,2) )
226               CALL fld_fill( sf_cd, (/ sn_cdg /), cn_dir, 'sbc_wave', 'Wave module ', 'namsbc_wave' )
227            ENDIF
228            ALLOCATE( cdn_wave(jpi,jpj) )
229         ENDIF
230
231         IF( ln_tauoc ) THEN
232            IF( .NOT. cpl_wstrf ) THEN
233               ALLOCATE( sf_tauoc(1), STAT=ierror )           !* allocate and fill sf_wave with sn_tauoc
234               IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave: unable to allocate sf_wave structure' )
235               !
236                                       ALLOCATE( sf_tauoc(1)%fnow(jpi,jpj,1)   )
237               IF( sn_tauoc%ln_tint )  ALLOCATE( sf_tauoc(1)%fdta(jpi,jpj,1,2) )
238               CALL fld_fill( sf_tauoc, (/ sn_tauoc /), cn_dir, 'sbc_wave', 'Wave module', 'namsbc_wave' )
239            ENDIF
240            ALLOCATE( tauoc_wave(jpi,jpj) )
241         ENDIF
242
243         IF( ln_sdw ) THEN
244            ! Find out how many fields have to be read from file if not coupled
245            jpfld=0
246            jp_usd=0; jp_vsd=0; jp_swh=0; jp_wmp=0
247            IF( .NOT. cpl_sdrftx ) THEN
248               jpfld=jpfld+1
249               jp_usd=jpfld
250            ENDIF
251            IF( .NOT. cpl_sdrfty ) THEN
252               jpfld=jpfld+1
253               jp_vsd=jpfld
254            ENDIF
255            IF( .NOT. cpl_hsig ) THEN
256               jpfld=jpfld+1
257               jp_swh=jpfld
258            ENDIF
259            IF( .NOT. cpl_wper ) THEN
260               jpfld=jpfld+1
261               jp_wmp=jpfld
262            ENDIF
263
264            ! Read from file only the non-coupled fields
265            IF( jpfld > 0 ) THEN
266               ALLOCATE( slf_i(jpfld) )
267               IF( jp_usd > 0 ) slf_i(jp_usd) = sn_usd
268               IF( jp_vsd > 0 ) slf_i(jp_vsd) = sn_vsd
269               IF( jp_swh > 0 ) slf_i(jp_swh) = sn_swh
270               IF( jp_wmp > 0 ) slf_i(jp_wmp) = sn_wmp
271               ALLOCATE( sf_sd(jpfld), STAT=ierror )           !* allocate and fill sf_sd with stokes drift
272               IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave: unable to allocate sf_wave structure' )
273               !
274               DO ifpr= 1, jpfld
275                  ALLOCATE( sf_sd(ifpr)%fnow(jpi,jpj,1) )
276                  IF( slf_i(ifpr)%ln_tint )   ALLOCATE( sf_sd(ifpr)%fdta(jpi,jpj,1,2) )
277               END DO
278
279               CALL fld_fill( sf_sd, slf_i, cn_dir, 'sbc_wave', 'Wave module ', 'namsbc_wave' )
280            ENDIF
281            ALLOCATE( usd3d(jpi,jpj,jpk),vsd3d(jpi,jpj,jpk),wsd3d(jpi,jpj,jpk) )
282            ALLOCATE( usd3dt(jpi,jpj,jpk),vsd3dt(jpi,jpj,jpk) )
283            ALLOCATE( swh(jpi,jpj), wmp(jpi,jpj) )
284            ALLOCATE( zusd2dt(jpi,jpj), zvsd2dt(jpi,jpj) )
285            usd3d(:,:,:) = 0._wp
286            vsd3d(:,:,:) = 0._wp
287            wsd3d(:,:,:) = 0._wp
288            IF( ln_zdfqiao ) THEN     !==  Vertical mixing enhancement using Qiao,2010  ==!
289               IF( .NOT. cpl_wnum ) THEN
290                  ALLOCATE( sf_wn(1), STAT=ierror )           !* allocate and fill sf_wave with sn_wnum
291                  IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave: unable toallocate sf_wave structure' )
292                                         ALLOCATE( sf_wn(1)%fnow(jpi,jpj,1)   )
293                  IF( sn_wnum%ln_tint )  ALLOCATE( sf_wn(1)%fdta(jpi,jpj,1,2) )
294                  CALL fld_fill( sf_wn, (/ sn_wnum /), cn_dir, 'sbc_wave', 'Wave module', 'namsbc_wave' )
295               ENDIF
296               ALLOCATE( wnum(jpi,jpj),tsd2d(jpi,jpj) )
297            ENDIF
298         ENDIF
299      ENDIF
300      !
301      IF( ln_cdgw .AND. .NOT. cpl_wdrag ) THEN              !==  Neutral drag coefficient  ==!
302         CALL fld_read( kt, nn_fsbc, sf_cd )      ! read from external forcing
303         cdn_wave(:,:) = sf_cd(1)%fnow(:,:,1)
304      ENDIF
305
306      IF( ln_tauoc .AND. .NOT. cpl_wstrf ) THEN             !==  Wave induced stress  ==!
307         CALL fld_read( kt, nn_fsbc, sf_tauoc )      !* read wave norm stress from external forcing
308         tauoc_wave(:,:) = sf_tauoc(1)%fnow(:,:,1)
309      ENDIF
310
311      IF( ln_sdw )  THEN                         !==  Computation of the 3d Stokes Drift  ==!
312         !
313         ! Read from file only if the field is not coupled
314         IF( jpfld > 0 ) THEN
315            CALL fld_read( kt, nn_fsbc, sf_sd )      !* read wave parameters from external forcing
316            IF( jp_swh > 0 ) swh(:,:)     = sf_sd(jp_swh)%fnow(:,:,1)   ! significant wave height
317            IF( jp_wmp > 0 ) wmp(:,:)     = sf_sd(jp_wmp)%fnow(:,:,1)   ! wave mean period
318            IF( jp_usd > 0 ) zusd2dt(:,:) = sf_sd(jp_usd)%fnow(:,:,1)   ! 2D zonal Stokes Drift at T point
319            IF( jp_vsd > 0 ) zvsd2dt(:,:) = sf_sd(jp_vsd)%fnow(:,:,1)   ! 2D meridional Stokes Drift at T point
320         ENDIF
321         !
322         ! Read also wave number if needed, so that it is available in coupling routines
323         IF( ln_zdfqiao .AND. .NOT. cpl_wnum ) THEN
324            CALL fld_read( kt, nn_fsbc, sf_wn )      !* read wave parameters from external forcing
325            wnum(:,:) = sf_wn(1)%fnow(:,:,1)
326         ENDIF
327           
328         !==  Computation of the 3d Stokes Drift according to Breivik et al.,2014
329         !(DOI: 10.1175/JPO-D-14-0020.1)==!
330         !
331         ! Calculate only if no necessary fields are coupled, if not calculate later after coupling
332         IF( jpfld == 4 ) THEN
333            CALL sbc_stokes()
334            IF( ln_zdfqiao .AND. .NOT. cpl_wnum ) THEN
335               CALL sbc_qiao()
336            ENDIF
337         ENDIF
338      ENDIF
339      !
340   END SUBROUTINE sbc_wave
341     
342   !!======================================================================
343END MODULE sbcwave
Note: See TracBrowser for help on using the repository browser.