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/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90 – NEMO

Ignore:
Timestamp:
2017-11-20T17:25:03+01:00 (7 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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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.