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 7905 for branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM – NEMO

Ignore:
Timestamp:
2017-04-13T12:07:16+02:00 (7 years ago)
Author:
jcastill
Message:

Series of small bug fixes and stetic changes:

-Fix possible bug in the calculation of Stokes-Coriolis
-Move all the wave control variables to namelist namsbc_wave
-Use one namelist variable instead of two to set Stokes drift velocity coupling
-Cap the values of the Craig and Banner constant as calculated from wave input fields to take into account small values of the friction velocity
-Add new Phillips parametrization for Stokes drift vertical velocity, using the inverse depth scale as in Breivik 2015, instead of the peak wave number as calculated from wave input fields
-Better control of the wave fields that are read from file depending on the wave parameters

Location:
branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/CONFIG/SHARED/namelist_ref

    r7878 r7905  
    266266                           !     =2 annual global mean of e-p-r set to zero 
    267267   ln_wave = .false.       !  Activate coupling with wave (T => fill namsbc_wave)   
    268    ln_cdgw = .false.       !  Neutral drag coefficient read from wave model (T => ln_wave=.true. & fill namsbc_wave)   
    269    ln_sdw  = .false.       !  Read 2D Surf Stokes Drift & Computation of 3D stokes drift (T => ln_wave=.true. & fill namsbc_wave)    
    270    ln_tauoc= .false.       !  Activate ocean stress modified by external wave induced stress (T => ln_wave=.true. & fill namsbc_wave)   
    271    ln_phioc= .false.       !  Activate wave to ocean energy (T => ln_wave=.true. & fill namsbc_wave)   
    272    ln_stcor= .false.       !  Activate Stokes Coriolis term (T => ln_wave=.true. & ln_sdw=.true. & fill namsbc_wave)   
    273268   nn_lsm  = 0             !  =0 land/sea mask for input fields is not applied (keep empty land/sea mask filename field) , 
    274269                           !  =1:n number of iterations of land/sea mask application for input fields (fill land/sea mask filename field) 
     
    278273                           !  = 1  Average and redistribute per-category fluxes, forced mode only, not yet implemented coupled 
    279274                           !  = 2  Redistribute a single flux over categories (coupled mode only) 
    280    nn_drag   = 0           !  formula to calculate momentum from the wind components 
    281                            !  = 0 UKMO SHELF formulation 
    282                            !  = 1 standard formulation with forced of coupled drag coefficient 
    283                            !  = 2 standard formulation with constant drag coefficient 
    284                            !  = 3 momentum calculated from core forcing fields 
    285    nn_sdrift = 0           !  Parameterization for the calculation of 3D-Stokes drift from the surface Stokes drift 
    286                            !  = 0 Breivik 2015 parameterization: v_z=v_0*[exp(2*k*z)/(1-8*k*z)] 
    287                            !  = 1 Phillips:                      v_z=v_o*[exp(2*k*z)-beta*sqrt(-2*k*pi*z)*erfc(sqrt(-2*k*z))] 
    288275/ 
    289276!----------------------------------------------------------------------- 
     
    394381   sn_rcv_mslp   =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
    395382   sn_rcv_phioc  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
    396    sn_rcv_sdrfx  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
    397    sn_rcv_sdrfy  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
     383   sn_rcv_sdrft  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
    398384   sn_rcv_wper   =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
    399385   sn_rcv_wfreq  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
     
    948934   ln_zdfexp   = .false.   !  time-stepping: split-explicit (T) or implicit (F) time stepping 
    949935   nn_zdfexp   =    3            !  number of sub-timestep for ln_zdfexp=T 
    950    ln_zdfqiao  = .false.   !  Enhanced wave vertical mixing Qiao (2010) (T => ln_wave=.true. & ln_sdw=.true. & fill namsbc_wave) 
    951936/ 
    952937!----------------------------------------------------------------------- 
     
    10221007   nn_stab_func  =     2   !  stability function (0=Galp, 1= KC94, 2=CanutoA, 3=CanutoB) 
    10231008   nn_clos       =     1   !  predefined closure type (0=MY82, 1=k-eps, 2=k-w, 3=Gen) 
    1024    nn_wmix       =     0   !  type of wave breaking mixing 
    1025            !                             ! = 0 Craig and Banner formulation (original NEMO formulation)  
    1026            !                             ! = 1 Janssen formulation (no assumption of direct energy conversion)  
    10271009/ 
    10281010!----------------------------------------------------------------------- 
     
    13021284!              !  file name  ! frequency (hours) ! variable     ! time interp. !  clim   ! 'yearly'/ ! weights  ! rotation ! land/sea mask ! 
    13031285!              !             !  (if <0  months)  !   name       !   (logical)  !  (T/F)  ! 'monthly' ! filename ! pairing  ! filename      ! 
     1286   ln_cdgw     = .false.   !  Neutral drag coefficient read from wave model 
     1287   ln_sdw      = .false.   !  Read 2D Surf Stokes Drift & Computation of 3D stokes drift 
     1288   ln_stcor    = .false.   !  Activate Stokes Coriolis term 
     1289   ln_tauoc    = .false.   !  Activate ocean stress modified by external wave induced stress 
     1290   ln_phioc    = .false.   !  Activate wave to ocean energy 
     1291   ln_rough    = .false.   !  Wave roughness equals the significant wave height 
     1292   ln_zdfqiao  = .false.   !  Enhanced wave vertical mixing Qiao (2010) 
     1293   nn_drag   = 0      !  formula to calculate momentum from the wind components 
     1294                           ! = 0 UKMO SHELF formulation 
     1295                           ! = 1 standard formulation with forced of coupled drag coefficient 
     1296                           ! = 2 standard formulation with constant drag coefficient 
     1297                           ! = 3 momentum calculated from core forcing fields 
     1298   nn_sdrift   =  0   !  Parameterization for the calculation of 3D-Stokes drift from the surface Stokes drift 
     1299                           ! = 0 Breivik 2015 parameterization: v_z=v_0*[exp(2*k*z)/(1-8*k*z)] 
     1300                           ! = 1 Phillips:                      v_z=v_o*[exp(2*k*z)-beta*sqrt(-2*k*pi*z)*erfc(sqrt(-2*k*z))] 
     1301   nn_wmix     =  0   !  type of wave breaking mixing 
     1302                           ! = 0 Craig and Banner formulation (original NEMO formulation)  
     1303                           ! = 1 Janssen formulation (no assumption of direct energy conversion)  
    13041304   sn_cdg      =  'sdw_wave' ,        1          , 'drag_coeff' ,     .true.   , .false. , 'daily'   ,  ''      , ''       , '' 
    13051305   sn_usd      =  'sdw_wave' ,        1          , 'u_sd2d'     ,     .true.   , .false. , 'daily'   ,  ''      , ''       , '' 
     
    13111311   sn_tauoc    =  'sdw_wave' ,        1          , 'wave_stress',     .true.   , .false. , 'daily'   ,  ''      , ''       , ''  
    13121312   sn_phioc    =  'sdw_wave' ,        1          , 'wave_energy',     .true.   , .false. , 'daily'   ,  ''      , ''       , ''  
     1313   cn_dir      = './'  !  root directory for the location of wave forcing files 
    13131314!  
    1314    cn_dir      = './'  !  root directory for the location of drag coefficient files 
    13151315/ 
    13161316!----------------------------------------------------------------------- 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/DYN/dynvor.F90

    r7606 r7905  
    163163                             CALL vor_ens( kt, nrvm, un , vn , ua, va )   ! relative vorticity or metric trend (ens) 
    164164                             CALL vor_ene( kt, ncor, un , vn , ua, va )   ! planetary vorticity trend (ene) 
     165            IF( ln_stcor )   CALL vor_ens( kt, nrvm, usd, vsd, ua, va )   ! add the Stokes-Coriolis trend 
    165166            IF( ln_stcor )   CALL vor_ene( kt, ncor, usd, vsd, ua, va )   ! add the Stokes-Coriolis trend 
    166167         ENDIF 
     
    182183         ELSE 
    183184                             CALL vor_een( kt, ntot, un, vn, ua, va )    ! total vorticity 
    184             IF( ln_stcor )   CALL vor_ene( kt, ncor, usd, vsd, ua, va )  ! add the Stokes-Coriolis trend 
     185            IF( ln_stcor )   CALL vor_een( kt, ncor, usd, vsd, ua, va )  ! add the Stokes-Coriolis trend 
    185186         ENDIF 
    186187         ! 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r7878 r7905  
    6666   LOGICAL , PUBLIC ::   ln_wave        !: true if some coupling with wave model 
    6767   LOGICAL , PUBLIC ::   ln_cdgw        !: true if neutral drag coefficient from wave model 
    68    LOGICAL , PUBLIC ::   ln_sdw         !: true if 3d stokes drift from wave model 
     68   LOGICAL , PUBLIC ::   ln_sdw         !: true if 3d Stokes drift from wave model 
     69   LOGICAL , PUBLIC ::   ln_stcor       !: true if Stokes-Coriolis term is used  
    6970   LOGICAL , PUBLIC ::   ln_tauoc       !: true if normalized stress from wave is used  
    7071   LOGICAL , PUBLIC ::   ln_phioc       !: true if wave energy to ocean is used  
    71    LOGICAL , PUBLIC ::   ln_stcor       !: true if Stokes-Coriolis term is used  
     72   LOGICAL , PUBLIC ::   ln_rough       !: true if wave roughness equals significant wave height 
     73   LOGICAL , PUBLIC ::   ln_zdfqiao     !: Enhanced wave vertical mixing Qiao(2010) formulation flag 
    7274   INTEGER , PUBLIC ::   nn_drag        ! type of formula to calculate wind stress from wind components 
    73    INTEGER , PUBLIC ::   nn_sdrift      ! type of parameterization to calculate vertical Stokes drift 
     75   INTEGER , PUBLIC ::   nn_wmix        ! type of wave breaking mixing 
    7476   ! 
    7577   LOGICAL , PUBLIC ::   ln_icebergs    !: Icebergs 
     
    107109 
    108110   !!---------------------------------------------------------------------- 
    109    !!           Stokes drift parameterization 
    110    !!---------------------------------------------------------------------- 
    111    INTEGER, PUBLIC, PARAMETER ::   jp_breivik  = 0     ! Breivik 2015: v_z=v_0*[exp(2*k*z)/(1-8*k*z)] 
    112    INTEGER, PUBLIC, PARAMETER ::   jp_phillips = 1     ! Phillips:     v_z=v_o*[exp(2*k*z)-beta*sqrt(-2*k*pi*z)*erfc(sqrt(-2*k*z))] 
     111   !!           Wave mixing vertical parameterization 
     112   !!---------------------------------------------------------------------- 
     113   INTEGER, PUBLIC, PARAMETER ::   jp_craigbanner = 0  ! Craig and Banner formulation (original NEMO formulation - 
     114                                                       !    direct conversion of mechanical to turbulent energy) 
     115   INTEGER, PUBLIC, PARAMETER ::   jp_janssen     = 1  ! Janssen formulation - no assumption on direct energy conversion  
    113116 
    114117   !!---------------------------------------------------------------------- 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r7878 r7905  
    168168   TYPE(FLD_C) ::   sn_snd_ifrac, sn_snd_crtw, sn_snd_wlev   
    169169   ! Received from waves   
    170    TYPE(FLD_C) ::   sn_rcv_hsig,sn_rcv_phioc,sn_rcv_sdrfx,sn_rcv_sdrfy,sn_rcv_wper, & 
     170   TYPE(FLD_C) ::   sn_rcv_hsig,sn_rcv_phioc,sn_rcv_sdrft,sn_rcv_wper, & 
    171171                    sn_rcv_wfreq,sn_rcv_wnum,sn_rcv_tauoc,sn_rcv_wdrag 
    172172   ! Other namelist parameters                        ! 
     
    244244         &                  sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau   , sn_rcv_dqnsdt, sn_rcv_qsr,      &   
    245245         &                  sn_snd_ifrac, sn_snd_crtw , sn_snd_wlev  , sn_rcv_hsig  , sn_rcv_phioc ,   &   
    246          &                  sn_rcv_sdrfx, sn_rcv_sdrfy, sn_rcv_wper  , sn_rcv_wnum  , sn_rcv_wfreq,    & 
    247          &                  sn_rcv_tauoc, sn_rcv_wdrag, sn_rcv_qns   , sn_rcv_emp   , sn_rcv_rnf,      & 
    248          &                  sn_rcv_cal , sn_rcv_iceflx, sn_rcv_co2   , sn_rcv_mslp  , nn_cplmodel,     & 
    249          &                  ln_usecplmask 
     246         &                  sn_rcv_sdrft, sn_rcv_wper  , sn_rcv_wnum  , sn_rcv_wfreq, sn_rcv_tauoc,    & 
     247         &                  sn_rcv_wdrag, sn_rcv_qns   , sn_rcv_emp   , sn_rcv_rnf  , sn_rcv_cal ,     & 
     248         &                  sn_rcv_iceflx, sn_rcv_co2   , sn_rcv_mslp  , nn_cplmodel, ln_usecplmask 
    250249      !!--------------------------------------------------------------------- 
    251250      ! 
     
    290289         WRITE(numout,*)'      significant wave heigth         = ', TRIM(sn_rcv_hsig%cldes  ), ' (', TRIM(sn_rcv_hsig%clcat  ), ')'   
    291290         WRITE(numout,*)'      wave to oce energy flux         = ', TRIM(sn_rcv_phioc%cldes ), ' (', TRIM(sn_rcv_phioc%clcat ), ')'   
    292          WRITE(numout,*)'      Surface Stokes drift grid u     = ', TRIM(sn_rcv_sdrfx%cldes ), ' (', TRIM(sn_rcv_sdrfx%clcat ), ')'   
    293          WRITE(numout,*)'      Surface Stokes drift grid v     = ', TRIM(sn_rcv_sdrfy%cldes ), ' (', TRIM(sn_rcv_sdrfy%clcat ), ')'   
     291         WRITE(numout,*)'      Surface Stokes drift u,v        = ', TRIM(sn_rcv_sdrft%cldes ), ' (', TRIM(sn_rcv_sdrft%clcat ), ')'   
    294292         WRITE(numout,*)'      Mean wave period                = ', TRIM(sn_rcv_wper%cldes  ), ' (', TRIM(sn_rcv_wper%clcat  ), ')'   
    295293         WRITE(numout,*)'      Mean wave number                = ', TRIM(sn_rcv_wnum%cldes  ), ' (', TRIM(sn_rcv_wnum%clcat  ), ')'   
     
    549547      ENDIF  
    550548      srcv(jpr_sdrftx)%clname = 'O_Sdrfx'    ! Stokes drift in the u direction  
    551       IF( TRIM(sn_rcv_sdrfx%cldes ) == 'coupled' )  THEN  
     549      srcv(jpr_sdrfty)%clname = 'O_Sdrfy'    ! Stokes drift in the v direction  
     550      IF( TRIM(sn_rcv_sdrft%cldes ) == 'coupled' )  THEN  
    552551         srcv(jpr_sdrftx)%laction = .TRUE.  
    553          cpl_sdrftx = .TRUE.  
    554       ENDIF  
    555       srcv(jpr_sdrfty)%clname = 'O_Sdrfy'    ! Stokes drift in the v direction  
    556       IF( TRIM(sn_rcv_sdrfy%cldes ) == 'coupled' )  THEN  
    557552         srcv(jpr_sdrfty)%laction = .TRUE.  
    558          cpl_sdrfty = .TRUE.  
     553         cpl_sdrft = .TRUE.  
    559554      ENDIF  
    560555      srcv(jpr_wper)%clname = 'O_WPer'       ! mean wave period  
     
    964959      !!                        emp          upward mass flux [evap. - precip. (- runoffs) (- calving)] (ocean only case) 
    965960      !!---------------------------------------------------------------------- 
    966       USE zdf_oce,  ONLY : ln_zdfqiao 
    967961      USE sbcflx ,  ONLY : ln_shelf_flx 
    968962 
     
    11711165      IF( ln_sdw ) THEN  ! Stokes Drift correction activated  
    11721166      !                                                      ! ========================= !   
    1173       !                                                      !       Stokes drift u      !  
     1167      !                                                      !     Stokes drift u,v      !  
    11741168      !                                                      ! ========================= !   
    1175          IF( srcv(jpr_sdrftx)%laction ) ut0sd(:,:) = frcv(jpr_sdrftx)%z3(:,:,1)  
    1176       !  
    1177       !                                                      ! ========================= !   
    1178       !                                                      !       Stokes drift v      !  
    1179       !                                                      ! ========================= !   
    1180          IF( srcv(jpr_sdrfty)%laction ) vt0sd(:,:) = frcv(jpr_sdrfty)%z3(:,:,1)  
     1169         IF( srcv(jpr_sdrftx)%laction .AND. srcv(jpr_sdrfty)%laction ) THEN 
     1170                                        ut0sd(:,:) = frcv(jpr_sdrftx)%z3(:,:,1)  
     1171                                        vt0sd(:,:) = frcv(jpr_sdrfty)%z3(:,:,1)  
     1172         ENDIF 
    11811173      !  
    11821174      !                                                      ! ========================= !   
     
    12011193       
    12021194         ! Calculate the 3D Stokes drift both in coupled and not fully uncoupled mode  
    1203          IF( srcv(jpr_sdrftx)%laction .OR. srcv(jpr_sdrfty)%laction .OR. srcv(jpr_wper)%laction &  
    1204                                       .OR. srcv(jpr_hsig)%laction   .OR. srcv(jpr_wfreq)%laction) &  
     1195         IF( (srcv(jpr_sdrftx)%laction .AND. srcv(jpr_sdrfty)%laction) .OR. srcv(jpr_wper)%laction &  
     1196                                        .OR. srcv(jpr_hsig)%laction   .OR. srcv(jpr_wfreq)%laction) &  
    12051197            CALL sbc_stokes()  
    12061198      ENDIF  
     
    12151207      IF( srcv(jpr_phioc)%laction .AND. ln_phioc ) THEN 
    12161208         rn_crban(:,:) = 29.0 * frcv(jpr_phioc)%z3(:,:,1) 
     1209         WHERE( rn_crban <    0.0 ) rn_crban = 0.0 
     1210         WHERE( rn_crban > 1000.0 ) rn_crban = 1000.0 
    12171211      ENDIF 
    12181212       
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r7878 r7905  
    8888      NAMELIST/namsbc/ nn_fsbc   , ln_ana    , ln_flx, ln_blk_clio, ln_blk_core, ln_mixcpl,   & 
    8989         &             ln_blk_mfs, ln_apr_dyn, nn_ice, nn_ice_embd, ln_dm2dc   , ln_rnf   ,   & 
    90          &             ln_ssr    , nn_isf    , nn_fwb, ln_cdgw    , ln_wave    , ln_sdw   ,   & 
    91          &             ln_tauoc  , ln_stcor  , nn_lsm, nn_limflx , nn_components, ln_cpl  ,   & 
    92          &             ln_phioc  , ln_wavcpl , nn_drag, nn_sdrift 
     90         &             ln_ssr    , nn_isf    , nn_fwb, ln_wave    , nn_lsm     , nn_limflx,   & 
     91                       nn_components, ln_cpl , ln_wavcpl 
    9392      INTEGER  ::   ios 
    9493      INTEGER  ::   ierr, ierr0, ierr1, ierr2, ierr3, jpm 
     
    134133         WRITE(numout,*) '              forced-coupled wav mixed formulation       ln_wavcpl   = ', ln_wavcpl 
    135134         WRITE(numout,*) '              wave physics                               ln_wave     = ', ln_wave  
    136          WRITE(numout,*) '                 Stokes drift corr. to vert. velocity    ln_sdw      = ', ln_sdw  
    137          WRITE(numout,*) '                 wave modified ocean stress              ln_tauoc    = ', ln_tauoc  
    138          WRITE(numout,*) '                 wave to ocean energy - wave breaking    ln_phioc    = ', ln_phioc 
    139          WRITE(numout,*) '                 Stokes coriolis term                    ln_stcor    = ', ln_stcor  
    140          WRITE(numout,*) '                 neutral drag coefficient                ln_cdgw     = ', ln_cdgw 
    141135         WRITE(numout,*) '              OASIS coupling (with atm or sas)           lk_oasis    = ', lk_oasis 
    142136         WRITE(numout,*) '              components of your executable              nn_components = ', nn_components 
     
    153147         WRITE(numout,*) '              closed sea (=0/1) (set in namdom)          nn_closea   = ', nn_closea 
    154148         WRITE(numout,*) '              n. of iterations if land-sea-mask applied  nn_lsm      = ', nn_lsm 
    155          WRITE(numout,*) '              momentum formulation                       nn_drag     = ', nn_drag 
    156149      ENDIF 
    157150 
     
    222215      IF( ln_dm2dc .AND. .NOT.( ln_flx .OR. ln_blk_core ) .AND. nn_components /= jp_iam_opa )   & 
    223216         &   CALL ctl_stop( 'diurnal cycle into qsr field from daily values requires a flux or core-bulk formulation' ) 
    224        
    225       IF ( ln_wave ) THEN 
    226          !Activated wave module but neither drag nor stokes drift activated  
    227          IF ( .NOT.(ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor .OR. ln_phioc) )   THEN   
    228              CALL ctl_warn( 'Ask for wave coupling but ln_cdgw=F, ln_sdw=F, ln_tauoc=F, ln_stcor=F, ln_phioc=F')  
    229          ELSEIF (ln_stcor .AND. .NOT. ln_sdw) THEN   
    230              CALL ctl_stop( 'Stokes-Coriolis term calculated only if activated Stokes Drift ln_sdw=T') 
    231          ENDIF 
    232          IF ( ln_cdgw .AND. .NOT.(nn_drag==jp_ukmo .OR. nn_drag==jp_std .OR. nn_drag==jp_const .OR. nn_drag==jp_mcore) ) &  
    233              CALL ctl_stop( 'The chosen nn_drag for momentum calculation must be 0, 1, 2, or 3') 
    234          IF ( ln_cdgw .AND. ln_blk_core .AND. nn_drag==0 ) & 
    235              CALL ctl_stop( 'The chosen nn_drag for momentum calculation in core forcing must be 1, 2, or 3') 
    236          IF ( ln_cdgw .AND. ln_flx .AND. nn_drag==3 ) & 
    237              CALL ctl_stop( 'The chosen nn_drag for momentum calculation in direct forcing must be 0, 1, or 2') 
    238          IF ( ln_sdw .AND. .NOT.(nn_sdrift==jp_breivik .OR. nn_sdrift==jp_phillips) ) & 
    239              CALL ctl_stop( 'The chosen nn_sdrift for vertical Stokes drift must be 0, or 1') 
    240       ELSE 
    241          IF ( ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor .OR. ln_phioc ) &   
    242             &   CALL ctl_stop( 'Not Activated Wave Module (ln_wave=F) but asked coupling ',    &  
    243             &                  'with drag coefficient (ln_cdgw =T) '  ,                        &  
    244             &                  'or Stokes Drift (ln_sdw=T) ' ,                                 &  
    245             &                  'or ocean stress modification due to waves (ln_tauoc=T) ',      &  
    246             &                  'or wave to ocean energy modification (ln_phioc=T) ',           &  
    247             &                  'or Stokes-Coriolis term (ln_stcor=T)'  ) 
    248       ENDIF  
    249217      !                          ! Choice of the Surface Boudary Condition (set nsbc) 
    250218      ll_purecpl = ln_cpl .AND. .NOT. ln_mixcpl .AND. .NOT. ln_wavcpl 
     
    414382            SELECT CASE( nsbc )  
    415383            CASE(  0,1,2,3,5,-1 )  ;  
    416                 IF(lwp .AND. kt == nit000 ) WRITE(numout,*) 'WARNING: You are subtracting the wave stress to the ocean. &  
    417                         & If not requested select ln_tauoc=.false'  
     384                IF(lwp .AND. kt == nit000 ) THEN 
     385                   write(numout,*) 
     386                   WRITE(numout,*) 'WARNING: You are subtracting the wave stress to the ocean. &  
     387                                                      & If not requested select ln_tauoc=.false'  
     388                   write(numout,*) 
     389                END IF 
    418390            END SELECT  
    419391      !  
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r7878 r7905  
    1818   USE oce            ! ocean variables 
    1919   USE sbc_oce        ! Surface boundary condition: ocean fields 
    20    USE zdf_oce,  ONLY : ln_zdfqiao 
    2120   USE bdy_oce        ! open boundary condition variables 
    2221   USE domvvl         ! domain: variable volume layers 
     
    3938   LOGICAL, PUBLIC ::   cpl_hsig   = .FALSE. 
    4039   LOGICAL, PUBLIC ::   cpl_phioc  = .FALSE. 
    41    LOGICAL, PUBLIC ::   cpl_sdrftx = .FALSE. 
    42    LOGICAL, PUBLIC ::   cpl_sdrfty = .FALSE. 
     40   LOGICAL, PUBLIC ::   cpl_sdrft  = .FALSE. 
    4341   LOGICAL, PUBLIC ::   cpl_wper   = .FALSE. 
    4442   LOGICAL, PUBLIC ::   cpl_wfreq  = .FALSE. 
     
    4644   LOGICAL, PUBLIC ::   cpl_tauoc  = .FALSE. 
    4745   LOGICAL, PUBLIC ::   cpl_wdrag  = .FALSE. 
     46 
     47   INTEGER ::   nn_sdrift      ! type of parameterization to calculate vertical Stokes drift 
     48   INTEGER, PARAMETER ::   jp_breivik  = 0     ! Breivik 2015: v_z=v_0*[exp(2*k*z)/(1-8*k*z)] 
     49   INTEGER, PARAMETER ::   jp_phillips = 1     ! Phillips:     v_z=v_o*[exp(2*k*z)-beta*sqrt(-2*k*pi*z)*erfc(sqrt(-2*k*z))] 
     50   INTEGER, PARAMETER ::   jp_peakph   = 2     ! Phillips using the peak wave number read from wave model instead of the inverse depth scale 
    4851 
    4952   INTEGER ::   jpfld    ! number of files to read for stokes drift 
     
    103106      ! 
    104107      ! select parameterization for the calculation of vertical Stokes drift 
    105       SELECT CASE ( nn_sdrift ) 
    106       ! 
    107       CASE ( jp_breivik ) 
     108      ! exp. wave number at t-point 
     109      IF( nn_sdrift==jp_breivik .OR. nn_sdrift==jp_phillips ) THEN   ! (Eq. (19) in Breivick et al. (2014) ) 
    108110         zfac = 2.0_wp * rpi / 16.0_wp 
    109          DO jj = 1, jpj               ! exp. wave number at t-point    (Eq. (19) in Breivick et al. (2014) ) 
     111         DO jj = 1, jpj                
    110112            DO ji = 1, jpi 
    111113               ! Stokes drift velocity estimated from Hs and Tmean 
     
    126128            END DO 
    127129         END DO 
    128          ! 
    129          !                       !==  horizontal Stokes Drift 3D velocity  ==! 
     130      ELSE IF( nn_sdrift==jp_peakph ) THEN    ! peak wave number calculated from the peak frequency received by the wave model 
     131         DO jj = 1, jpjm1               
     132            DO ji = 1, jpim1 
     133               zk_u(ji,jj) = 0.5_wp * ( wfreq(ji,jj)*wfreq(ji,jj) + wfreq(ji+1,jj)*wfreq(ji+1,jj) ) / grav 
     134               zk_v(ji,jj) = 0.5_wp * ( wfreq(ji,jj)*wfreq(ji,jj) + wfreq(ji,jj+1)*wfreq(ji,jj+1) ) / grav 
     135               ! 
     136               zu0_sd(ji,jj) = 0.5_wp * ( ut0sd(ji,jj) + ut0sd(ji+1,jj) ) 
     137               zv0_sd(ji,jj) = 0.5_wp * ( vt0sd(ji,jj) + vt0sd(ji,jj+1) ) 
     138            END DO 
     139         END DO 
     140      ENDIF 
     141      ! 
     142      !                       !==  horizontal Stokes Drift 3D velocity  ==! 
     143      IF( nn_sdrift==jp_breivik ) THEN 
    130144         DO jk = 1, jpkm1 
    131145            DO jj = 2, jpjm1 
     
    145159            END DO 
    146160         END DO 
    147       CASE ( jp_phillips ) 
    148          DO jj = 1, jpjm1              ! Peak wavenumber & Stokes drift velocity at u- & v-points 
    149             DO ji = 1, jpim1 
    150                zk_u(ji,jj) = 0.5_wp * ( wfreq(ji,jj)*wfreq(ji,jj) + wfreq(ji+1,jj)*wfreq(ji+1,jj) ) / grav 
    151                zk_v(ji,jj) = 0.5_wp * ( wfreq(ji,jj)*wfreq(ji,jj) + wfreq(ji,jj+1)*wfreq(ji,jj+1) ) / grav 
    152                ! 
    153                zu0_sd(ji,jj) = 0.5_wp * ( ut0sd(ji,jj) + ut0sd(ji+1,jj) ) 
    154                zv0_sd(ji,jj) = 0.5_wp * ( vt0sd(ji,jj) + vt0sd(ji,jj+1) ) 
    155             END DO 
    156          END DO 
    157          ! 
    158          !                       !==  horizontal Stokes Drift 3D velocity  ==! 
     161      ELSE IF( nn_sdrift==jp_phillips .OR. nn_sdrift==jp_peakph ) THEN 
    159162         DO jk = 1, jpkm1 
    160163            DO jj = 2, jpjm1 
     
    165168                  zkh_u = zk_u(ji,jj) * zdep_u     ! k * depth 
    166169                  zkh_v = zk_v(ji,jj) * zdep_v 
    167                   !                                ! Depth attenuation: beta=1 for Phillips 
    168                   zda_u = EXP( -2.0_wp*zkh_u ) - 1.0*SQRT(2.0*rpi*zkh_u) * ERFC(SQRT(2.0*zkh_u)) 
    169                   zda_v = EXP( -2.0_wp*zkh_v ) - 1.0*SQRT(2.0*rpi*zkh_v) * ERFC(SQRT(2.0*zkh_v)) 
     170                  !                                ! Depth attenuation 
     171                  zda_u = EXP( -2.0_wp*zkh_u ) - SQRT(2.0_wp*rpi*zkh_u) * ERFC(SQRT(2.0_wp*zkh_u)) 
     172                  zda_v = EXP( -2.0_wp*zkh_v ) - SQRT(2.0_wp*rpi*zkh_v) * ERFC(SQRT(2.0_wp*zkh_v)) 
    170173                  ! 
    171174                  usd(ji,jj,jk) = zda_u * zu0_sd(ji,jj) * umask(ji,jj,jk) 
     
    174177            END DO 
    175178         END DO 
    176       END SELECT 
     179      ENDIF 
    177180 
    178181      CALL lbc_lnk( usd(:,:,:), 'U', vsd(:,:,:), 'V', -1. ) 
     
    265268         CALL fld_read( kt, nn_fsbc, sf_phioc )          ! read wave to ocean energy from external forcing 
    266269         rn_crban(:,:) = 29.0 * sf_phioc(1)%fnow(:,:,1)     ! ! Alfa is phioc*sqrt(rau0/zrhoa)  : rau0=water density, zhroa= air density 
    267          WHERE( rn_crban < -1000.0 ) rn_crban = 0.0 
    268          WHERE( rn_crban >  1000.0 ) rn_crban = 0.0 
    269       ENDIF 
    270  
    271       IF( ln_sdw )  THEN                           !==  Computation of the 3d Stokes Drift  ==!  
     270         WHERE( rn_crban > 1.e8   ) rn_crban = 0.0    !remove first mask mistmatch points, then cap values in case of low friction velocity 
     271         WHERE( rn_crban < 0.0    ) rn_crban = 0.0 
     272         WHERE( rn_crban > 1000.0 ) rn_crban = 1000.0 
     273      ENDIF 
     274 
     275      IF( ln_sdw .OR. ln_rough )  THEN             !==  Computation of the 3d Stokes Drift  ==!  
    272276         ! 
    273277         IF( jpfld > 0 ) THEN                            ! Read from file only if the field is not coupled 
     
    285289            IF( jp_wfr > 0 ) THEN 
    286290               wfreq(:,:) = sf_sd(jp_wfr)%fnow(:,:,1)   ! Peak wave frequency  
    287                WHERE( wfreq <    0.0 ) wfreq = 0.001  
    288                WHERE( wfreq >  100.0 ) wfreq = 0.001 
     291               WHERE( wfreq <    0.0 ) wfreq = 0.0  
     292               WHERE( wfreq >  100.0 ) wfreq = 0.0 
    289293            ENDIF 
    290294            IF( jp_usd > 0 ) THEN 
     
    299303            ENDIF 
    300304         ENDIF 
    301          ! 
     305      ENDIF 
     306      ! 
     307      IF( ln_sdw ) THEN 
    302308         ! Read also wave number if needed, so that it is available in coupling routines 
    303309         IF( ln_zdfqiao .AND. .NOT.cpl_wnum ) THEN 
     
    308314         !                                         !==  Computation of the 3d Stokes Drift  ==!  
    309315         ! 
    310          IF( (nn_sdrift==jp_breivik  .AND. jp_hsw>0 .AND. jp_wmp>0 .AND. jp_usd>0 .AND. jp_vsd>0) .OR. & 
    311              (nn_sdrift==jp_phillips .AND. jp_wfr>0 .AND. jp_usd>0 .AND. jp_vsd>0) ) & 
     316         IF( ((nn_sdrift==jp_breivik .OR. nn_sdrift==jp_phillips) .AND. & 
     317                          jp_hsw>0 .AND. jp_wmp>0 .AND. jp_usd>0 .AND. jp_vsd>0) .OR. & 
     318             (nn_sdrift==jp_peakph .AND. jp_wfr>0 .AND. jp_usd>0 .AND. jp_vsd>0) ) & 
    312319            CALL sbc_stokes()            ! Calculate only if required fields are read 
    313320         !                               ! In coupled wave model-NEMO case the call is done after coupling 
     
    341348                             &   sn_tauoc      ! informations about the fields to be read 
    342349      ! 
    343       NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wfr, sn_wnum, sn_tauoc, sn_phioc 
     350      NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wfr, sn_wnum, sn_tauoc, sn_phioc, & 
     351                             ln_cdgw, ln_sdw, ln_stcor, ln_phioc, ln_tauoc, ln_zdfqiao, ln_rough,                 & 
     352                             nn_drag, nn_sdrift, nn_wmix 
    344353      !!--------------------------------------------------------------------- 
    345354      ! 
     
    353362      IF(lwm) WRITE ( numond, namsbc_wave ) 
    354363      ! 
     364      IF(lwp) THEN               !* Parameter print 
     365         WRITE(numout,*) 
     366         WRITE(numout,*) 'sbc_wave_init: wave physics' 
     367         WRITE(numout,*) '~~~~~~~~' 
     368         WRITE(numout,*) '   Namelist namsbc_wave : set wave physics parameters' 
     369         WRITE(numout,*) '      Stokes drift corr. to vert. velocity    ln_sdw      = ', ln_sdw  
     370         WRITE(numout,*) '        vertical parametrization              nn_sdrift   = ', nn_sdrift  
     371         WRITE(numout,*) '      Stokes coriolis term                    ln_stcor    = ', ln_stcor  
     372         WRITE(numout,*) '      wave modified ocean stress              ln_tauoc    = ', ln_tauoc  
     373         WRITE(numout,*) '      wave to ocean energy                    ln_phioc    = ', ln_phioc 
     374         WRITE(numout,*) '        vertical mixing parametrization       nn_wmix     = ', nn_wmix  
     375         WRITE(numout,*) '      neutral drag coefficient                ln_cdgw     = ', ln_cdgw 
     376         WRITE(numout,*) '        momentum formulation                  nn_drag     = ', nn_drag 
     377         WRITE(numout,*) '      wave roughness length modification      ln_rough    = ', ln_rough  
     378         WRITE(numout,*) '      Qiao vertical mixing formulation        ln_zdfqiao  = ', ln_zdfqiao 
     379      ENDIF 
     380 
     381      IF ( ln_wave ) THEN 
     382         ! Activated wave physics but no wave physics components activated  
     383         IF ( .NOT.(ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor .OR. ln_phioc .OR. ln_rough .OR. ln_zdfqiao) )   THEN   
     384             CALL ctl_warn( 'Ask for wave coupling but ln_cdgw=F, ln_sdw=F, ln_tauoc=F, ln_stcor=F, ln_phioc=F ', & 
     385                                                      'ln_rough=F, ln_zdfqiao=F' )  
     386         ELSEIF (ln_stcor .AND. .NOT. ln_sdw) THEN   
     387             CALL ctl_stop( 'Stokes-Coriolis term calculated only if activated Stokes Drift ln_sdw=T') 
     388         ENDIF 
     389         IF ( ln_cdgw .AND. .NOT.(nn_drag==jp_ukmo .OR. nn_drag==jp_std .OR. nn_drag==jp_const .OR. nn_drag==jp_mcore) ) &  
     390             CALL ctl_stop( 'The chosen nn_drag for momentum calculation must be 0, 1, 2, or 3') 
     391         IF ( ln_cdgw .AND. ln_blk_core .AND. nn_drag==0 ) & 
     392             CALL ctl_stop( 'The chosen nn_drag for momentum calculation in core forcing must be 1, 2, or 3') 
     393         IF ( ln_cdgw .AND. ln_flx .AND. nn_drag==3 ) & 
     394             CALL ctl_stop( 'The chosen nn_drag for momentum calculation in direct forcing must be 0, 1, or 2') 
     395         IF( ln_phioc .AND. .NOT.(nn_wmix==jp_craigbanner .OR. nn_wmix==jp_janssen) ) &  
     396            CALL ctl_stop( 'The chosen nn_wmix for wave vertical mixing must be 0, or 1' ) 
     397         IF( ln_sdw .AND. .NOT.(nn_sdrift==jp_breivik .OR. nn_sdrift==jp_phillips .OR. nn_sdrift==jp_peakph) ) &  
     398            CALL ctl_stop( 'The chosen nn_sdrift for Stokes drift vertical velocity must be 0, 1, or 2' ) 
     399         IF( ln_zdfqiao .AND. .NOT.ln_sdw ) &  
     400            CALL ctl_stop( 'Qiao vertical mixing can not be used without Stokes drift (ln_sdw)' ) 
     401      ELSE 
     402         IF ( ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor .OR. ln_phioc .OR. ln_rough .OR. ln_zdfqiao ) &   
     403            &   CALL ctl_stop( 'Not Activated Wave Module (ln_wave=F) but asked coupling ',    &  
     404            &                  'with drag coefficient (ln_cdgw =T) '  ,                        &  
     405            &                  'or Stokes Drift (ln_sdw=T) ' ,                                 &  
     406            &                  'or Stokes-Coriolis term (ln_stcor=T)',                         & 
     407            &                  'or ocean stress modification due to waves (ln_tauoc=T) ',      &  
     408            &                  'or wave to ocean energy modification (ln_phioc=T) ',           &  
     409            &                  'or wave surface roughness (ln_rough=T) ',                      &  
     410            &                  'or Qiao vertical mixing formulation (ln_zdfqiao=T) ' ) 
     411      ENDIF  
     412      ! 
    355413      IF( ln_cdgw ) THEN 
    356414         IF( .NOT. cpl_wdrag ) THEN 
     
    360418                                   ALLOCATE( sf_cd(1)%fnow(jpi,jpj,1)   ) 
    361419            IF( sn_cdg%ln_tint )   ALLOCATE( sf_cd(1)%fdta(jpi,jpj,1,2) ) 
    362             CALL fld_fill( sf_cd, (/ sn_cdg /), cn_dir, 'sbc_wave_init', 'Wave module ', 'namsbc_wave' ) 
     420            CALL fld_fill( sf_cd, (/ sn_cdg /), cn_dir, 'sbc_wave_init', 'read wave input', 'namsbc_wave' ) 
    363421         ENDIF 
    364422         ALLOCATE( cdn_wave(jpi,jpj) ) 
     
    372430                                    ALLOCATE( sf_tauoc(1)%fnow(jpi,jpj,1)   ) 
    373431            IF( sn_tauoc%ln_tint )  ALLOCATE( sf_tauoc(1)%fdta(jpi,jpj,1,2) ) 
    374             CALL fld_fill( sf_tauoc, (/ sn_tauoc /), cn_dir, 'sbc_wave_init', 'Wave module', 'namsbc_wave' ) 
     432            CALL fld_fill( sf_tauoc, (/ sn_tauoc /), cn_dir, 'sbc_wave_init', 'read wave input', 'namsbc_wave' ) 
    375433         ENDIF 
    376434         ALLOCATE( tauoc_wave(jpi,jpj) ) 
     
    384442                                    ALLOCATE( sf_phioc(1)%fnow(jpi,jpj,1)   ) 
    385443            IF( sn_phioc%ln_tint )  ALLOCATE( sf_phioc(1)%fdta(jpi,jpj,1,2) ) 
    386             CALL fld_fill( sf_phioc, (/ sn_phioc /), cn_dir, 'sbc_wave_init', 'Wave module', 'namsbc_wave' ) 
     444            CALL fld_fill( sf_phioc, (/ sn_phioc /), cn_dir, 'sbc_wave_init', 'read wave input', 'namsbc_wave' ) 
    387445         ENDIF 
    388446         ALLOCATE( rn_crban(jpi,jpj) ) 
    389447      ENDIF 
    390448 
    391       IF( ln_sdw ) THEN   ! Find out how many fields have to be read from file if not coupled 
    392          jpfld=0 
    393          jp_usd=0   ;   jp_vsd=0   ;   jp_hsw=0   ;   jp_wmp=0   ;   jp_wfr=0 
    394          IF( .NOT. cpl_sdrftx ) THEN 
     449      ! Find out how many fields have to be read from file if not coupled 
     450      jpfld=0 
     451      jp_usd=0   ;   jp_vsd=0   ;   jp_hsw=0   ;   jp_wmp=0   ;   jp_wfr=0 
     452      IF( ln_sdw ) THEN 
     453         IF( .NOT. cpl_sdrft ) THEN 
    395454            jpfld  = jpfld + 1 
    396455            jp_usd = jpfld 
    397          ENDIF 
    398          IF( .NOT. cpl_sdrfty ) THEN 
    399456            jpfld  = jpfld + 1 
    400457            jp_vsd = jpfld 
    401458         ENDIF 
    402          IF( .NOT. cpl_hsig ) THEN 
     459         IF( .NOT. cpl_hsig .AND. (nn_sdrift==jp_breivik .OR. nn_sdrift==jp_phillips) ) THEN 
    403460            jpfld  = jpfld + 1 
    404461            jp_hsw = jpfld 
    405462         ENDIF 
    406          IF( .NOT. cpl_wper ) THEN 
     463         IF( .NOT. cpl_wper .AND. (nn_sdrift==jp_breivik .OR. nn_sdrift==jp_phillips) ) THEN 
    407464            jpfld  = jpfld + 1 
    408465            jp_wmp = jpfld 
    409466         ENDIF 
    410          IF( .NOT. cpl_wfreq ) THEN 
     467         IF( .NOT. cpl_wfreq .AND. nn_sdrift==jp_peakph ) THEN 
    411468            jpfld  = jpfld + 1 
    412469            jp_wfr = jpfld 
    413470         ENDIF 
    414  
    415          ! Read from file only the non-coupled fields  
    416          IF( jpfld > 0 ) THEN 
    417             ALLOCATE( slf_i(jpfld) ) 
    418             IF( jp_usd > 0 )   slf_i(jp_usd) = sn_usd 
    419             IF( jp_vsd > 0 )   slf_i(jp_vsd) = sn_vsd 
    420             IF( jp_hsw > 0 )   slf_i(jp_hsw) = sn_hsw 
    421             IF( jp_wmp > 0 )   slf_i(jp_wmp) = sn_wmp 
    422             IF( jp_wfr > 0 )   slf_i(jp_wfr) = sn_wfr 
    423             ALLOCATE( sf_sd(jpfld), STAT=ierror )   !* allocate and fill sf_sd with stokes drift 
    424             IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_sd structure' ) 
    425             ! 
    426             DO ifpr= 1, jpfld 
    427                ALLOCATE( sf_sd(ifpr)%fnow(jpi,jpj,1) ) 
    428                IF( slf_i(ifpr)%ln_tint )   ALLOCATE( sf_sd(ifpr)%fdta(jpi,jpj,1,2) ) 
    429             END DO 
    430             ! 
    431             CALL fld_fill( sf_sd, slf_i, cn_dir, 'sbc_wave_init', 'Wave module ', 'namsbc_wave' ) 
    432          ENDIF 
     471      ENDIF 
     472 
     473      IF( ln_rough .AND. .NOT. cpl_hsig .AND. jp_hsw==0 ) THEN 
     474         jpfld  = jpfld + 1 
     475         jp_hsw = jpfld 
     476      ENDIF 
     477 
     478      ! Read from file only the non-coupled fields  
     479      IF( jpfld > 0 ) THEN 
     480         ALLOCATE( slf_i(jpfld) ) 
     481         IF( jp_usd > 0 )   slf_i(jp_usd) = sn_usd 
     482         IF( jp_vsd > 0 )   slf_i(jp_vsd) = sn_vsd 
     483         IF( jp_hsw > 0 )   slf_i(jp_hsw) = sn_hsw 
     484         IF( jp_wmp > 0 )   slf_i(jp_wmp) = sn_wmp 
     485         IF( jp_wfr > 0 )   slf_i(jp_wfr) = sn_wfr 
     486         ALLOCATE( sf_sd(jpfld), STAT=ierror )   !* allocate and fill sf_sd with stokes drift 
     487         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_sd structure' ) 
     488         ! 
     489         DO ifpr= 1, jpfld 
     490            ALLOCATE( sf_sd(ifpr)%fnow(jpi,jpj,1) ) 
     491            IF( slf_i(ifpr)%ln_tint )   ALLOCATE( sf_sd(ifpr)%fdta(jpi,jpj,1,2) ) 
     492         END DO 
     493         ! 
     494         CALL fld_fill( sf_sd, slf_i, cn_dir, 'sbc_wave_init', 'read wave input', 'namsbc_wave' ) 
     495      ENDIF 
     496 
     497      IF( ln_sdw ) THEN 
    433498         ALLOCATE( usd  (jpi,jpj,jpk), vsd  (jpi,jpj,jpk), wsd(jpi,jpj,jpk) ) 
    434          ALLOCATE( hsw  (jpi,jpj)    , wmp  (jpi,jpj)     ) 
     499         ALLOCATE( wmp  (jpi,jpj)  ) 
    435500         ALLOCATE( wfreq (jpi,jpj) ) 
    436501         ALLOCATE( ut0sd(jpi,jpj)    , vt0sd(jpi,jpj)     ) 
     
    446511                                   ALLOCATE( sf_wn(1)%fnow(jpi,jpj,1)   ) 
    447512            IF( sn_wnum%ln_tint )  ALLOCATE( sf_wn(1)%fdta(jpi,jpj,1,2) ) 
    448             CALL fld_fill( sf_wn, (/ sn_wnum /), cn_dir, 'sbc_wave', 'Wave module', 'namsbc_wave' ) 
     513            CALL fld_fill( sf_wn, (/ sn_wnum /), cn_dir, 'sbc_wave', 'read wave input', 'namsbc_wave' ) 
    449514         ENDIF 
    450515         ALLOCATE( wnum(jpi,jpj) ) 
     516      ENDIF 
     517 
     518      IF( ln_sdw .OR. ln_rough ) THEN 
     519         ALLOCATE( hsw  (jpi,jpj) ) 
    451520      ENDIF 
    452521      ! 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/ZDF/zdf_oce.F90

    r7471 r7905  
    1010   USE in_out_manager ! I/O manager 
    1111   USE lib_mpp        ! MPP library 
     12   USE sbc_oce, ONLY : ln_zdfqiao 
    1213 
    1314   IMPLICIT NONE 
     
    3536   INTEGER , PUBLIC ::   nn_npc      !: non penetrative convective scheme call  frequency 
    3637   INTEGER , PUBLIC ::   nn_npcp     !: non penetrative convective scheme print frequency 
    37    LOGICAL , PUBLIC ::   ln_zdfqiao  !: Enhanced wave vertical mixing Qiao(2010) formulation flag 
    3838 
    3939 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfgls.F90

    r7853 r7905  
    2424   USE phycst         ! physical constants 
    2525   USE zdfmxl         ! mixed layer 
    26    USE sbcwave, ONLY: hsw,rn_crban 
     26   USE sbcwave 
    2727   !  
    2828   USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
     
    6262   INTEGER  ::   nn_stab_func      ! stability functions G88, KC or Canuto (=0/1/2) 
    6363   INTEGER  ::   nn_clos           ! closure 0/1/2/3 MY82/k-eps/k-w/gen 
    64    INTEGER  ::   nn_wmix           ! type of wave breaking mixing 
    65    INTEGER, PUBLIC, PARAMETER ::   jp_craigbanner = 0   ! Craig and Banner formulation (original NEMO formulation - 
    66                                                         !    direct conversion of mechanical to turbulent energy) 
    67    INTEGER, PUBLIC, PARAMETER ::   jp_janssen     = 1   ! Janssen formulation - no assumption on direct energy conversion  
    6864   REAL(wp) ::   rn_clim_galp      ! Holt 2008 value for k-eps: 0.267 
    6965   REAL(wp) ::   rn_epsmin         ! minimum value of dissipation (m2/s3) 
     
    181177            rsbc_tke3(:,:) = rdt * rn_crban(:,:)                                           ! Neumann + Wave breaking 
    182178            rsbc_psi1(:,:) = rc0**rpp * rsbc_tke1(:,:)**rmm * rl_sf**rnn                   ! Dirichlet + Wave breaking 
    183          ELSE 
     179         ELSE IF( nn_wmix==jp_craigbanner ) THEN 
    184180            rsbc_tke1(:,:) = -3._wp/2._wp*rn_crban(:,:)*ra_sf*rl_sf 
    185181            rsbc_tke3(:,:) = rdt * rn_crban(:,:) / rl_sf 
     
    359355               z_elem_c(:,:,2) = 0._wp 
    360356               z_elem_b(:,:,2) = 1._wp 
    361             ELSE 
     357            ELSE IF( nn_wmix==jp_craigbanner ) THEN 
    362358               en(:,:,1) = rc02r * ustars2(:,:) * (1._wp + rsbc_tke1(:,:))**(2._wp/3._wp) 
    363359               en(:,:,1) = MAX(en(:,:,1), rn_emin)  
     
    405401               zflxs(:,:) = rsbc_tke3(:,:) * ustars2(:,:)**1.5_wp * ((zhsro(:,:)+fsdept(:,:,1) ) / zhsro(:,:) )**(1.5*ra_sf) 
    406402               en(:,:,2) = en(:,:,2) + zflxs(:,:) / fse3w(:,:,2) 
    407             ELSE 
     403            ELSE IF( nn_wmix==jp_craigbanner ) THEN 
    408404               ! Dirichlet conditions at k=1 
    409405               en(:,:,1)       = rc02r * ustars2(:,:) * (1._wp + rsbc_tke1(:,:))**(2._wp/3._wp) 
     
    652648               !  
    653649               ! 
    654             ELSE 
     650            ELSE IF( nn_wmix==jp_craigbanner ) THEN 
    655651               ! Surface value 
    656652               zdep(:,:)       = zhsro(:,:) * rl_sf ! Cosmetic 
     
    708704               psi(:,:,2) = psi(:,:,2) + zflxs(:,:) / fse3w(:,:,2) 
    709705               ! 
    710             ELSE 
     706            ELSE IF( nn_wmix==jp_craigbanner ) THEN 
    711707               ! Surface value: Dirichlet 
    712708               zdep(:,:)       = zhsro(:,:) * rl_sf 
     
    10471043         &            rn_crban_default, rn_charn, rn_frac_hs,& 
    10481044         &            nn_bc_surf, nn_bc_bot, nn_z0_met,      & 
    1049          &            nn_stab_func, nn_clos, nn_wmix 
     1045         &            nn_stab_func, nn_clos 
    10501046      !!---------------------------------------------------------- 
    10511047      ! 
     
    10901086      IF( nn_bc_surf < 0 .OR. nn_bc_surf > 1 ) CALL ctl_stop( 'zdf_gls_init: bad flag: nn_bc_surf is 0 or 1' )  
    10911087      IF( nn_z0_met < 0 .OR. nn_z0_met > 3 ) CALL ctl_stop( 'zdf_gls_init: bad flag: nn_z0_met is 0, 1, 2 or 3' )  
    1092       IF( nn_z0_met == 3 .AND. .NOT.ln_sdw ) CALL ctl_stop( 'zdf_gls_init: nn_z0_met=3 requires ln_sdw=T' )  
     1088      IF( nn_z0_met == 3 .AND. .NOT.ln_rough ) CALL ctl_stop( 'zdf_gls_init: nn_z0_met=3 requires ln_rough=T' )  
     1089      IF( nn_z0_met .NE. 3 .AND. ln_rough ) THEN 
     1090         CALL ctl_warn('W A R N I N G:  ln_rough=.TRUE. but nn_z0_met is not 3 - resetting nn_z0_met to 3') 
     1091         nn_z0_met = 3 
     1092      ENDIF 
    10931093      IF( nn_stab_func  < 0 .OR. nn_stab_func  > 3 ) CALL ctl_stop( 'zdf_gls_init: bad flag: nn_stab_func is 0, 1, 2 and 3' )  
    10941094      IF( nn_clos       < 0 .OR. nn_clos       > 3 ) CALL ctl_stop( 'zdf_gls_init: bad flag: nn_clos is 0, 1, 2 or 3' ) 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfini.F90

    r7471 r7905  
    5454      !! 
    5555      NAMELIST/namzdf/ rn_avm0, rn_avt0, nn_avb, nn_havtb, ln_zdfexp, nn_zdfexp,  &  
    56          &        ln_zdfevd, nn_evdm, rn_avevd, ln_zdfnpc, nn_npc, nn_npcp,       &  
    57          &        ln_zdfqiao  
     56         &        ln_zdfevd, nn_evdm, rn_avevd, ln_zdfnpc, nn_npc, nn_npcp 
    5857      !!---------------------------------------------------------------------- 
    5958 
     
    8483         WRITE(numout,*) '      npc call  frequency                 nn_npc    = ', nn_npc 
    8584         WRITE(numout,*) '      npc print frequency                 nn_npcp   = ', nn_npcp 
    86          WRITE(numout,*) '      Qiao formulation flag               ln_zdfqiao=', ln_zdfqiao 
    8785      ENDIF 
    8886 
Note: See TracChangeset for help on using the changeset viewer.