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 @ 7380

Last change on this file since 7380 was 7359, checked in by emanuelaclementi, 8 years ago

#1805 updated nomenclature in 2016/dev_INGV_UKMO_2016

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