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 8755 for branches – NEMO

Changeset 8755 for branches


Ignore:
Timestamp:
2017-11-20T17:25:03+01:00 (6 years ago)
Author:
jcastill
Message:

Further changes for ticket #1980
Receive the ocean wind stress components from a wave model, both in forced and coupled mode

Location:
branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/CONFIG/SHARED/namelist_ref

    r8750 r8755  
    221221                           !   = 2 Phillips as (1) but using the wave frequency from a wave model 
    222222   ln_tauoc    = .false.   !  Activate ocean stress modified by external wave induced stress (T => ln_wave=.true. & fill namsbc_wave) 
     223   ln_tauw     = .false.   !  Activate ocean stress components from wave model 
    223224   ln_stcor    = .false.   !  Activate Stokes Coriolis term (T => ln_wave=.true. & ln_sdw=.true. & fill namsbc_wave) 
    224225   nn_lsm      = 0         !  =0 land/sea mask for input fields is not applied (keep empty land/sea mask filename field) , 
     
    304305   sn_rcv_wfreq  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   '' 
    305306   sn_rcv_wnum   =       'none'                 ,    'no'    ,     ''      ,         ''          ,   '' 
    306    sn_rcv_wstrf  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   '' 
     307   sn_rcv_tauoc  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   '' 
     308   sn_rcv_tauw   =       'none'                 ,    'no'    ,     ''      ,         ''          ,   '' 
    307309   sn_rcv_wdrag  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   '' 
    308310! 
     
    464466   sn_wnum     =  'sdw_wave' ,        1          , 'wave_num'   ,     .true.   , .false. , 'daily'   ,  ''      , ''       , '' 
    465467   sn_tauoc    =  'sdw_wave' ,        1          , 'wave_stress',     .true.   , .false. , 'daily'   ,  ''      , ''       , '' 
     468   sn_tauwx    =  'sdw_wave' ,        1          , 'wave_stress',     .true.   , .false. , 'daily'   ,  ''      , ''       , '' 
     469   sn_tauwy    =  'sdw_wave' ,        1          , 'wave_stress',     .true.   , .false. , 'daily'   ,  ''      , ''       , '' 
    466470! 
    467471   cn_dir  = './'  !  root directory for the location of drag coefficient files 
  • branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/cpl_oasis3.F90

    r8749 r8755  
    6666   INTEGER                    ::   nsnd         ! total number of fields sent  
    6767   INTEGER                    ::   ncplmodel    ! Maximum number of models to/from which NEMO is potentialy sending/receiving data 
    68    INTEGER, PUBLIC, PARAMETER ::   nmaxfld=55   ! Maximum number of coupling fields 
     68   INTEGER, PUBLIC, PARAMETER ::   nmaxfld=60   ! Maximum number of coupling fields 
    6969   INTEGER, PUBLIC, PARAMETER ::   nmaxcat=5    ! Maximum number of coupling fields 
    7070   INTEGER, PUBLIC, PARAMETER ::   nmaxcpl=5    ! Maximum number of coupling fields 
  • branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r8750 r8755  
    6565   LOGICAL , PUBLIC ::   ln_sdw         !: true if 3d stokes drift from wave model 
    6666   LOGICAL , PUBLIC ::   ln_tauoc       !: true if normalized stress from wave is used 
     67   LOGICAL , PUBLIC ::   ln_tauw        !: true if ocean stress components from wave is used 
    6768   LOGICAL , PUBLIC ::   ln_stcor       !: true if Stokes-Coriolis term is used 
    6869   ! 
  • branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r8750 r8755  
    113113   INTEGER, PARAMETER ::   jpr_wper   = 48   ! Mean wave period 
    114114   INTEGER, PARAMETER ::   jpr_wnum   = 49   ! Mean wavenumber 
    115    INTEGER, PARAMETER ::   jpr_wstrf  = 50   ! Stress fraction adsorbed by waves 
     115   INTEGER, PARAMETER ::   jpr_tauoc  = 50   ! Stress fraction adsorbed by waves 
    116116   INTEGER, PARAMETER ::   jpr_wdrag  = 51   ! Neutral surface drag coefficient 
    117117   INTEGER, PARAMETER ::   jpr_isf    = 52 
    118118   INTEGER, PARAMETER ::   jpr_icb    = 53 
    119119   INTEGER, PARAMETER ::   jpr_wfreq  = 54   ! Wave peak frequency 
    120  
    121    INTEGER, PARAMETER ::   jprcv      = 54   ! total number of fields received   
     120   INTEGER, PARAMETER ::   jpr_tauwx  = 55   ! x component of the ocean stress from waves 
     121   INTEGER, PARAMETER ::   jpr_tauwy  = 56   ! y component of the ocean stress from waves 
     122 
     123   INTEGER, PARAMETER ::   jprcv      = 56   ! total number of fields received   
    122124 
    123125   INTEGER, PARAMETER ::   jps_fice   =  1   ! ice fraction sent to the atmosphere 
     
    166168   TYPE(FLD_C) ::   sn_snd_temp, sn_snd_alb, sn_snd_thick, sn_snd_crt, sn_snd_co2                         
    167169   !                                   ! Received from the atmosphere 
    168    TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_dqnsdt, sn_rcv_qsr, sn_rcv_qns, sn_rcv_emp, sn_rcv_rnf 
     170   TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_tauw, sn_rcv_dqnsdt, sn_rcv_qsr, & 
     171                                                            sn_rcv_qns, sn_rcv_emp, sn_rcv_rnf 
    169172   TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2, sn_rcv_mslp, sn_rcv_icb, sn_rcv_isf                               
    170173   ! Send to waves  
    171174   TYPE(FLD_C) ::   sn_snd_ifrac, sn_snd_crtw, sn_snd_wlev  
    172175   ! Received from waves  
    173    TYPE(FLD_C) ::   sn_rcv_hsig,sn_rcv_phioc,sn_rcv_sdrfx,sn_rcv_sdrfy,sn_rcv_wper,sn_rcv_wnum,sn_rcv_wstrf,sn_rcv_wdrag, & 
     176   TYPE(FLD_C) ::   sn_rcv_hsig,sn_rcv_phioc,sn_rcv_sdrfx,sn_rcv_sdrfy,sn_rcv_wper,sn_rcv_wnum,sn_rcv_tauoc,sn_rcv_wdrag, & 
    174177                    sn_rcv_wfreq 
    175178   !                                   ! Other namelist parameters 
     
    244247         &                  sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau   , sn_rcv_dqnsdt, sn_rcv_qsr,      &  
    245248         &                  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_wstrf ,   & 
     249         &                  sn_rcv_sdrfx, sn_rcv_sdrfy, sn_rcv_wper  , sn_rcv_wnum  , sn_rcv_tauoc ,   & 
    247250         &                  sn_rcv_wdrag, sn_rcv_qns  , sn_rcv_emp   , sn_rcv_rnf   , sn_rcv_cal   ,   & 
    248251         &                  sn_rcv_iceflx,sn_rcv_co2  , nn_cplmodel  , ln_usecplmask, sn_rcv_mslp  ,   & 
    249          &                  sn_rcv_icb , sn_rcv_isf   , sn_rcv_wfreq 
     252         &                  sn_rcv_icb , sn_rcv_isf   , sn_rcv_wfreq , sn_rcv_tauw 
    250253 
    251254      !!--------------------------------------------------------------------- 
     
    298301         WRITE(numout,*)'      Mean wave number                = ', TRIM(sn_rcv_wnum%cldes  ), ' (', TRIM(sn_rcv_wnum%clcat  ), ')'  
    299302         WRITE(numout,*)'      Wave peak frequency             = ', TRIM(sn_rcv_wfreq%cldes ), ' (', TRIM(sn_rcv_wfreq%clcat ), ')' 
    300          WRITE(numout,*)'      Stress frac adsorbed by waves   = ', TRIM(sn_rcv_wstrf%cldes ), ' (', TRIM(sn_rcv_wstrf%clcat ), ')'  
     303         WRITE(numout,*)'      Stress frac adsorbed by waves   = ', TRIM(sn_rcv_tauoc%cldes ), ' (', TRIM(sn_rcv_tauoc%clcat ), ')'  
     304         WRITE(numout,*)'      Stress components by waves      = ', TRIM(sn_rcv_tauw%cldes  ), ' (', TRIM(sn_rcv_tauw%clcat  ), ')' 
    301305         WRITE(numout,*)'      Neutral surf drag coefficient   = ', TRIM(sn_rcv_wdrag%cldes ), ' (', TRIM(sn_rcv_wdrag%clcat ), ')'  
    302306         WRITE(numout,*)'  sent fields (multiple ice categories)' 
     
    591595         cpl_wnum = .TRUE. 
    592596      ENDIF 
    593       srcv(jpr_wstrf)%clname = 'O_WStrf'     ! stress fraction adsorbed by the wave 
    594       IF( TRIM(sn_rcv_wstrf%cldes ) == 'coupled' )  THEN 
    595          srcv(jpr_wstrf)%laction = .TRUE. 
    596          cpl_wstrf = .TRUE. 
     597      srcv(jpr_tauoc)%clname = 'O_TauOce'    ! stress fraction adsorbed by the wave 
     598      IF( TRIM(sn_rcv_tauoc%cldes ) == 'coupled' )  THEN 
     599         srcv(jpr_tauoc)%laction = .TRUE. 
     600         cpl_tauoc = .TRUE. 
     601      ENDIF 
     602      srcv(jpr_tauwx)%clname = 'O_Tauwx'      ! ocean stress from wave in the x direction 
     603      srcv(jpr_tauwy)%clname = 'O_Tauwy'      ! ocean stress from wave in the y direction 
     604      IF( TRIM(sn_rcv_tauw%cldes ) == 'coupled' )  THEN 
     605         srcv(jpr_tauwx)%laction = .TRUE. 
     606         srcv(jpr_tauwy)%laction = .TRUE. 
     607         cpl_tauw = .TRUE. 
    597608      ENDIF 
    598609      srcv(jpr_wdrag)%clname = 'O_WDrag'     ! neutral surface drag coefficient 
     
    602613      ENDIF 
    603614      !  
     615      IF( srcv(jpr_tauoc)%laction .AND. srcv(jpr_tauwx)%laction .AND. srcv(jpr_tauwy)%laction ) & 
     616            CALL ctl_stop( 'More than one method for modifying the ocean stress has been selected ', & 
     617                                     '(sn_rcv_tauoc=coupled and sn_rcv_tauw=coupled)' ) 
     618      ! 
    604619      !                                                      ! ------------------------------- ! 
    605620      !                                                      !   OPA-SAS coupling - rcv by opa !    
     
    11931208      !                                                      ! Stress adsorbed by waves  ! 
    11941209      !                                                      ! ========================= !  
    1195       IF( srcv(jpr_wstrf)%laction .AND. ln_tauoc ) tauoc_wave(:,:) = frcv(jpr_wstrf)%z3(:,:,1) 
     1210      IF( srcv(jpr_tauoc)%laction .AND. ln_tauoc ) tauoc_wave(:,:) = frcv(jpr_tauoc)%z3(:,:,1) 
     1211 
     1212      !                                                      ! ========================= !   
     1213      !                                                      ! Stress component by waves !  
     1214      !                                                      ! ========================= !   
     1215      IF( srcv(jpr_tauwx)%laction .AND. srcv(jpr_tauwy)%laction .AND. ln_tauw ) THEN 
     1216         tauw_x(:,:) = frcv(jpr_tauwx)%z3(:,:,1) 
     1217         tauw_y(:,:) = frcv(jpr_tauwy)%z3(:,:,1) 
     1218      ENDIF 
    11961219 
    11971220      !                                                      ! ========================= !  
  • branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90

    r8749 r8755  
    2929   PUBLIC sbc_flx       ! routine called by step.F90 
    3030 
    31    INTEGER , PARAMETER ::   jpfld   = 5   ! maximum number of files to read  
    32    INTEGER , PARAMETER ::   jp_utau = 1   ! index of wind stress (i-component) file 
    33    INTEGER , PARAMETER ::   jp_vtau = 2   ! index of wind stress (j-component) file 
    34    INTEGER , PARAMETER ::   jp_qtot = 3   ! index of total (non solar+solar) heat file 
    35    INTEGER , PARAMETER ::   jp_qsr  = 4   ! index of solar heat file 
    36    INTEGER , PARAMETER ::   jp_emp  = 5   ! index of evaporation-precipation file 
     31   INTEGER             ::   jpfld         ! maximum number of files to read  
     32   INTEGER             ::   jp_utau       ! index of wind stress (i-component) file 
     33   INTEGER             ::   jp_vtau       ! index of wind stress (j-component) file 
     34   INTEGER             ::   jp_qtot       ! index of total (non solar+solar) heat file 
     35   INTEGER             ::   jp_qsr        ! index of solar heat file 
     36   INTEGER             ::   jp_emp        ! index of evaporation-precipation file 
    3737   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read) 
    3838 
     
    8282      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient 
    8383      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables 
     84      LOGICAL  ::   ln_readtau            ! Is it necessary to read utau, vtau from file? 
    8485      !! 
    8586      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files 
     
    9091      ! 
    9192      IF( kt == nit000 ) THEN                ! First call kt=nit000   
     93         ln_readtau = .NOT. (ln_wave .AND. ln_tauw ) 
     94 
     95         ! prepare the index of the fields that have to be read 
     96         jpfld = 0 
     97         IF( ln_readtau ) THEN 
     98            jp_utau = jpfld+1 
     99            jp_vtau = jpfld+2 
     100            jpfld = jpfld+2 
     101         ELSE 
     102            jp_utau = 0   ;  jp_vtau = 0 
     103         ENDIF 
     104         jp_qtot = jpfld+1 
     105         jp_qsr = jpfld+2 
     106         jp_emp = jpfld+3 
     107         jpfld = jpfld+3 
     108 
    92109         ! set file information 
    93110         REWIND( numnam_ref )              ! Namelist namsbc_flx in reference namelist : Files for fluxes 
     
    105122         ! 
    106123         !                                         ! store namelist information in an array 
    107          slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau 
     124         IF( ln_readtau ) THEN 
     125            slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau 
     126         ENDIF 
    108127         slf_i(jp_qtot) = sn_qtot   ;   slf_i(jp_qsr ) = sn_qsr  
    109128         slf_i(jp_emp ) = sn_emp 
     
    133152         DO jj = 1, jpj                                           ! set the ocean fluxes from read fields 
    134153            DO ji = 1, jpi 
    135                utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1) 
    136                vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1) 
     154               IF( ln_readtau ) THEN 
     155                  utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1) 
     156                  vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1) 
     157               ENDIF 
    137158               qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj,1) - sf(jp_qsr)%fnow(ji,jj,1) 
    138159               emp (ji,jj) = sf(jp_emp )%fnow(ji,jj,1) 
     
    143164         ! 
    144165         !                                                        ! module of wind stress and wind speed at T-point 
    145          zcoef = 1. / ( zrhoa * zcdrag ) 
    146          DO jj = 2, jpjm1 
    147             DO ji = fs_2, fs_jpim1   ! vect. opt. 
    148                ztx = utau(ji-1,jj  ) + utau(ji,jj)  
    149                zty = vtau(ji  ,jj-1) + vtau(ji,jj)  
    150                zmod = 0.5 * SQRT( ztx * ztx + zty * zty ) 
    151                taum(ji,jj) = zmod 
    152                wndm(ji,jj) = SQRT( zmod * zcoef ) 
     166         IF( ln_readtau ) THEN 
     167            zcoef = 1. / ( zrhoa * zcdrag ) 
     168            DO jj = 2, jpjm1 
     169               DO ji = fs_2, fs_jpim1   ! vect. opt. 
     170                  ztx = utau(ji-1,jj  ) + utau(ji,jj)  
     171                  zty = vtau(ji  ,jj-1) + vtau(ji,jj)  
     172                  zmod = 0.5 * SQRT( ztx * ztx + zty * zty ) 
     173                  taum(ji,jj) = zmod 
     174                  wndm(ji,jj) = SQRT( zmod * zcoef ) 
     175               END DO 
    153176            END DO 
    154          END DO 
    155          taum(:,:) = taum(:,:) * tmask(:,:,1) ; wndm(:,:) = wndm(:,:) * tmask(:,:,1) 
    156          CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. ) 
     177            taum(:,:) = taum(:,:) * tmask(:,:,1) ; wndm(:,:) = wndm(:,:) * tmask(:,:,1) 
     178            CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. ) 
     179         ENDIF 
    157180 
    158181         IF( nitend-nit000 <= 100 .AND. lwp ) THEN                ! control print (if less than 100 time-step asked) 
  • branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r8750 r8755  
    9696         &             ln_rnf   , nn_fwb   , ln_ssr   , ln_isf    , ln_apr_dyn ,     & 
    9797         &             ln_wave  , ln_cdgw  , ln_sdw   , ln_tauoc  , ln_stcor   ,     & 
    98          &             nn_lsm, nn_sdrift 
     98         &             ln_tauw  , nn_lsm, nn_sdrift 
    9999      !!---------------------------------------------------------------------- 
    100100      ! 
     
    159159         WRITE(numout,*) '                  vertical parametrization          nn_sdrift     = ', nn_sdrift 
    160160         WRITE(numout,*) '               wave modified ocean stress           ln_tauoc      = ', ln_tauoc 
     161         WRITE(numout,*) '               wave modified ocean stress component ln_tauw       = ', ln_tauw 
    161162         WRITE(numout,*) '               Stokes coriolis term                 ln_stcor      = ', ln_stcor 
    162163         WRITE(numout,*) '               neutral drag coefficient (CORE, MFS) ln_cdgw       = ', ln_cdgw 
     
    167168            CALL ctl_stop( 'The chosen nn_sdrift for Stokes drift vertical velocity must be 0, 1, or 2' ) 
    168169      ENDIF 
     170      IF( ln_tauoc .AND. ln_tauw ) & 
     171         CALL ctl_stop( 'More than one method for modifying the ocean stress has been selected ', & 
     172                                  '(ln_tauoc=.true. and ln_tauw=.true.)' ) 
     173      IF( ln_tauoc ) & 
     174         CALL ctl_warn( 'You are subtracting the wave stress to the ocean (ln_tauoc=.true.)' ) 
     175      IF( ln_tauw ) & 
     176         CALL ctl_warn( 'The wave modified ocean stress components are used (ln_tauw=.true.) ', & 
     177                              'This will override any other specification of the ocean stress' ) 
    169178      ! 
    170179      IF( .NOT.ln_usr ) THEN     ! the model calendar needs some specificities (except in user defined case) 
     
    416425         IF( ll_opa    )       CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
    417426      END SELECT 
    418       IF ( ln_wave .AND. ln_tauoc) THEN                                 ! Wave stress subctracted 
    419             utau(:,:) = utau(:,:)*tauoc_wave(:,:) 
    420             vtau(:,:) = vtau(:,:)*tauoc_wave(:,:) 
    421             taum(:,:) = taum(:,:)*tauoc_wave(:,:) 
    422       ! 
    423             SELECT CASE( nsbc ) 
    424             CASE(  0,1,2,3,5,-1 )  ; 
    425                 IF(lwp .AND. kt == nit000 ) WRITE(numout,*) 'WARNING: You are subtracting the wave stress to the ocean. & 
    426                         & If not requested select ln_tauoc=.false' 
    427             END SELECT 
    428       ! 
    429       END IF 
     427      ! 
    430428      IF( ln_mixcpl )          CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
    431  
     429      ! 
     430      IF ( ln_wave .AND. (ln_tauoc .OR. ln_tauw) ) CALL sbc_wstress( )      ! Wind stress provided by waves  
    432431      ! 
    433432      !                                            !==  Misc. Options  ==! 
  • branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r8750 r8755  
    3333 
    3434   PUBLIC   sbc_stokes      ! routine called in sbccpl 
     35   PUBLIC   sbc_wstress     ! routine called in sbcmod  
    3536   PUBLIC   sbc_wave        ! routine called in sbcmod 
    3637   PUBLIC   sbc_wave_init   ! routine called in sbcmod 
     
    4445   LOGICAL, PUBLIC ::   cpl_wfreq  = .FALSE. 
    4546   LOGICAL, PUBLIC ::   cpl_wnum   = .FALSE. 
    46    LOGICAL, PUBLIC ::   cpl_wstrf  = .FALSE. 
     47   LOGICAL, PUBLIC ::   cpl_tauoc  = .FALSE. 
     48   LOGICAL, PUBLIC ::   cpl_tauw   = .FALSE. 
    4749   LOGICAL, PUBLIC ::   cpl_wdrag  = .FALSE. 
    4850 
     
    5860   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_wn      ! structure of input fields (file informations, fields read) wave number for Qiao 
    5961   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tauoc   ! structure of input fields (file informations, fields read) normalized wave stress into the ocean 
     62   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tauw    ! structure of input fields (file informations, fields read) ocean stress components from wave model 
     63 
    6064   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   cdn_wave            !: 
    6165   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   hsw, wmp, wnum      !:  
    6266   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   wfreq               !:  
    6367   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauoc_wave          !:   
     68   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauw_x, tauw_y      !:   
    6469   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tsd2d               !:  
    6570   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   div_sd              !: barotropic stokes drift divergence 
     
    225230 
    226231 
     232   SUBROUTINE sbc_wstress( ) 
     233      !!--------------------------------------------------------------------- 
     234      !!                     ***  ROUTINE sbc_wstress  *** 
     235      !! 
     236      !! ** Purpose :   Updates the ocean momentum modified by waves 
     237      !! 
     238      !! ** Method  : - Calculate u,v components of stress depending on stress 
     239      !!                model  
     240      !!              - Calculate the stress module 
     241      !!              - The wind module is not modified by waves  
     242      !! ** action   
     243      !!--------------------------------------------------------------------- 
     244      INTEGER  ::   jj, ji   ! dummy loop argument 
     245      ! 
     246      IF( ln_tauoc ) THEN 
     247         utau(:,:) = utau(:,:)*tauoc_wave(:,:) 
     248         vtau(:,:) = vtau(:,:)*tauoc_wave(:,:) 
     249         taum(:,:) = taum(:,:)*tauoc_wave(:,:) 
     250      ENDIF 
     251      ! 
     252      IF( ln_tauw ) THEN 
     253         DO jj = 1, jpjm1 
     254            DO ji = 1, jpim1 
     255               ! Stress components at u- & v-points 
     256               utau(ji,jj) = 0.5_wp * ( tauw_x(ji,jj) + tauw_x(ji+1,jj) ) 
     257               vtau(ji,jj) = 0.5_wp * ( tauw_y(ji,jj) + tauw_y(ji,jj+1) ) 
     258               ! 
     259               ! Stress module at t points 
     260               taum(ji,jj) = SQRT( tauw_x(ji,jj)*tauw_x(ji,jj) + tauw_y(ji,jj)*tauw_y(ji,jj) ) 
     261            END DO 
     262         END DO 
     263 
     264      ENDIF 
     265      ! 
     266   END SUBROUTINE sbc_wstress 
     267 
     268 
    227269   SUBROUTINE sbc_wave( kt ) 
    228270      !!--------------------------------------------------------------------- 
     
    247289      ENDIF 
    248290 
    249       IF( ln_tauoc .AND. .NOT. cpl_wstrf ) THEN    !==  Wave induced stress  ==! 
     291      IF( ln_tauoc .AND. .NOT. cpl_tauoc ) THEN    !==  Wave induced stress  ==! 
    250292         CALL fld_read( kt, nn_fsbc, sf_tauoc )          ! read wave norm stress from external forcing 
    251293         tauoc_wave(:,:) = sf_tauoc(1)%fnow(:,:,1) 
     294      ENDIF 
     295 
     296      IF( ln_tauw .AND. .NOT. cpl_tauw ) THEN      !==  Wave induced stress  ==! 
     297         CALL fld_read( kt, nn_fsbc, sf_tauw )           ! read ocean stress components from external forcing (T grid) 
     298         tauw_x(:,:) = sf_tauw(1)%fnow(:,:,1) 
     299         tauw_y(:,:) = sf_tauw(2)%fnow(:,:,1) 
    252300      ENDIF 
    253301 
     
    300348      !! 
    301349      CHARACTER(len=100)     ::  cn_dir                          ! Root directory for location of drag coefficient files 
    302       TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   slf_i     ! array of namelist informations on the fields to read 
     350      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   slf_i, slf_j     ! array of namelist informations on the fields to read 
    303351      TYPE(FLD_N)            ::  sn_cdg, sn_usd, sn_vsd,  & 
    304                              &   sn_hsw, sn_wmp, sn_wfr, sn_wnum, sn_tauoc      ! informations about the fields to be read 
    305       ! 
    306       NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wfr, sn_wnum, sn_tauoc 
     352                             &   sn_hsw, sn_wmp, sn_wfr, sn_wnum, & 
     353                             &   sn_tauoc, sn_tauwx, sn_tauwy      ! informations about the fields to be read 
     354      ! 
     355      NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wfr, & 
     356                             sn_wnum, sn_tauoc, sn_tauwx, sn_tauwy 
    307357      !!--------------------------------------------------------------------- 
    308358      ! 
     
    329379 
    330380      IF( ln_tauoc ) THEN 
    331          IF( .NOT. cpl_wstrf ) THEN 
     381         IF( .NOT. cpl_tauoc ) THEN 
    332382            ALLOCATE( sf_tauoc(1), STAT=ierror )           !* allocate and fill sf_wave with sn_tauoc 
    333383            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_wave structure' ) 
     
    338388         ENDIF 
    339389         ALLOCATE( tauoc_wave(jpi,jpj) ) 
     390      ENDIF 
     391 
     392      IF( ln_tauw ) THEN 
     393         IF( .NOT. cpl_tauw ) THEN 
     394            ALLOCATE( sf_tauw(2), STAT=ierror )           !* allocate and fill sf_wave with sn_tauwx/y 
     395            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_tauw structure' ) 
     396            ! 
     397            ALLOCATE( slf_j(2) ) 
     398            slf_j(1) = sn_tauwx 
     399            slf_j(2) = sn_tauwy 
     400                                    ALLOCATE( sf_tauw(1)%fnow(jpi,jpj,1)   ) 
     401                                    ALLOCATE( sf_tauw(2)%fnow(jpi,jpj,1)   ) 
     402            IF( slf_j(1)%ln_tint )  ALLOCATE( sf_tauw(1)%fdta(jpi,jpj,1,2) ) 
     403            IF( slf_j(2)%ln_tint )  ALLOCATE( sf_tauw(2)%fdta(jpi,jpj,1,2) ) 
     404            CALL fld_fill( sf_tauw, (/ slf_j /), cn_dir, 'sbc_wave_init', 'read wave input', 'namsbc_wave' ) 
     405         ENDIF 
     406         ALLOCATE( tauw_x(jpi,jpj) ) 
     407         ALLOCATE( tauw_y(jpi,jpj) ) 
    340408      ENDIF 
    341409 
Note: See TracChangeset for help on using the changeset viewer.