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/UKMO/r6232_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/r6232_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90 @ 7471

Last change on this file since 7471 was 7471, checked in by jcastill, 7 years ago

Version as merged to the trunk during the Nov-2016 merge party, equivalent to branches/UKMO/r5936_INGV1_WAVE-coupling@7360

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