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/r8395_cpl_tauwav/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/r8395_cpl_tauwav/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90 @ 12287

Last change on this file since 12287 was 12287, checked in by jcastill, 4 years ago

Fist attempt at adding wave momentum coupling (not tested)

File size: 21.4 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   !!             -   !  2016-12  (G. Madec, E. Clementi) update Stoke drift computation
10   !!                                                    + add sbc_wave_ini routine
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   sbc_stokes    : calculate 3D Stokes-drift velocities
15   !!   sbc_wave      : wave data from wave model in netcdf files
16   !!   sbc_wave_init : initialisation fo surface waves
17   !!----------------------------------------------------------------------
18   USE phycst         ! physical constants
19   USE oce            ! ocean variables
20   USE sbc_oce        ! Surface boundary condition: ocean fields
21   USE zdf_oce,  ONLY : ln_zdfqiao
22   USE bdy_oce        ! open boundary condition variables
23   USE domvvl         ! domain: variable volume layers
24   !
25   USE iom            ! I/O manager library
26   USE in_out_manager ! I/O manager
27   USE lib_mpp        ! distribued memory computing library
28   USE fldread        ! read input fields
29   USE wrk_nemo       !
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   sbc_stokes      ! routine called in sbccpl
35   PUBLIC   sbc_stress      ! routine called in sbcmod
36   PUBLIC   sbc_wave        ! routine called in sbcmod
37   PUBLIC   sbc_wave_init   ! routine called in sbcmod
38   
39   ! Variables checking if the wave parameters are coupled (if not, they are read from file)
40   LOGICAL, PUBLIC ::   cpl_hsig   = .FALSE.
41   LOGICAL, PUBLIC ::   cpl_phioc  = .FALSE.
42   LOGICAL, PUBLIC ::   cpl_sdrftx = .FALSE.
43   LOGICAL, PUBLIC ::   cpl_sdrfty = .FALSE.
44   LOGICAL, PUBLIC ::   cpl_wper   = .FALSE.
45   LOGICAL, PUBLIC ::   cpl_wnum   = .FALSE.
46   LOGICAL, PUBLIC ::   cpl_wstrf  = .FALSE.
47   LOGICAL, PUBLIC ::   cpl_tauw   = .FALSE.
48   LOGICAL, PUBLIC ::   cpl_wdrag  = .FALSE.
49
50   INTEGER ::   jpfld    ! number of files to read for stokes drift
51   INTEGER ::   jp_usd   ! index of stokes drift  (i-component) (m/s)    at T-point
52   INTEGER ::   jp_vsd   ! index of stokes drift  (j-component) (m/s)    at T-point
53   INTEGER ::   jp_hsw   ! index of significant wave hight      (m)      at T-point
54   INTEGER ::   jp_wmp   ! index of mean wave period            (s)      at T-point
55
56   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_cd      ! structure of input fields (file informations, fields read) Drag Coefficient
57   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sd      ! structure of input fields (file informations, fields read) Stokes Drift
58   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_wn      ! structure of input fields (file informations, fields read) wave number for Qiao
59   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tauoc   ! structure of input fields (file informations, fields read) normalized wave stress into the ocean
60   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tauw    ! structure of input fields (file informations, fields read) ocean stress components from wave model
61   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   cdn_wave            !:
62   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   hsw, wmp, wnum      !:
63   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauoc_wave          !: 
64   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauw_x              !:
65   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauw_y              !:
66   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tsd2d               !:
67   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   div_sd              !: barotropic stokes drift divergence
68   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   ut0sd, vt0sd        !: surface Stokes drift velocities at t-point
69   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) ::   usd  , vsd  , wsd   !: Stokes drift velocities at u-, v- & w-points, resp.
70
71   !! * Substitutions
72#  include "vectopt_loop_substitute.h90"
73   !!----------------------------------------------------------------------
74   !! NEMO/OPA 3.7 , NEMO Consortium (2014)
75   !! $Id$
76   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
77   !!----------------------------------------------------------------------
78CONTAINS
79
80   SUBROUTINE sbc_stokes( )
81      !!---------------------------------------------------------------------
82      !!                     ***  ROUTINE sbc_stokes  ***
83      !!
84      !! ** Purpose :   compute the 3d Stokes Drift according to Breivik et al.,
85      !!                2014 (DOI: 10.1175/JPO-D-14-0020.1)
86      !!
87      !! ** Method  : - Calculate Stokes transport speed
88      !!              - Calculate horizontal divergence
89      !!              - Integrate the horizontal divergenze from the bottom
90      !! ** action 
91      !!---------------------------------------------------------------------
92      INTEGER  ::   jj, ji, jk   ! dummy loop argument
93      INTEGER  ::   ik           ! local integer
94      REAL(wp) ::  ztransp, zfac, ztemp, zsp0
95      REAL(wp) ::  zdep_u, zdep_v, zkh_u, zkh_v, zda_u, zda_v
96      REAL(wp), DIMENSION(:,:)  , POINTER ::   zk_t, zk_u, zk_v, zu0_sd, zv0_sd   ! 2D workspace
97      REAL(wp), DIMENSION(:,:,:), POINTER ::   ze3divh                            ! 3D workspace
98      !!---------------------------------------------------------------------
99      !
100      CALL wrk_alloc( jpi,jpj,jpk,   ze3divh )
101      CALL wrk_alloc( jpi,jpj,       zk_t, zk_u, zk_v, zu0_sd, zv0_sd )
102      !
103      !
104      zfac =  2.0_wp * rpi / 16.0_wp
105      DO jj = 1, jpj                ! exp. wave number at t-point    (Eq. (19) in Breivick et al. (2014) )
106         DO ji = 1, jpi
107               ! Stokes drift velocity estimated from Hs and Tmean
108               ztransp = zfac * hsw(ji,jj)*hsw(ji,jj) / MAX( wmp(ji,jj) , 0.0000001_wp )
109               ! Stokes surface speed
110               zsp0 = SQRT( ut0sd(ji,jj)*ut0sd(ji,jj) + vt0sd(ji,jj)*vt0sd(ji,jj) )
111               tsd2d(ji,jj) = zsp0
112               ! Wavenumber scale
113               zk_t(ji,jj) = ABS( zsp0 ) / MAX( ABS( 5.97_wp*ztransp ) , 0.0000001_wp )
114         END DO
115      END DO     
116      DO jj = 1, jpjm1              ! exp. wave number & Stokes drift velocity at u- & v-points
117         DO ji = 1, jpim1
118            zk_u(ji,jj) = 0.5_wp * ( zk_t(ji,jj) + zk_t(ji+1,jj) )
119            zk_v(ji,jj) = 0.5_wp * ( zk_t(ji,jj) + zk_t(ji,jj+1) )
120            !
121            zu0_sd(ji,jj) = 0.5_wp * ( ut0sd(ji,jj) + ut0sd(ji+1,jj) )
122            zv0_sd(ji,jj) = 0.5_wp * ( vt0sd(ji,jj) + vt0sd(ji,jj+1) )
123         END DO
124      END DO
125      !
126      !                       !==  horizontal Stokes Drift 3D velocity  ==!
127      DO jk = 1, jpkm1
128         DO jj = 2, jpjm1
129            DO ji = 2, jpim1
130               zdep_u = 0.5_wp * ( gdept_n(ji,jj,jk) + gdept_n(ji+1,jj,jk) )
131               zdep_v = 0.5_wp * ( gdept_n(ji,jj,jk) + gdept_n(ji,jj+1,jk) )
132               !                         
133               zkh_u = zk_u(ji,jj) * zdep_u     ! k * depth
134               zkh_v = zk_v(ji,jj) * zdep_v
135               !                                ! Depth attenuation
136               zda_u = EXP( -2.0_wp*zkh_u ) / ( 1.0_wp + 8.0_wp*zkh_u )
137               zda_v = EXP( -2.0_wp*zkh_v ) / ( 1.0_wp + 8.0_wp*zkh_v )
138               !
139               usd(ji,jj,jk) = zda_u * zu0_sd(ji,jj) * umask(ji,jj,jk)
140               vsd(ji,jj,jk) = zda_v * zv0_sd(ji,jj) * vmask(ji,jj,jk)
141            END DO
142         END DO
143      END DO   
144      CALL lbc_lnk( usd(:,:,:), 'U', vsd(:,:,:), 'V', -1. )
145      !
146      !                       !==  vertical Stokes Drift 3D velocity  ==!
147      !
148      DO jk = 1, jpkm1               ! Horizontal e3*divergence
149         DO jj = 2, jpj
150            DO ji = fs_2, jpi
151               ze3divh(ji,jj,jk) = (  e2u(ji  ,jj) * e3u_n(ji  ,jj,jk) * usd(ji  ,jj,jk)    &
152                  &                 - e2u(ji-1,jj) * e3u_n(ji-1,jj,jk) * usd(ji-1,jj,jk)    &
153                  &                 + e1v(ji,jj  ) * e3v_n(ji,jj  ,jk) * vsd(ji,jj  ,jk)    &
154                  &                 - e1v(ji,jj-1) * e3v_n(ji,jj-1,jk) * vsd(ji,jj-1,jk)  ) * r1_e1e2t(ji,jj)
155            END DO
156         END DO
157      END DO
158      !
159      IF( .NOT. AGRIF_Root() ) THEN
160         IF( nbondi ==  1 .OR. nbondi == 2 )   ze3divh(nlci-1,   :  ,:) = 0._wp      ! east
161         IF( nbondi == -1 .OR. nbondi == 2 )   ze3divh(  2   ,   :  ,:) = 0._wp      ! west
162         IF( nbondj ==  1 .OR. nbondj == 2 )   ze3divh(  :   ,nlcj-1,:) = 0._wp      ! north
163         IF( nbondj == -1 .OR. nbondj == 2 )   ze3divh(  :   ,  2   ,:) = 0._wp      ! south
164      ENDIF
165      !
166      CALL lbc_lnk( ze3divh, 'T', 1. )
167      !
168      IF( ln_linssh ) THEN   ;   ik = 1   ! none zero velocity through the sea surface
169      ELSE                   ;   ik = 2   ! w=0 at the surface (set one for all in sbc_wave_init)
170      ENDIF
171      DO jk = jpkm1, ik, -1          ! integrate from the bottom the hor. divergence (NB: at k=jpk w is always zero)
172         wsd(:,:,jk) = wsd(:,:,jk+1) - ze3divh(:,:,jk)
173      END DO
174      !
175      IF( ln_bdy ) THEN
176         DO jk = 1, jpkm1
177            wsd(:,:,jk) = wsd(:,:,jk) * bdytmask(:,:)
178         END DO
179      ENDIF
180      !                       !==  Horizontal divergence of barotropic Stokes transport  ==!
181      div_sd(:,:) = 0._wp
182      DO jk = 1, jpkm1                                 !
183        div_sd(:,:) = div_sd(:,:) + ze3divh(:,:,jk)
184      END DO
185      !
186      CALL iom_put( "ustokes",  usd  )
187      CALL iom_put( "vstokes",  vsd  )
188      CALL iom_put( "wstokes",  wsd  )
189      !
190      CALL wrk_dealloc( jpi,jpj,jpk,   ze3divh )
191      CALL wrk_dealloc( jpi,jpj,       zk_t, zk_u, zk_v, zu0_sd, zv0_sd )
192      !
193   END SUBROUTINE sbc_stokes
194
195   SUBROUTINE sbc_stress( ) 
196      !!---------------------------------------------------------------------
197      !!                     ***  ROUTINE sbc_stress  ***
198      !!
199      !! ** Purpose :   Updates the ocean momentum modified by waves
200      !!
201      !! ** Method  : - Calculate u,v components of stress depending on stress
202      !!                model 
203      !!              - Calculate the stress module
204      !!              - The wind module is not modified by waves 
205      !! ** action   
206      !!---------------------------------------------------------------------
207      INTEGER  ::   jj, ji   ! dummy loop argument
208      !
209      IF( ln_tauoc ) THEN
210         utau(:,:) = utau(:,:)*tauoc_wave(:,:) 
211         vtau(:,:) = vtau(:,:)*tauoc_wave(:,:) 
212         taum(:,:) = taum(:,:)*tauoc_wave(:,:) 
213      ENDIF 
214      !
215      IF( ln_tauw ) THEN
216         DO jj = 1, jpjm1 
217            DO ji = 1, jpim1 
218               ! Stress components at u- & v-points
219               utau(ji,jj) = 0.5_wp * ( tauw_x(ji,jj) + tauw_x(ji+1,jj) ) 
220               vtau(ji,jj) = 0.5_wp * ( tauw_y(ji,jj) + tauw_y(ji,jj+1) ) 
221               !
222               ! Stress module at t points
223               taum(ji,jj) = SQRT( tauw_x(ji,jj)*tauw_x(ji,jj) + tauw_y(ji,jj)*tauw_y(ji,jj) ) 
224            END DO
225         END DO
226         CALL lbc_lnk_multi( utau(:,:), 'U', -1. , vtau(:,:), 'V', -1. , taum(:,: ), 'T', -1. ) 
227      ENDIF 
228      !
229   END SUBROUTINE sbc_stress 
230
231   SUBROUTINE sbc_wave( kt )
232      !!---------------------------------------------------------------------
233      !!                     ***  ROUTINE sbc_wave  ***
234      !!
235      !! ** Purpose :   read wave parameters from wave model  in netcdf files.
236      !!
237      !! ** Method  : - Read namelist namsbc_wave
238      !!              - Read Cd_n10 fields in netcdf files
239      !!              - Read stokes drift 2d in netcdf files
240      !!              - Read wave number in netcdf files
241      !!              - Compute 3d stokes drift using Breivik et al.,2014
242      !!                formulation
243      !! ** action 
244      !!---------------------------------------------------------------------
245      INTEGER, INTENT(in   ) ::   kt   ! ocean time step
246      !!---------------------------------------------------------------------
247      !
248      IF( ln_cdgw .AND. .NOT. cpl_wdrag ) THEN     !==  Neutral drag coefficient  ==!
249         CALL fld_read( kt, nn_fsbc, sf_cd )             ! read from external forcing
250         cdn_wave(:,:) = sf_cd(1)%fnow(:,:,1)
251      ENDIF
252
253      IF( ln_tauoc .AND. .NOT. cpl_wstrf ) THEN    !==  Wave induced stress  ==!
254         CALL fld_read( kt, nn_fsbc, sf_tauoc )          ! read wave norm stress from external forcing
255         tauoc_wave(:,:) = sf_tauoc(1)%fnow(:,:,1)
256      ENDIF
257
258      IF( ln_tauw .AND. .NOT. cpl_tauw ) THEN      !==  Wave induced stress  ==!
259         CALL fld_read( kt, nn_fsbc, sf_tauw )           ! read ocean stress components from external forcing (T grid)
260         tauw_x(:,:) = sf_tauw(1)%fnow(:,:,1) 
261         tauw_y(:,:) = sf_tauw(2)%fnow(:,:,1) 
262      ENDIF
263
264      IF( ln_sdw )  THEN                           !==  Computation of the 3d Stokes Drift  ==!
265         !
266         IF( jpfld > 0 ) THEN                            ! Read from file only if the field is not coupled
267            CALL fld_read( kt, nn_fsbc, sf_sd )          ! read wave parameters from external forcing
268            IF( jp_hsw > 0 )   hsw  (:,:) = sf_sd(jp_hsw)%fnow(:,:,1)   ! significant wave height
269            IF( jp_wmp > 0 )   wmp  (:,:) = sf_sd(jp_wmp)%fnow(:,:,1)   ! wave mean period
270            IF( jp_usd > 0 )   ut0sd(:,:) = sf_sd(jp_usd)%fnow(:,:,1)   ! 2D zonal Stokes Drift at T point
271            IF( jp_vsd > 0 )   vt0sd(:,:) = sf_sd(jp_vsd)%fnow(:,:,1)   ! 2D meridional Stokes Drift at T point
272         ENDIF
273         !
274         ! Read also wave number if needed, so that it is available in coupling routines
275         IF( ln_zdfqiao .AND. .NOT.cpl_wnum ) THEN
276            CALL fld_read( kt, nn_fsbc, sf_wn )          ! read wave parameters from external forcing
277            wnum(:,:) = sf_wn(1)%fnow(:,:,1)
278         ENDIF
279           
280         !                                         !==  Computation of the 3d Stokes Drift  ==!
281         !
282         IF( jpfld == 4 )   CALL sbc_stokes()            ! Calculate only if required fields are read
283         !                                               ! In coupled wave model-NEMO case the call is done after coupling
284         !
285      ENDIF
286      !
287   END SUBROUTINE sbc_wave
288
289
290   SUBROUTINE sbc_wave_init
291      !!---------------------------------------------------------------------
292      !!                     ***  ROUTINE sbc_wave_init  ***
293      !!
294      !! ** Purpose :   read wave parameters from wave model  in netcdf files.
295      !!
296      !! ** Method  : - Read namelist namsbc_wave
297      !!              - Read Cd_n10 fields in netcdf files
298      !!              - Read stokes drift 2d in netcdf files
299      !!              - Read wave number in netcdf files
300      !!              - Compute 3d stokes drift using Breivik et al.,2014
301      !!                formulation
302      !! ** action 
303      !!---------------------------------------------------------------------
304      INTEGER ::   ierror, ios   ! local integer
305      INTEGER ::   ifpr
306      !!
307      CHARACTER(len=100)     ::  cn_dir                          ! Root directory for location of drag coefficient files
308      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   slf_i, slf_j   ! array of namelist informations on the fields to read
309      TYPE(FLD_N)            ::  sn_cdg, sn_usd, sn_vsd,  &
310                             &   sn_hsw, sn_wmp, sn_wnum, sn_tauoc      ! informations about the fields to be read
311      !
312      NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wnum, sn_tauoc, sn_tauwx, sn_tauwy
313      !!---------------------------------------------------------------------
314      !
315      REWIND( numnam_ref )              ! Namelist namsbc_wave in reference namelist : File for drag coeff. from wave model
316      READ  ( numnam_ref, namsbc_wave, IOSTAT = ios, ERR = 901)
317901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave in reference namelist', lwp )
318         
319      REWIND( numnam_cfg )              ! Namelist namsbc_wave in configuration namelist : File for drag coeff. from wave model
320      READ  ( numnam_cfg, namsbc_wave, IOSTAT = ios, ERR = 902 )
321902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave in configuration namelist', lwp )
322      IF(lwm) WRITE ( numond, namsbc_wave )
323      !
324      IF( ln_tauoc .AND. ln_tauw ) & 
325         CALL ctl_stop( 'More than one method for modifying the ocean stress has been selected ', & 
326                                  '(ln_tauoc=.true. and ln_tauw=.true.)' ) 
327      IF( ln_tauoc ) & 
328          CALL ctl_warn( 'You are subtracting the wave stress to the ocean (ln_tauoc=.true.)' ) 
329      IF( ln_tauw ) & 
330          CALL ctl_warn( 'The wave modified ocean stress components are used (ln_tauw=.true.) ', & 
331                               'This will override any other specification of the ocean stress' ) 
332
333      IF( ln_cdgw ) THEN
334         IF( .NOT. cpl_wdrag ) THEN
335            ALLOCATE( sf_cd(1), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg
336            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_wave structure' )
337            !
338                                   ALLOCATE( sf_cd(1)%fnow(jpi,jpj,1)   )
339            IF( sn_cdg%ln_tint )   ALLOCATE( sf_cd(1)%fdta(jpi,jpj,1,2) )
340            CALL fld_fill( sf_cd, (/ sn_cdg /), cn_dir, 'sbc_wave_init', 'Wave module ', 'namsbc_wave' )
341         ENDIF
342         ALLOCATE( cdn_wave(jpi,jpj) )
343      ENDIF
344
345      IF( ln_tauoc ) THEN
346         IF( .NOT. cpl_wstrf ) THEN
347            ALLOCATE( sf_tauoc(1), STAT=ierror )           !* allocate and fill sf_wave with sn_tauoc
348            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_wave structure' )
349            !
350                                    ALLOCATE( sf_tauoc(1)%fnow(jpi,jpj,1)   )
351            IF( sn_tauoc%ln_tint )  ALLOCATE( sf_tauoc(1)%fdta(jpi,jpj,1,2) )
352            CALL fld_fill( sf_tauoc, (/ sn_tauoc /), cn_dir, 'sbc_wave_init', 'Wave module', 'namsbc_wave' )
353         ENDIF
354         ALLOCATE( tauoc_wave(jpi,jpj) )
355      ENDIF
356
357      IF( ln_tauw ) THEN
358         IF( .NOT. cpl_tauw ) THEN
359            ALLOCATE( sf_tauw(2), STAT=ierror )           !* allocate and fill sf_wave with sn_tauwx/y
360            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_tauw structure' ) 
361            !
362            ALLOCATE( slf_j(2) ) 
363            slf_j(1) = sn_tauwx 
364            slf_j(2) = sn_tauwy 
365                                    ALLOCATE( sf_tauw(1)%fnow(jpi,jpj,1)   ) 
366                                    ALLOCATE( sf_tauw(2)%fnow(jpi,jpj,1)   ) 
367            IF( slf_j(1)%ln_tint )  ALLOCATE( sf_tauw(1)%fdta(jpi,jpj,1,2) ) 
368            IF( slf_j(2)%ln_tint )  ALLOCATE( sf_tauw(2)%fdta(jpi,jpj,1,2) ) 
369            CALL fld_fill( sf_tauw, (/ slf_j /), cn_dir, 'sbc_wave_init', 'read wave input', 'namsbc_wave' ) 
370         ENDIF
371         ALLOCATE( tauw_x(jpi,jpj) ) 
372         ALLOCATE( tauw_y(jpi,jpj) ) 
373      ENDIF
374
375      IF( ln_sdw ) THEN   ! Find out how many fields have to be read from file if not coupled
376         jpfld=0
377         jp_usd=0   ;   jp_vsd=0   ;   jp_hsw=0   ;   jp_wmp=0
378         IF( .NOT. cpl_sdrftx ) THEN
379            jpfld  = jpfld + 1
380            jp_usd = jpfld
381         ENDIF
382         IF( .NOT. cpl_sdrfty ) THEN
383            jpfld  = jpfld + 1
384            jp_vsd = jpfld
385         ENDIF
386         IF( .NOT. cpl_hsig ) THEN
387            jpfld  = jpfld + 1
388            jp_hsw = jpfld
389         ENDIF
390         IF( .NOT. cpl_wper ) THEN
391            jpfld  = jpfld + 1
392            jp_wmp = jpfld
393         ENDIF
394
395         ! Read from file only the non-coupled fields
396         IF( jpfld > 0 ) THEN
397            ALLOCATE( slf_i(jpfld) )
398            IF( jp_usd > 0 )   slf_i(jp_usd) = sn_usd
399            IF( jp_vsd > 0 )   slf_i(jp_vsd) = sn_vsd
400            IF( jp_hsw > 0 )   slf_i(jp_hsw) = sn_hsw
401            IF( jp_wmp > 0 )   slf_i(jp_wmp) = sn_wmp
402            ALLOCATE( sf_sd(jpfld), STAT=ierror )   !* allocate and fill sf_sd with stokes drift
403            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_wave structure' )
404            !
405            DO ifpr= 1, jpfld
406               ALLOCATE( sf_sd(ifpr)%fnow(jpi,jpj,1) )
407               IF( slf_i(ifpr)%ln_tint )   ALLOCATE( sf_sd(ifpr)%fdta(jpi,jpj,1,2) )
408            END DO
409            !
410            CALL fld_fill( sf_sd, slf_i, cn_dir, 'sbc_wave_init', 'Wave module ', 'namsbc_wave' )
411         ENDIF
412         ALLOCATE( usd  (jpi,jpj,jpk), vsd  (jpi,jpj,jpk), wsd(jpi,jpj,jpk) )
413         ALLOCATE( hsw  (jpi,jpj)    , wmp  (jpi,jpj)     )
414         ALLOCATE( ut0sd(jpi,jpj)    , vt0sd(jpi,jpj)     )
415         ALLOCATE( div_sd(jpi,jpj) )
416         ALLOCATE( tsd2d (jpi,jpj) )
417         usd(:,:,:) = 0._wp
418         vsd(:,:,:) = 0._wp
419         wsd(:,:,:) = 0._wp
420         ! Wave number needed only if ln_zdfqiao=T
421         IF( .NOT. cpl_wnum ) THEN
422            ALLOCATE( sf_wn(1), STAT=ierror )           !* allocate and fill sf_wave with sn_wnum
423            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable toallocate sf_wave structure' )
424                                   ALLOCATE( sf_wn(1)%fnow(jpi,jpj,1)   )
425            IF( sn_wnum%ln_tint )  ALLOCATE( sf_wn(1)%fdta(jpi,jpj,1,2) )
426            CALL fld_fill( sf_wn, (/ sn_wnum /), cn_dir, 'sbc_wave', 'Wave module', 'namsbc_wave' )
427         ENDIF
428         ALLOCATE( wnum(jpi,jpj) )
429      ENDIF
430      !
431   END SUBROUTINE sbc_wave_init
432
433   !!======================================================================
434END MODULE sbcwave
Note: See TracBrowser for help on using the repository browser.