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

Changeset 8756 for branches


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

Changes for receiving the ocean wind stress components from a wave model, both in forced and coupled mode
WARNING: this might not work properly without merging the branch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/UKMO/AMM15_v3_6_STABLE_package_UKEP

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

Legend:

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

    r8415 r8756  
    393393   sn_rcv_wnum   =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
    394394   sn_rcv_tauoc  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
     395   sn_rcv_tauw   =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
    395396   sn_rcv_wdrag  =       'none'                 ,    'no'    ,     ''      ,         ''          ,   ''  
    396397! 
     
    12951296   ln_stcor    = .false.   !  Activate Stokes Coriolis term 
    12961297   ln_tauoc    = .false.   !  Activate ocean stress modified by external wave induced stress 
     1298   ln_tauw     = .false.   !  Activate ocean stress components from wave model 
    12971299   ln_phioc    = .false.   !  Activate wave to ocean energy 
    12981300   ln_rough    = .false.   !  Wave roughness equals the significant wave height 
     
    13121314   sn_wnum     =  'sdw_wave' ,        1          , 'wave_num'   ,     .true.   , .false. , 'daily'   ,  ''      , ''       , ''  
    13131315   sn_tauoc    =  'sdw_wave' ,        1          , 'wave_stress',     .true.   , .false. , 'daily'   ,  ''      , ''       , ''  
     1316   sn_tauwx    =  'sdw_wave' ,        1          , 'wave_stress',     .true.   , .false. , 'daily'   ,  ''      , ''       , ''  
     1317   sn_tauwy    =  'sdw_wave' ,        1          , 'wave_stress',     .true.   , .false. , 'daily'   ,  ''      , ''       , ''  
    13141318   sn_phioc    =  'sdw_wave' ,        1          , 'wave_energy',     .true.   , .false. , 'daily'   ,  ''      , ''       , ''  
    13151319   cn_dir      = './'  !  root directory for the location of wave forcing files 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r7905 r8756  
    6969   LOGICAL , PUBLIC ::   ln_stcor       !: true if Stokes-Coriolis term is used  
    7070   LOGICAL , PUBLIC ::   ln_tauoc       !: true if normalized stress from wave is used  
     71   LOGICAL , PUBLIC ::   ln_tauw        !: true if ocean stress components from wave is used  
    7172   LOGICAL , PUBLIC ::   ln_phioc       !: true if wave energy to ocean is used  
    7273   LOGICAL , PUBLIC ::   ln_rough       !: true if wave roughness equals significant wave height 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r8553 r8756  
    116116   INTEGER, PARAMETER ::   jpr_wdrag  = 51            ! Neutral surface drag coefficient  
    117117   INTEGER, PARAMETER ::   jpr_wfreq  = 52            ! Wave peak frequency  
    118    INTEGER, PARAMETER ::   jprcv      = 52            ! total number of fields received 
     118   INTEGER, PARAMETER ::   jpr_tauwx  = 53            ! x component of the ocean stress from waves 
     119   INTEGER, PARAMETER ::   jpr_tauwy  = 54            ! y component of the ocean stress from waves 
     120   INTEGER, PARAMETER ::   jprcv      = 54            ! total number of fields received 
    119121 
    120122   INTEGER, PARAMETER ::   jps_fice   =  1            ! ice fraction sent to the atmosphere 
     
    169171   ! Received from waves   
    170172   TYPE(FLD_C) ::   sn_rcv_hsig,sn_rcv_phioc,sn_rcv_sdrft,sn_rcv_wper, & 
    171                     sn_rcv_wfreq,sn_rcv_wnum,sn_rcv_tauoc,sn_rcv_wdrag 
     173                    sn_rcv_wfreq,sn_rcv_wnum,sn_rcv_tauoc,sn_rcv_tauw, & 
     174                    sn_rcv_wdrag 
    172175   ! Other namelist parameters                        ! 
    173176   INTEGER     ::   nn_cplmodel            ! Maximum number of models to/from which NEMO is potentialy sending/receiving data 
     
    246249         &                  sn_rcv_sdrft, sn_rcv_wper  , sn_rcv_wnum  , sn_rcv_wfreq, sn_rcv_tauoc,    & 
    247250         &                  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 
     251         &                  sn_rcv_iceflx, sn_rcv_co2   , sn_rcv_mslp , sn_rcv_tauw ,                  & 
     252         &                  nn_cplmodel, ln_usecplmask 
    249253      !!--------------------------------------------------------------------- 
    250254      ! 
     
    295299         WRITE(numout,*)'      Wave peak frequency             = ', TRIM(sn_rcv_wfreq%cldes ), ' (', TRIM(sn_rcv_wfreq%clcat ), ')'   
    296300         WRITE(numout,*)'      Stress frac adsorbed by waves   = ', TRIM(sn_rcv_tauoc%cldes ), ' (', TRIM(sn_rcv_tauoc%clcat ), ')'   
     301         WRITE(numout,*)'      Stress components by waves      = ', TRIM(sn_rcv_tauw%cldes  ), ' (', TRIM(sn_rcv_tauw%clcat  ), ')'   
    297302         WRITE(numout,*)'      Neutral surf drag coefficient   = ', TRIM(sn_rcv_wdrag%cldes ), ' (', TRIM(sn_rcv_wdrag%clcat ), ')' 
    298303         WRITE(numout,*)'  sent fields (multiple ice categories)' 
     
    573578         cpl_tauoc = .TRUE.  
    574579      ENDIF  
     580      srcv(jpr_tauwx)%clname = 'O_Tauwx'      ! ocean stress from wave in the x direction 
     581      srcv(jpr_tauwy)%clname = 'O_Tauwy'      ! ocean stress from wave in the y direction 
     582      IF( TRIM(sn_rcv_tauw%cldes ) == 'coupled' )  THEN  
     583         srcv(jpr_tauwx)%laction = .TRUE.  
     584         srcv(jpr_tauwy)%laction = .TRUE.  
     585         cpl_tauw = .TRUE.  
     586      ENDIF  
    575587      srcv(jpr_wdrag)%clname = 'O_WDrag'     ! neutral surface drag coefficient  
    576588      IF( TRIM(sn_rcv_wdrag%cldes ) == 'coupled' )  THEN  
     
    578590         cpl_wdrag = .TRUE.  
    579591      ENDIF  
     592      ! 
     593      IF( srcv(jpr_tauoc)%laction .AND. srcv(jpr_tauwx)%laction .AND. srcv(jpr_tauwy)%laction ) & 
     594            CALL ctl_stop( 'More than one method for modifying the ocean stress has been selected ', & 
     595                                     '(sn_rcv_tauoc=coupled and sn_rcv_tauw=coupled)' ) 
     596      ! 
    580597      !   
    581598      !                                                      ! ------------------------------- ! 
     
    12051222         WHERE(tauoc_wave <   0.0 ) tauoc_wave = 1.0 
    12061223         WHERE(tauoc_wave > 100.0 ) tauoc_wave = 1.0 
     1224      ENDIF 
     1225      !                                                      ! ========================= !   
     1226      !                                                      ! Stress component by waves !  
     1227      !                                                      ! ========================= !   
     1228      IF( srcv(jpr_tauwx)%laction .AND. srcv(jpr_tauwy)%laction .AND. ln_tauw ) THEN 
     1229         tauw_x(:,:) = frcv(jpr_tauwx)%z3(:,:,1) 
     1230         tauw_y(:,:) = frcv(jpr_tauwy)%z3(:,:,1) 
     1231         ! cap the value of tauoc 
     1232         WHERE(tauw_x < -100.0 ) tauw_x = 0.0 
     1233         WHERE(tauw_x >  100.0 ) tauw_x = 0.0 
     1234         WHERE(tauw_y < -100.0 ) tauw_y = 0.0 
     1235         WHERE(tauw_y >  100.0 ) tauw_y = 0.0 
    12071236      ENDIF 
    12081237       
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90

    r8503 r8756  
    3030   PUBLIC sbc_flx       ! routine called by step.F90 
    3131 
    32    INTEGER , PARAMETER ::   jpfld   = 5   ! maximum number of files to read  
    33    INTEGER , PARAMETER ::   jp_utau = 1   ! index of wind stress (i-component) file 
    34    INTEGER , PARAMETER ::   jp_vtau = 2   ! index of wind stress (j-component) file 
    35    INTEGER , PARAMETER ::   jp_qtot = 3   ! index of total (non solar+solar) heat file 
    36    INTEGER , PARAMETER ::   jp_qsr  = 4   ! index of solar heat file 
    37    INTEGER , PARAMETER ::   jp_emp  = 5   ! index of evaporation-precipation file 
     32   INTEGER             ::   jpfld   = 6   ! maximum number of files to read  
     33   INTEGER             ::   jp_utau       ! index of wind stress (i-component) file 
     34   INTEGER             ::   jp_vtau       ! index of wind stress (j-component) file 
     35   INTEGER             ::   jp_qtot       ! index of total (non solar+solar) heat file 
     36   INTEGER             ::   jp_qsr        ! index of solar heat file 
     37   INTEGER             ::   jp_emp        ! index of evaporation-precipation file 
     38   INTEGER             ::   jp_press      ! index of pressure for UKMO shelf fluxes 
    3839   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read) 
    3940   LOGICAL , PUBLIC    ::   ln_shelf_flx = .FALSE. ! UKMO SHELF specific flux flag 
     
    9293      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files 
    9394      NAMELIST/namsbc_flx/ ln_shelf_flx, ln_rel_wind, rn_wfac     ! Put here to allow merging with another UKMO branch 
     95      LOGICAL  :: ln_readtau                                      ! Is it necessary to read tau from file? 
    9496      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                    ! array of namelist information structures 
    9597      TYPE(FLD_N) ::   sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp  ! informations about the fields to be read 
     
    9799      !!--------------------------------------------------------------------- 
    98100      ! 
     101      ln_readtau = .NOT. (ln_wave .AND. ln_tauw ) 
     102 
     103      ! prepare the index of the fields that have to be read 
     104      jpfld = 0 
     105      IF( ln_readtau ) THEN 
     106         jp_utau = jpfld+1 
     107         jp_vtau = jpfld+2 
     108         jpfld = jpfld+2 
     109      ELSE 
     110         jp_utau = 0   ;  jp_vtau = 0 
     111      ENDIF 
     112      jp_qtot = jpfld+1 
     113      jp_qsr = jpfld+2 
     114      jp_emp = jpfld+3 
     115      jp_press = jpfld+4 
     116      jpfld = jpfld+4 
     117 
    99118      IF( kt == nit000 ) THEN                ! First call kt=nit000   
    100119         ! set file information 
     
    122141         ! 
    123142         !                                         ! store namelist information in an array 
     143         IF( ln_readtau ) THEN 
    124144         slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau 
     145         ENDIF 
    125146         slf_i(jp_qtot) = sn_qtot   ;   slf_i(jp_qsr ) = sn_qsr  
    126147         slf_i(jp_emp ) = sn_emp 
     
    146167 
    147168         !!UKMO SHELF wind speed relative to surface currents - put here to allow merging with coupling branch 
    148          IF( ln_shelf_flx ) THEN 
     169         IF( ln_shelf_flx .AND. ln_readtau ) THEN 
    149170            CALL wrk_alloc( jpi,jpj, zwnd_i, zwnd_j ) 
    150171 
     
    178199         !                                                        ! add modification due to drag coefficient read from wave forcing 
    179200         !                                                        ! this code is inefficient but put here to allow merging with another UKMO branch 
    180          IF( ln_shelf_flx ) THEN 
     201         IF( ln_shelf_flx .AND. ln_readtau ) THEN 
    181202            IF( ln_cdgw .AND. nn_drag == jp_std ) THEN 
    182203               IF( cpl_wdrag ) THEN  
     
    212233         ! 
    213234         !                                                        ! module of wind stress and wind speed at T-point 
     235         IF( ln_readtau ) THEN 
    214236         zcoef = 1. / ( zrhoa * zcdrag ) 
    215237!CDIR NOVERRCHK 
     
    233255         taum(:,:) = taum(:,:) * tmask(:,:,1) ; wndm(:,:) = wndm(:,:) * tmask(:,:,1) 
    234256         CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. ) 
     257         ENDIF 
    235258 
    236259         IF( nitend-nit000 <= 100 .AND. lwp ) THEN                ! control print (if less than 100 time-step asked) 
     
    248271         ENDIF 
    249272         ! 
    250          IF( ln_shelf_flx ) THEN 
     273         IF( ln_shelf_flx .AND. ln_readtau ) THEN 
    251274            CALL wrk_dealloc( jpi,jpj, zwnd_i, zwnd_j ) 
    252275         ENDIF 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r7906 r8756  
    376376      IF( ln_mixcpl .OR. ln_wavcpl )  CALL sbc_cpl_rcv ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
    377377 
    378       IF ( ln_wave .AND. ln_tauoc) THEN                 ! Wave stress subctracted  
    379             utau(:,:) = utau(:,:)*tauoc_wave(:,:)  
    380             vtau(:,:) = vtau(:,:)*tauoc_wave(:,:)  
    381             taum(:,:) = taum(:,:)*tauoc_wave(:,:)  
    382       !  
    383             SELECT CASE( nsbc )  
    384             CASE(  0,1,2,3,5,-1 )  ;  
    385                 IF(lwp .AND. kt == nit000 ) THEN 
    386                    write(numout,*) 
    387                    WRITE(numout,*) 'WARNING: You are subtracting the wave stress to the ocean. &  
    388                                                       & If not requested select ln_tauoc=.false'  
    389                    write(numout,*) 
    390                 END IF 
    391             END SELECT  
    392       !  
    393       END IF 
     378      IF ( ln_wave .AND. (ln_tauoc .OR. ln_tauw) ) CALL sbc_stress( )   ! Wave stress update  
    394379 
    395380      !                                            !==  Misc. Options  ==! 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r8553 r8756  
    3232 
    3333   PUBLIC   sbc_stokes      ! routine called in sbccpl  
     34   PUBLIC   sbc_stress      ! routine called in sbcmod 
    3435   PUBLIC   sbc_wave        ! routine called in sbcmod  
    3536   PUBLIC   sbc_wave_init   ! routine called in sbcmod 
     
    4344   LOGICAL, PUBLIC ::   cpl_wnum   = .FALSE. 
    4445   LOGICAL, PUBLIC ::   cpl_tauoc  = .FALSE. 
     46   LOGICAL, PUBLIC ::   cpl_tauw   = .FALSE. 
    4547   LOGICAL, PUBLIC ::   cpl_wdrag  = .FALSE. 
    4648 
     
    6163   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::  sf_wn    ! structure of input fields (file informations, fields read) wave number for Qiao 
    6264   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::  sf_tauoc ! structure of input fields (file informations, fields read) normalized wave stress into the ocean 
     65   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::  sf_tauw ! structure of input fields (file informations, fields read) ocean stress components from wave model 
    6366   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::  sf_phioc ! structure of input fields (file informations, fields read) wave to ocean energy  
    6467   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   cdn_wave            !: 
     
    6770   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   rn_crban            !: Craig and Banner constant for surface breaking waves mixing 
    6871   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauoc_wave          !: 
     72   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauw_x              !: 
     73   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauw_y              !: 
    6974   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tsd2d               !: 
    7075   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   div_sd              !: barotropic stokes drift divergence 
     
    232237 
    233238 
     239   SUBROUTINE sbc_stress( ) 
     240      !!--------------------------------------------------------------------- 
     241      !!                     ***  ROUTINE sbc_stress  *** 
     242      !! 
     243      !! ** Purpose :   Updates the ocean momentum modified by waves 
     244      !! 
     245      !! ** Method  : - Calculate u,v components of stress depending on stress 
     246      !!                model  
     247      !!              - Calculate the stress module 
     248      !!              - The wind module is not modified by waves  
     249      !! ** action   
     250      !!--------------------------------------------------------------------- 
     251      INTEGER  ::   jj, ji   ! dummy loop argument 
     252      ! 
     253      IF( ln_tauoc ) THEN 
     254         utau(:,:) = utau(:,:)*tauoc_wave(:,:) 
     255         vtau(:,:) = vtau(:,:)*tauoc_wave(:,:) 
     256         taum(:,:) = taum(:,:)*tauoc_wave(:,:) 
     257      ENDIF 
     258      ! 
     259      IF( ln_tauw ) THEN 
     260         DO jj = 1, jpjm1 
     261            DO ji = 1, jpim1 
     262               ! Stress components at u- & v-points 
     263               utau(ji,jj) = 0.5_wp * ( tauw_x(ji,jj) + tauw_x(ji+1,jj) ) 
     264               vtau(ji,jj) = 0.5_wp * ( tauw_y(ji,jj) + tauw_y(ji,jj+1) ) 
     265               ! 
     266               ! Stress module at t points 
     267               taum(ji,jj) = SQRT( tauw_x(ji,jj)*tauw_x(ji,jj) + tauw_y(ji,jj)*tauw_y(ji,jj) ) 
     268            END DO 
     269         END DO 
     270 
     271      ENDIF 
     272      ! 
     273   END SUBROUTINE sbc_stress 
     274 
     275 
    234276   SUBROUTINE sbc_wave( kt ) 
    235277      !!--------------------------------------------------------------------- 
     
    263305         WHERE( tauoc_wave <   0.0 ) tauoc_wave = 1.0 
    264306         WHERE( tauoc_wave > 100.0 ) tauoc_wave = 1.0 
     307      ENDIF 
     308 
     309      IF( ln_tauw .AND. .NOT. cpl_tauw ) THEN      !==  Wave induced stress  ==! 
     310         CALL fld_read( kt, nn_fsbc, sf_tauw )           ! read ocean stress components from external forcing (T grid) 
     311         tauw_x(:,:) = sf_tauw(1)%fnow(:,:,1) 
     312         WHERE( tauw_x < -100.0 ) tauw_x = 0.0 
     313         WHERE( tauw_x >  100.0 ) tauw_x = 0.0 
     314 
     315         tauw_y(:,:) = sf_tauw(2)%fnow(:,:,1) 
     316         WHERE( tauw_y < -100.0 ) tauw_y = 0.0 
     317         WHERE( tauw_y >  100.0 ) tauw_y = 0.0 
    265318      ENDIF 
    266319 
     
    343396      !! 
    344397      CHARACTER(len=100)     ::  cn_dir                          ! Root directory for location of drag coefficient files 
    345       TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   slf_i     ! array of namelist informations on the fields to read 
     398      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   slf_i, slf_j     ! array of namelist informations on the fields to read 
    346399      TYPE(FLD_N)            ::  sn_cdg, sn_usd, sn_vsd, sn_phioc, & 
    347400                             &   sn_hsw, sn_wmp, sn_wfr, sn_wnum , & 
    348                              &   sn_tauoc      ! informations about the fields to be read 
    349       ! 
    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,                 & 
     401                             &   sn_tauoc, sn_tauwx, sn_tauwy      ! information about the fields to be read 
     402      ! 
     403      NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wfr, sn_wnum, sn_phioc,          & 
     404                             sn_tauoc, sn_tauwx, sn_tauwy,                                                       & 
     405                             ln_cdgw, ln_sdw, ln_stcor, ln_phioc, ln_tauoc, ln_tauw, ln_zdfqiao, ln_rough,       & 
    352406                             nn_sdrift, nn_wmix 
    353407      !!--------------------------------------------------------------------- 
     
    371425         WRITE(numout,*) '      Stokes coriolis term                    ln_stcor    = ', ln_stcor  
    372426         WRITE(numout,*) '      wave modified ocean stress              ln_tauoc    = ', ln_tauoc  
     427         WRITE(numout,*) '      wave modified ocean stress components   ln_tauw     = ', ln_tauw  
    373428         WRITE(numout,*) '      wave to ocean energy                    ln_phioc    = ', ln_phioc 
    374429         WRITE(numout,*) '        vertical mixing parametrization       nn_wmix     = ', nn_wmix  
     
    380435      IF ( ln_wave ) THEN 
    381436         ! Activated wave physics but no wave physics components activated  
    382          IF ( .NOT.(ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor .OR. ln_phioc .OR. ln_rough .OR. ln_zdfqiao) )   THEN   
    383              CALL ctl_warn( 'Ask for wave coupling but ln_cdgw=F, ln_sdw=F, ln_tauoc=F, ln_stcor=F, ln_phioc=F ', & 
    384                                                       'ln_rough=F, ln_zdfqiao=F' )  
    385          ELSEIF (ln_stcor .AND. .NOT. ln_sdw) THEN   
     437         IF ( .NOT.(ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_tauw .OR. ln_stcor .OR. ln_phioc & 
     438                                                                    .OR. ln_rough .OR. ln_zdfqiao) )   THEN   
     439             CALL ctl_warn( 'Ask for wave coupling but ln_cdgw=F, ln_sdw=F, ln_tauoc=F, ln_tauw=F, ln_stcor=F ', & 
     440                                                      'ln_phioc=F, ln_rough=F, ln_zdfqiao=F' )  
     441         ELSE 
     442         IF (ln_stcor .AND. .NOT. ln_sdw) &  
    386443             CALL ctl_stop( 'Stokes-Coriolis term calculated only if activated Stokes Drift ln_sdw=T') 
    387          ENDIF 
    388444         IF ( ln_cdgw .AND. .NOT.(nn_drag==jp_ukmo .OR. nn_drag==jp_std .OR. nn_drag==jp_const .OR. nn_drag==jp_mcore) ) &  
    389445             CALL ctl_stop( 'The chosen nn_drag for momentum calculation must be 0, 1, 2, or 3') 
     
    398454         IF( ln_zdfqiao .AND. .NOT.ln_sdw ) &  
    399455            CALL ctl_stop( 'Qiao vertical mixing can not be used without Stokes drift (ln_sdw)' ) 
     456         IF( ln_tauoc .AND. ln_tauw ) &  
     457            CALL ctl_stop( 'More than one method for modifying the ocean stress has been selected ', & 
     458                                     '(ln_tauoc=.true. and ln_tauw=.true.)' ) 
     459         IF( ln_tauoc ) & 
     460             CALL ctl_warn( 'You are subtracting the wave stress to the ocean (ln_tauoc=.true.)' ) 
     461         IF( ln_tauw ) & 
     462             CALL ctl_warn( 'The wave modified ocean stress components are used (ln_tauw=.true.) ', & 
     463                                  'This will override any other specification of the ocean stress' )  
     464         ENDIF 
    400465      ELSE 
    401          IF ( ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor .OR. ln_phioc .OR. ln_rough .OR. ln_zdfqiao ) &   
     466         IF ( ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_tauw .OR. ln_stcor .OR. ln_phioc .OR. ln_rough .OR. ln_zdfqiao ) &   
    402467            &   CALL ctl_stop( 'Not Activated Wave Module (ln_wave=F) but asked coupling ',    &  
    403468            &                  'with drag coefficient (ln_cdgw =T) '  ,                        &  
     
    405470            &                  'or Stokes-Coriolis term (ln_stcor=T)',                         & 
    406471            &                  'or ocean stress modification due to waves (ln_tauoc=T) ',      &  
     472            &                  'or ocean stress components from waves (ln_tauw=T) ',          &  
    407473            &                  'or wave to ocean energy modification (ln_phioc=T) ',           &  
    408474            &                  'or wave surface roughness (ln_rough=T) ',                      &  
     
    432498         ENDIF 
    433499         ALLOCATE( tauoc_wave(jpi,jpj) ) 
     500      ENDIF 
     501 
     502      IF( ln_tauw ) THEN 
     503         IF( .NOT. cpl_tauw ) THEN 
     504            ALLOCATE( sf_tauw(2), STAT=ierror )           !* allocate and fill sf_wave with sn_tauwx/y 
     505            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_tauw structure' ) 
     506            ! 
     507            ALLOCATE( slf_j(2) ) 
     508            slf_j(1) = sn_tauwx 
     509            slf_j(2) = sn_tauwy 
     510                                    ALLOCATE( sf_tauw(1)%fnow(jpi,jpj,1)   ) 
     511                                    ALLOCATE( sf_tauw(2)%fnow(jpi,jpj,1)   ) 
     512            IF( slf_j(1)%ln_tint )  ALLOCATE( sf_tauw(1)%fdta(jpi,jpj,1,2) ) 
     513            IF( slf_j(2)%ln_tint )  ALLOCATE( sf_tauw(2)%fdta(jpi,jpj,1,2) ) 
     514            CALL fld_fill( sf_tauw, (/ slf_j /), cn_dir, 'sbc_wave_init', 'read wave input', 'namsbc_wave' ) 
     515         ENDIF 
     516         ALLOCATE( tauw_x(jpi,jpj) ) 
     517         ALLOCATE( tauw_y(jpi,jpj) ) 
    434518      ENDIF 
    435519 
Note: See TracChangeset for help on using the changeset viewer.