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.
Changeset 7807 for branches/UKMO/r6232_HZG_WAVE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90 – NEMO

Ignore:
Timestamp:
2017-03-17T10:44:05+01:00 (7 years ago)
Author:
jcastill
Message:

Changes as in HZG wave forcing branch, but adapted to r6232

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/r6232_HZG_WAVE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r5215 r7807  
    44   !! Wave module  
    55   !!====================================================================== 
    6    !! History :  3.3.1  !   2011-09  (Adani M)  Original code: Drag Coefficient  
    7    !!         :  3.4    !   2012-10  (Adani M)                 Stokes Drift  
     6   !! History :  3.3.1  !   2011-09  (Adani M)  Original code 
    87   !!---------------------------------------------------------------------- 
    98   USE iom             ! I/O manager library 
    109   USE in_out_manager  ! I/O manager 
    1110   USE lib_mpp         ! distribued memory computing library 
    12    USE fldread        ! read input fields 
    13    USE oce 
    14    USE sbc_oce        ! Surface boundary condition: ocean fields 
    15    USE domvvl 
    16  
    17     
     11   USE fldread         ! read input fields 
     12   USE sbc_oce         ! Surface boundary condition: ocean fields 
     13   USE phycst          ! physical constants 
     14   ! USE sbcblk_core, ONLY: Cd_n10    
    1815   !!---------------------------------------------------------------------- 
    1916   !!   sbc_wave       : read drag coefficient from wave model in netcdf files  
     
    2320   PRIVATE 
    2421 
    25    PUBLIC   sbc_wave    ! routine called in sbc_blk_core or sbc_blk_mfs 
    26     
    27    INTEGER , PARAMETER ::   jpfld  = 3           ! maximum number of files to read for srokes drift 
    28    INTEGER , PARAMETER ::   jp_usd = 1           ! index of stokes drift  (i-component) (m/s)    at T-point 
    29    INTEGER , PARAMETER ::   jp_vsd = 2           ! index of stokes drift  (j-component) (m/s)    at T-point 
    30    INTEGER , PARAMETER ::   jp_wn  = 3           ! index of wave number                 (1/m)    at T-point 
    31    TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_cd    ! structure of input fields (file informations, fields read) Drag Coefficient 
    32    TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_sd    ! structure of input fields (file informations, fields read) Stokes Drift 
    33    REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: cdn_wave  
    34    REAL(wp),ALLOCATABLE,DIMENSION (:,:)              :: usd2d,vsd2d,uwavenum,vwavenum  
    35    REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:,:)     :: usd3d,vsd3d,wsd3d  
     22   PUBLIC   sbc_wavepar    ! routine called in sbc_blk_core or sbc_blk_mfs 
     23    PUBLIC   sbc_wave    ! routine called in sbc_blk_core or sbc_blk_mfs 
     24 
     25   INTEGER , PARAMETER ::   jpfld_wavepar = 7    ! maximum number of fields to be read  
     26   INTEGER , PARAMETER ::   jp_ust = 1           ! index of Stokes velocity (east component) (m/s)  at T-point 
     27   INTEGER , PARAMETER ::   jp_vst = 2           ! index of Stokes velocity (north component) (m/s) at T-point 
     28   INTEGER , PARAMETER ::   jp_swh = 3           ! index of significant wave height (m) 
     29   INTEGER , PARAMETER ::   jp_mwp = 4           ! index of mean wave period (s) 
     30   INTEGER , PARAMETER ::   jp_phioc = 5         ! index of normalized energy flux into the ocean (non-dim) 
     31   INTEGER , PARAMETER ::   jp_tauoc = 6         ! index of normalized wave stress into the ocean (non-dim) 
     32   !INTEGER , PARAMETER ::   jp_cdww = 7          ! index of wave drag coeff (non-dim) 
     33   INTEGER , PARAMETER ::   jp_wspd = 7          ! index of 10 m neutral wind speed (m/s) 
     34 
     35   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_wave ! structure of input fields (file informations, fields read) 
     36   !REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: cdn_wave ! CCC moved to sbc_oce 
     37   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_wavepar ! structure of input fields (file informations, fields read) 
     38   REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: ust_wavepar, vst_wavepar, swh_wavepar, mwp_wavepar 
     39   REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: phioc_wavepar  !WAVE2NEMO 14.12.2016 moved rn_crban to sbc_oce 
     40   !REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: tauoc_wavepar ! CCC moved to sbc_oce 
     41   !REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: wspd_wavepar  ! CCC moved to sbc_oce 
     42   !REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: cdww_wavepar 
    3643 
    3744   !! * Substitutions 
    3845#  include "domzgr_substitute.h90" 
     46#  include "vectopt_loop_substitute.h90" 
    3947   !!---------------------------------------------------------------------- 
    4048   !! NEMO/OPA 4.0 , NEMO Consortium (2011)  
     
    5159      !! 
    5260      !! ** Method  : - Read namelist namsbc_wave 
    53       !!              - Read Cd_n10 fields in netcdf files  
    54       !!              - Read stokes drift 2d in netcdf files  
    55       !!              - Read wave number      in netcdf files  
    56       !!              - Compute 3d stokes drift using monochromatic 
    57       !! ** action  :    
    58       !!                
    59       !!--------------------------------------------------------------------- 
    60       USE oce,  ONLY : un,vn,hdivn,rotn 
    61       USE divcur 
    62       USE wrk_nemo 
    63 #if defined key_bdy 
    64       USE bdy_oce, ONLY : bdytmask 
    65 #endif 
    66       INTEGER, INTENT( in  ) ::  kt       ! ocean time step 
     61      !!              - Read Cd_n10 fields in netcdf files 
     62      !! ** action  : 
     63      !! 
     64      !!--------------------------------------------------------------------- 
     65      INTEGER, INTENT( in  ) ::  kt   ! ocean time step 
    6766      INTEGER                ::  ierror   ! return error code 
    68       INTEGER                ::  ifpr, jj,ji,jk  
    69       INTEGER                ::   ios     ! Local integer output status for namelist read 
    70       REAL(wp),DIMENSION(:,:,:),POINTER             ::  udummy,vdummy,hdivdummy,rotdummy 
    71       REAL                                          ::  z2dt,z1_2dt 
    72       TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i     ! array of namelist informations on the fields to read 
    73       CHARACTER(len=100)     ::  cn_dir                          ! Root directory for location of drag coefficient files 
    74       TYPE(FLD_N)            ::  sn_cdg, sn_usd, sn_vsd, sn_wn   ! informations about the fields to be read 
    75       !!--------------------------------------------------------------------- 
    76       NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_wn 
     67      CHARACTER(len=100)     ::  cn_dir_cdg                      ! Rootdirectory for location of drag coefficient files 
     68      TYPE(FLD_N)            ::  sn_cdg                          ! informationsabout the fields to be read 
     69      !!--------------------------------------------------------------------- 
     70      NAMELIST/namsbc_wave/  sn_cdg, cn_dir_cdg 
    7771      !!--------------------------------------------------------------------- 
    7872 
     
    8377      IF( kt == nit000 ) THEN                   ! First call kt=nit000 ! 
    8478         !                                      ! -------------------- ! 
    85          REWIND( numnam_ref )              ! Namelist namsbc_wave in reference namelist : File for drag coeff. from wave model 
    86          READ  ( numnam_ref, namsbc_wave, IOSTAT = ios, ERR = 901) 
    87 901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave in reference namelist', lwp ) 
    88  
    89          REWIND( numnam_cfg )              ! Namelist namsbc_wave in configuration namelist : File for drag coeff. from wave model 
    90          READ  ( numnam_cfg, namsbc_wave, IOSTAT = ios, ERR = 902 ) 
    91 902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave in configuration namelist', lwp ) 
    92          IF(lwm) WRITE ( numond, namsbc_wave ) 
    93          ! 
    94  
    95          IF ( ln_cdgw ) THEN 
    96             ALLOCATE( sf_cd(1), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg 
    97             IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave: unable to allocate sf_wave structure' ) 
    98             ! 
    99                                    ALLOCATE( sf_cd(1)%fnow(jpi,jpj,1)   ) 
    100             IF( sn_cdg%ln_tint )   ALLOCATE( sf_cd(1)%fdta(jpi,jpj,1,2) ) 
    101             CALL fld_fill( sf_cd, (/ sn_cdg /), cn_dir, 'sbc_wave', 'Wave module ', 'namsbc_wave' ) 
    102             ALLOCATE( cdn_wave(jpi,jpj) ) 
    103             cdn_wave(:,:) = 0.0 
    104         ENDIF 
    105          IF ( ln_sdw ) THEN 
    106             slf_i(jp_usd) = sn_usd ; slf_i(jp_vsd) = sn_vsd; slf_i(jp_wn) = sn_wn 
    107             ALLOCATE( sf_sd(3), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg 
    108             IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave: unable to allocate sf_wave structure' ) 
    109             ! 
    110             DO ifpr= 1, jpfld 
    111                ALLOCATE( sf_sd(ifpr)%fnow(jpi,jpj,1) ) 
    112                IF( slf_i(ifpr)%ln_tint )   ALLOCATE( sf_sd(ifpr)%fdta(jpi,jpj,1,2) ) 
    113             END DO 
    114             CALL fld_fill( sf_sd, slf_i, cn_dir, 'sbc_wave', 'Wave module ', 'namsbc_wave' ) 
    115             ALLOCATE( usd2d(jpi,jpj),vsd2d(jpi,jpj),uwavenum(jpi,jpj),vwavenum(jpi,jpj) ) 
    116             ALLOCATE( usd3d(jpi,jpj,jpk),vsd3d(jpi,jpj,jpk),wsd3d(jpi,jpj,jpk) ) 
    117             usd2d(:,:) = 0.0 ;  vsd2d(:,:) = 0.0 ; uwavenum(:,:) = 0.0 ; vwavenum(:,:) = 0.0 
    118             usd3d(:,:,:) = 0.0 ;vsd3d(:,:,:) = 0.0 ; wsd3d(:,:,:) = 0.0 
     79         !                                            !* set file information 
     80         !                                            (default values) 
     81         ! ... default values (NB: frequency positive => hours, negative => 
     82         ! months) 
     83         !              !   file   ! frequency !  variable  ! time intep !  clim 
     84         !              ! 'yearly' or ! weights  ! rotation ! 
     85         !              !   name   !  (hours)  !   name     !   (T/F)    ! 
     86         !              (T/F)  !  'monthly'  ! filename ! pairs    ! 
     87         sn_cdg = FLD_N('cdg_wave'  ,    1     ,'drag_coeff',  .true.    ,.false. ,   'daily'   , ''       , '',''       ) 
     88         cn_dir_cdg = './'          ! directory in which the Patm data are 
     89 
     90 
     91         REWIND( numnam_ref )                             !* read in namlist namsbc_wave 
     92         READ  ( numnam_ref, namsbc_wave ) 
     93    REWIND( numnam_ref ) 
     94         REWIND( numnam_cfg )                             !* read in namlist namsbc_wave 
     95         READ  ( numnam_cfg, namsbc_wave ) 
     96    REWIND( numnam_cfg ) 
     97         ! 
     98 
     99         ALLOCATE( sf_wave(1), STAT=ierror )           !* allocate and fillsf_wave with sn_cdg 
     100         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave: unable to allocatesf_wave structure' ) 
     101         ! 
     102         CALL fld_fill( sf_wave, (/ sn_cdg /), cn_dir_cdg, 'sbc_wave', 'Wavemodule ', 'namsbc_wave' ) 
     103                                ALLOCATE( sf_wave(1)%fnow(jpi,jpj,1)   ) 
     104         IF( sn_cdg%ln_tint )   ALLOCATE( sf_wave(1)%fdta(jpi,jpj,1,2) ) 
     105         !ALLOCATE( cdn_wave(jpi,jpj) ) 
     106         ! Allocation done by sbc_oce 
     107         cdn_wave(:,:) = 0.0 
     108      ENDIF 
     109         ! 
     110         ! 
     111      CALL fld_read( kt, nn_fsbc, sf_wave )      !* read drag coefficient fromexternal forcing 
     112      cdn_wave(:,:) = sf_wave(1)%fnow(:,:,1) 
     113   END SUBROUTINE sbc_wave 
     114 
     115 
     116   SUBROUTINE sbc_wavepar( kt ) 
     117      !!--------------------------------------------------------------------- 
     118      !!                     ***  ROUTINE sbc_wavepar  *** 
     119      !! 
     120      !! ** Purpose :   Provide at each time step wave model parameters, including the 
     121      !!                Stokes drift (east and north components), significant wave height and the 
     122      !!                mean wave period as well as the normalized stress and energy flux into the  
     123      !!                ocean for TKE. 
     124      !! 
     125      !! 
     126      !! ** Method  : - Read namelist namsbc_wavepar 
     127      !!              - Read fields in NetCDF files  
     128      !! ** action  :    
     129      !!                
     130      !!--------------------------------------------------------------------- 
     131      INTEGER, INTENT( in  ) ::  kt  ! ocean time step 
     132      !! 
     133      INTEGER  ::  ierror ! return error code 
     134      INTEGER  ::   ji,iii,jjj      ! dummy loop index, Victor added iii, jjj 
     135      INTEGER  ::   jfld    ! dummy loop arguments 
     136      !! 
     137      CHARACTER(len=100)     ::  cn_dir_wavepar ! Root directory for location of ECWAM wave parameter fields 
     138      TYPE(FLD_N), DIMENSION(jpfld_wavepar) :: slf_i ! array of namelist informations on the fields to read 
     139      TYPE(FLD_N)            ::  sn_ust, sn_vst, sn_swh, sn_mwp ! information about the fields to be read 
     140      TYPE(FLD_N)            ::  sn_phioc, sn_tauoc 
     141      TYPE(FLD_N)            ::  sn_wspd 
     142      !TYPE(FLD_N)            ::  sn_cdww 
     143      !!--------------------------------------------------------------------- 
     144      !NAMELIST/namsbc_wavepar/  sn_ust, sn_vst, sn_swh, sn_mwp, sn_phioc, sn_tauoc, cn_dir_wavepar 
     145      NAMELIST/namsbc_wavepar/  sn_ust, sn_vst, sn_swh, sn_mwp, sn_wspd, sn_phioc, sn_tauoc, cn_dir_wavepar 
     146      !!--------------------------------------------------------------------- 
     147 
     148      !!---------------------------------------------------------------------- 
     149      ! 
     150      ! 
     151      !                                         ! -------------------- ! 
     152      IF( kt == nit000 ) THEN                   ! First call kt=nit000 ! 
     153         !                                      ! -------------------- ! 
     154         ! set file information (default values) 
     155         ! ... default values (NB: frequency positive => hours, negative => months) 
     156         !            !   file   ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation ! 
     157         !            !   name   !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    ! 
     158         sn_ust = FLD_N( 'ust'   ,     6     ,  'ust'     ,  .true.    , .false. ,   'monthly' , ''       , '' ,''       ) 
     159         sn_vst = FLD_N( 'vst'   ,     6     ,  'vst'     ,  .true.    , .false. ,   'monthly' , ''       , '' ,''      ) 
     160         sn_swh = FLD_N( 'swh'   ,     6     ,  'swh'     ,  .true.    , .false. ,   'monthly' , ''       , '' ,''      ) 
     161         sn_mwp = FLD_N( 'mwp'   ,     6     ,  'mwp'     ,  .true.    , .false. ,   'monthly' , ''       , '' ,''      ) 
     162         !sn_cdww = FLD_N( 'cdww'  ,    6     ,  'cdww'    ,  .true.    , .false. ,   'monthly' , ''       , ''       ) 
     163         sn_wspd = FLD_N( 'wspd'   ,   6     ,  'wspd'    ,  .true.    , .false. ,   'monthly' , ''       , '',''       ) 
     164         sn_phioc = FLD_N( 'phioc'   , 6     ,  'phioc'   ,  .true.    , .false. ,   'monthly' , ''       , '',''       ) 
     165         sn_tauoc = FLD_N( 'tauoc'   , 6     ,  'tauoc'   ,  .true.    , .false. ,   'monthly' , ''       , '',''       ) 
     166         cn_dir_wavepar = './'          ! directory in which the wave data are found 
     167 
     168         REWIND( numnam_ref )                             !* read in namlist namsbc_wave 
     169         READ  ( numnam_ref, namsbc_wavepar )  
     170         REWIND ( numnam_ref ) 
     171 
     172         REWIND( numnam_cfg )                             !* read in namlist namsbc_wave 
     173         READ  ( numnam_cfg, namsbc_wavepar )  
     174         REWIND ( numnam_cfg ) 
     175         ! 
     176 
     177 
     178         slf_i(jp_ust) = sn_ust  
     179         slf_i(jp_vst) = sn_vst 
     180         slf_i(jp_swh) = sn_swh 
     181         slf_i(jp_mwp) = sn_mwp 
     182         !slf_i(jp_cdww) = sn_cdww 
     183         slf_i(jp_wspd) = sn_wspd 
     184         slf_i(jp_phioc) = sn_phioc 
     185         slf_i(jp_tauoc) = sn_tauoc 
     186 
     187         ALLOCATE( sf_wavepar(jpfld_wavepar), STAT=ierror )          !* set sf_wavepar structure 
     188         IF ( ierror > 0 ) THEN 
     189            CALL ctl_stop( 'STOP', 'sbc_wavepar: unable to allocate sf_wavepar structure' ) ; RETURN 
    119190         ENDIF 
     191         ! 
     192         jfld = jpfld_wavepar 
     193         DO ji = 1, jpfld_wavepar 
     194            ALLOCATE( sf_wavepar(ji)%fnow(jpi,jpj,1)   ) 
     195            IF ( slf_i(ji)%ln_tint ) ALLOCATE( sf_wavepar(ji)%fdta(jpi,jpj,1,2) ) 
     196         ENDDO 
     197         ALLOCATE( ust_wavepar(jpi,jpj) ) 
     198         ALLOCATE( vst_wavepar(jpi,jpj) ) 
     199         ALLOCATE( swh_wavepar(jpi,jpj) ) 
     200         ALLOCATE( mwp_wavepar(jpi,jpj) ) 
     201         !ALLOCATE( cdww_wavepar(jpi,jpj) ) 
     202         !ALLOCATE( wspd_wavepar(jpi,jpj) ) 
     203         ALLOCATE( phioc_wavepar(jpi,jpj) ) 
     204         ALLOCATE( tauoc_wavepar(jpi,jpj) ) 
     205         ! 
     206         CALL fld_fill( sf_wavepar, slf_i, cn_dir_wavepar, 'sbc_wavepar', 'Wave module ', 'namsbc_wavepar' ) 
     207         ! 
    120208      ENDIF 
    121209         ! 
    122          ! 
    123       IF ( ln_cdgw ) THEN 
    124          CALL fld_read( kt, nn_fsbc, sf_cd )      !* read drag coefficient from external forcing 
    125          cdn_wave(:,:) = sf_cd(1)%fnow(:,:,1) 
    126       ENDIF 
    127       IF ( ln_sdw )  THEN 
    128           CALL fld_read( kt, nn_fsbc, sf_sd )      !* read drag coefficient from external forcing 
    129  
    130          ! Interpolate wavenumber, stokes drift into the grid_V and grid_V 
    131          !------------------------------------------------- 
    132  
    133          DO jj = 1, jpjm1 
    134             DO ji = 1, jpim1 
    135                uwavenum(ji,jj)=0.5 * ( 2. - umask(ji,jj,1) ) * ( sf_sd(3)%fnow(ji,jj,1) * tmask(ji,jj,1) & 
    136                &                                + sf_sd(3)%fnow(ji+1,jj,1) * tmask(ji+1,jj,1) ) 
    137  
    138                vwavenum(ji,jj)=0.5 * ( 2. - vmask(ji,jj,1) ) * ( sf_sd(3)%fnow(ji,jj,1) * tmask(ji,jj,1) & 
    139                &                                + sf_sd(3)%fnow(ji,jj+1,1) * tmask(ji,jj+1,1) ) 
    140  
    141                usd2d(ji,jj) = 0.5 * ( 2. - umask(ji,jj,1) ) * ( sf_sd(1)%fnow(ji,jj,1) * tmask(ji,jj,1) & 
    142                &                                + sf_sd(1)%fnow(ji+1,jj,1) * tmask(ji+1,jj,1) ) 
    143  
    144                vsd2d(ji,jj) = 0.5 * ( 2. - vmask(ji,jj,1) ) * ( sf_sd(2)%fnow(ji,jj,1) * tmask(ji,jj,1) & 
    145                &                                + sf_sd(2)%fnow(ji,jj+1,1) * tmask(ji,jj+1,1) ) 
    146             END DO 
    147          END DO 
    148  
    149           !Computation of the 3d Stokes Drift 
    150           DO jk = 1, jpk 
    151              DO jj = 1, jpj-1 
    152                 DO ji = 1, jpi-1 
    153                    usd3d(ji,jj,jk) = usd2d(ji,jj)*exp(2.0*uwavenum(ji,jj)*(-MIN( gdept_0(ji,jj,jk) , gdept_0(ji+1,jj  ,jk)))) 
    154                    vsd3d(ji,jj,jk) = vsd2d(ji,jj)*exp(2.0*vwavenum(ji,jj)*(-MIN( gdept_0(ji,jj,jk) , gdept_0(ji  ,jj+1,jk)))) 
    155                 END DO 
    156              END DO 
    157              usd3d(jpi,:,jk) = usd2d(jpi,:)*exp( 2.0*uwavenum(jpi,:)*(-gdept_0(jpi,:,jk)) ) 
    158              vsd3d(:,jpj,jk) = vsd2d(:,jpj)*exp( 2.0*vwavenum(:,jpj)*(-gdept_0(:,jpj,jk)) ) 
    159           END DO 
    160  
    161           CALL wrk_alloc( jpi,jpj,jpk,udummy,vdummy,hdivdummy,rotdummy) 
    162            
    163           udummy(:,:,:)=un(:,:,:) 
    164           vdummy(:,:,:)=vn(:,:,:) 
    165           hdivdummy(:,:,:)=hdivn(:,:,:) 
    166           rotdummy(:,:,:)=rotn(:,:,:) 
    167           un(:,:,:)=usd3d(:,:,:) 
    168           vn(:,:,:)=vsd3d(:,:,:) 
    169           CALL div_cur(kt) 
    170       !                                           !------------------------------! 
    171       !                                           !     Now Vertical Velocity    ! 
    172       !                                           !------------------------------! 
    173           z2dt = 2._wp * rdt                              ! set time step size (Euler/Leapfrog) 
    174  
    175           z1_2dt = 1.e0 / z2dt 
    176           DO jk = jpkm1, 1, -1                             ! integrate from the bottom the hor. divergence 
    177              ! - ML - need 3 lines here because replacement of fse3t by its expression yields too long lines otherwise 
    178              wsd3d(:,:,jk) = wsd3d(:,:,jk+1) -   fse3t_n(:,:,jk) * hdivn(:,:,jk)        & 
    179                 &                      - ( fse3t_a(:,:,jk) - fse3t_b(:,:,jk) )    & 
    180                 &                         * tmask(:,:,jk) * z1_2dt 
    181 #if defined key_bdy 
    182              wsd3d(:,:,jk) = wsd3d(:,:,jk) * bdytmask(:,:) 
    183 #endif 
    184           END DO 
    185           hdivn(:,:,:)=hdivdummy(:,:,:) 
    186           rotn(:,:,:)=rotdummy(:,:,:) 
    187           vn(:,:,:)=vdummy(:,:,:) 
    188           un(:,:,:)=udummy(:,:,:) 
    189           CALL wrk_dealloc( jpi,jpj,jpk,udummy,vdummy,hdivdummy,rotdummy) 
    190       ENDIF 
    191    END SUBROUTINE sbc_wave 
     210      CALL fld_read( kt, nn_fsbc, sf_wavepar )      !* read wave parameters from ECWAM NetCDF file 
     211      ust_wavepar(:,:) = sf_wavepar(jp_ust)%fnow(:,:,1) 
     212      vst_wavepar(:,:) = sf_wavepar(jp_vst)%fnow(:,:,1) 
     213      swh_wavepar(:,:) = sf_wavepar(jp_swh)%fnow(:,:,1) 
     214      mwp_wavepar(:,:) = sf_wavepar(jp_mwp)%fnow(:,:,1) 
     215      !cdww_wavepar(:,:) = sf_wavepar(jp_cdww)%fnow(:,:,1) 
     216      wspd_wavepar(:,:) = sf_wavepar(jp_wspd)%fnow(:,:,1) 
     217      phioc_wavepar(:,:) = sf_wavepar(jp_phioc)%fnow(:,:,1) 
     218      tauoc_wavepar(:,:) = sf_wavepar(jp_tauoc)%fnow(:,:,1) 
     219  
     220      
     221       rn_crban(:,:)=29*phioc_wavepar(:,:) ! Alfa is phioc*sqrt(rw/ra)sbc_wa 
     222       ! Limit cr_ban between 10 and 300 
     223       DO iii=1,jpi 
     224           DO jjj=1,jpj 
     225 
     226                IF (rn_crban(iii,jjj) < 10 ) THEN 
     227                rn_crban(iii,jjj)=10                 
     228                ELSEIF (rn_crban(iii,jjj) > 300) THEN                
     229                rn_crban(iii,jjj)=300 
     230                ENDIF 
     231         
     232           ENDDO 
     233       ENDDO 
     234  
     235     END SUBROUTINE sbc_wavepar 
    192236       
    193    !!====================================================================== 
     237 
    194238END MODULE sbcwave 
Note: See TracChangeset for help on using the changeset viewer.