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

Ignore:
Timestamp:
2017-03-17T15:21:06+01:00 (7 years ago)
Author:
jcastill
Message:

First implementation of the HZG wave focing/coupling branch - only ln_phioc and ln_tauoc in place. This is crashing amm7 runs with Baltic boundary conditions, but not without them.

Location:
branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r7792 r7809  
    6868   LOGICAL , PUBLIC ::   ln_sdw         !: true if 3d stokes drift from wave model 
    6969   LOGICAL , PUBLIC ::   ln_tauoc       !: true if normalized stress from wave is used  
     70   LOGICAL , PUBLIC ::   ln_phioc       !: true if wave energy to ocean is used  
    7071   LOGICAL , PUBLIC ::   ln_stcor       !: true if Stokes-Coriolis term is used  
    7172   ! 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r7797 r7809  
    11951195      !                                                      ! ========================= !   
    11961196      IF( srcv(jpr_tauoc)%laction .AND. ln_tauoc ) tauoc_wave(:,:) = frcv(jpr_tauoc)%z3(:,:,1)  
     1197       
     1198      !                                                      ! ========================= !   
     1199      !                                                      !   Wave to ocean energy    !  
     1200      !                                                      ! ========================= !   
     1201      IF( srcv(jpr_phioc)%laction .AND. ln_phioc ) THEN 
     1202         rn_crban(:,:) = 29.0 * frcv(jpr_phioc)%z3(:,:,1) 
     1203      ENDIF 
    11971204       
    11981205      !  Fields received by SAS when OASIS coupling 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r7792 r7809  
    9090         &             ln_ssr    , nn_isf    , nn_fwb, ln_cdgw    , ln_wave    , ln_sdw   ,   & 
    9191         &             ln_tauoc  , ln_stcor  , nn_lsm, nn_limflx , nn_components, ln_cpl  ,   & 
    92          &             ln_wavcpl , nn_drag 
     92         &             ln_phioc  , ln_wavcpl , nn_drag 
    9393      INTEGER  ::   ios 
    9494      INTEGER  ::   ierr, ierr0, ierr1, ierr2, ierr3, jpm 
     
    136136         WRITE(numout,*) '                 Stokes drift corr. to vert. velocity    ln_sdw      = ', ln_sdw  
    137137         WRITE(numout,*) '                 wave modified ocean stress              ln_tauoc    = ', ln_tauoc  
     138         WRITE(numout,*) '                 wave to ocean energy - wave breaking    ln_phioc    = ', ln_phioc 
    138139         WRITE(numout,*) '                 Stokes coriolis term                    ln_stcor    = ', ln_stcor  
    139140         WRITE(numout,*) '                 neutral drag coefficient                ln_cdgw     = ', ln_cdgw 
     
    224225      IF ( ln_wave ) THEN 
    225226         !Activated wave module but neither drag nor stokes drift activated  
    226          IF ( .NOT.(ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor ) )   THEN   
    227              CALL ctl_warn( 'Ask for wave coupling but ln_cdgw=F, ln_sdw=F, ln_tauoc=F, ln_stcor=F')  
     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')  
    228229         ELSEIF (ln_stcor .AND. .NOT. ln_sdw) THEN   
    229230             CALL ctl_stop( 'Stokes-Coriolis term calculated only if activated Stokes Drift ln_sdw=T') 
    230231         ENDIF 
    231232      ELSE 
    232          IF ( ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor ) &   
     233         IF ( ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor .OR. ln_phioc ) &   
    233234            &   CALL ctl_stop( 'Not Activated Wave Module (ln_wave=F) but asked coupling ',    &  
    234235            &                  'with drag coefficient (ln_cdgw =T) '  ,                        &  
    235236            &                  'or Stokes Drift (ln_sdw=T) ' ,                                 &  
    236237            &                  'or ocean stress modification due to waves (ln_tauoc=T) ',      &  
    237             &                  'or Stokes-Coriolis term (ln_stcori=T)'  ) 
     238            &                  'or wave to ocean energy modification (ln_phioc=T) ',           &  
     239            &                  'or Stokes-Coriolis term (ln_stcor=T)'  ) 
    238240      ENDIF  
    239241      !                          ! Choice of the Surface Boudary Condition (set nsbc) 
  • branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r7797 r7809  
    5656   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::  sf_wn    ! structure of input fields (file informations, fields read) wave number for Qiao 
    5757   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::  sf_tauoc ! structure of input fields (file informations, fields read) normalized wave stress into the ocean 
     58   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::  sf_phioc ! structure of input fields (file informations, fields read) wave to ocean energy  
    5859   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   cdn_wave            !: 
    5960   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   hsw, wmp, wnum      !: 
     61   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   rn_crban            !: Craig and Banner constant for surface breaking waves mixing 
    6062   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tauoc_wave          !: 
    6163   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   tsd2d               !: 
     
    222224      ENDIF 
    223225 
     226      IF( ln_phioc .AND. .NOT. cpl_phioc ) THEN    !==  Wave to ocean energy  ==! 
     227         CALL fld_read( kt, nn_fsbc, sf_phioc )          ! read wave to ocean energy from external forcing 
     228         rn_crban(:,:) = 29.0 * sf_phioc(1)%fnow(:,:,1)     ! ! Alfa is phioc*sqrt(rw/ra)sbc_wa 
     229         WHERE( rn_crban <  10.0 ) rn_crban =  10.0 
     230         WHERE( rn_crban > 300.0 ) rn_crban = 300.0 
     231      ENDIF 
     232 
    224233      IF( ln_sdw )  THEN                           !==  Computation of the 3d Stokes Drift  ==!  
    225234         ! 
     
    267276      CHARACTER(len=100)     ::  cn_dir                          ! Root directory for location of drag coefficient files 
    268277      TYPE(FLD_N), ALLOCATABLE, DIMENSION(:) ::   slf_i     ! array of namelist informations on the fields to read 
    269       TYPE(FLD_N)            ::  sn_cdg, sn_usd, sn_vsd,  & 
     278      TYPE(FLD_N)            ::  sn_cdg, sn_usd, sn_vsd,  sn_phioc, & 
    270279                             &   sn_hsw, sn_wmp, sn_wnum, sn_tauoc      ! informations about the fields to be read 
    271280      ! 
    272       NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wnum, sn_tauoc 
     281      NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wnum, sn_tauoc, sn_phioc 
    273282      !!--------------------------------------------------------------------- 
    274283      ! 
     
    285294         IF( .NOT. cpl_wdrag ) THEN 
    286295            ALLOCATE( sf_cd(1), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg 
    287             IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_wave structure' ) 
     296            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_cd structure' ) 
    288297            ! 
    289298                                   ALLOCATE( sf_cd(1)%fnow(jpi,jpj,1)   ) 
     
    297306         IF( .NOT. cpl_tauoc ) THEN 
    298307            ALLOCATE( sf_tauoc(1), STAT=ierror )           !* allocate and fill sf_wave with sn_tauoc 
    299             IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_wave structure' ) 
     308            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_tauoc structure' ) 
    300309            ! 
    301310                                    ALLOCATE( sf_tauoc(1)%fnow(jpi,jpj,1)   ) 
     
    304313         ENDIF 
    305314         ALLOCATE( tauoc_wave(jpi,jpj) ) 
     315      ENDIF 
     316 
     317      IF( ln_phioc ) THEN 
     318         IF( .NOT. cpl_phioc ) THEN 
     319            ALLOCATE( sf_phioc(1), STAT=ierror )           !* allocate and fill sf_wave with sn_phioc 
     320            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_phioc structure' ) 
     321            ! 
     322                                    ALLOCATE( sf_phioc(1)%fnow(jpi,jpj,1)   ) 
     323            IF( sn_phioc%ln_tint )  ALLOCATE( sf_phioc(1)%fdta(jpi,jpj,1,2) ) 
     324            CALL fld_fill( sf_phioc, (/ sn_phioc /), cn_dir, 'sbc_wave_init', 'Wave module', 'namsbc_wave' ) 
     325         ENDIF 
     326         ALLOCATE( rn_crban(jpi,jpj) ) 
    306327      ENDIF 
    307328 
     
    334355            IF( jp_wmp > 0 )   slf_i(jp_wmp) = sn_wmp 
    335356            ALLOCATE( sf_sd(jpfld), STAT=ierror )   !* allocate and fill sf_sd with stokes drift 
    336             IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_wave structure' ) 
     357            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable to allocate sf_sd structure' ) 
    337358            ! 
    338359            DO ifpr= 1, jpfld 
     
    354375         IF( ln_zdfqiao .AND. .NOT.cpl_wnum ) THEN 
    355376            ALLOCATE( sf_wn(1), STAT=ierror )           !* allocate and fill sf_wave with sn_wnum 
    356             IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable toallocate sf_wave structure' ) 
     377            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_init: unable toallocate sf_wn structure' ) 
    357378                                   ALLOCATE( sf_wn(1)%fnow(jpi,jpj,1)   ) 
    358379            IF( sn_wnum%ln_tint )  ALLOCATE( sf_wn(1)%fdta(jpi,jpj,1,2) ) 
Note: See TracChangeset for help on using the changeset viewer.