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 7717 for branches/UKMO – NEMO

Changeset 7717 for branches/UKMO


Ignore:
Timestamp:
2017-02-22T17:49:40+01:00 (7 years ago)
Author:
jcastill
Message:

Add surface drag coefficient direct forcing and coupling

Location:
branches/UKMO/r6232_INGV1_WAVE-coupling/NEMOGCM
Files:
5 edited

Legend:

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

    r7672 r7717  
    299299   sn_emp      = 'emp'       ,        24         , 'emp'     , .false.      , .false., 'yearly'  , ''       , ''       , '' 
    300300 
    301    cn_dir      = './'      !  root directory for the location of the flux files 
     301   cn_dir       = './'      !  root directory for the location of the flux files 
     302   ln_shelf_flx = .false.   !  UKMO SHELF specific flux flag - read from file wind components instead of momentum  
    302303/ 
    303304!----------------------------------------------------------------------- 
     
    12961297   sn_tauoc    =  'sdw_wave' ,        1          , 'wave_stress',     .true.   , .false. , 'daily'   ,  ''      , ''       , ''  
    12971298!  
    1298    cn_dir  = './'  !  root directory for the location of drag coefficient files 
     1299   cn_dir      = './'  !  root directory for the location of drag coefficient files 
     1300   nn_drag     = 0     !  formula to calculate momentum from the wind components 
     1301                              =0 UKMO SHELF formulation 
     1302                              =1 standard formulation 
    12991303/ 
    13001304!----------------------------------------------------------------------- 
  • branches/UKMO/r6232_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r7672 r7717  
    956956      !!---------------------------------------------------------------------- 
    957957      USE zdf_oce,  ONLY : ln_zdfqiao 
     958      USE sbcflx ,  ONLY : ln_shelf_flx 
    958959 
    959960      INTEGER, INTENT(in)           ::   kt          ! ocean model time step index 
     
    10391040      ELSE                                                   !   No dynamical coupling   ! 
    10401041         !                                                   ! ========================= ! 
     1042         ! it is possible that the momentum is calculated from the winds (ln_shelf_flx) and a coupled drag coefficient 
     1043         IF( srcv(jpr_wdrag)%laction .AND. ln_shelf_flx .AND. ln_cdgw .AND. nn_drag == jp_std ) THEN 
     1044            DO jj = 1, jpj 
     1045               DO ji = 1, jpi 
     1046                  ! here utau and vtau should contain the wind components as read from the forcing files 
     1047                  zcoef = SQRT(utau(ji,jj)*utau(ji,jj) + vtau(ji,jj)*vtau(ji,jj)) 
     1048                  frcv(jpr_otx1)%z3(ji,jj,1) = zrhoa * frcv(jpr_wdrag)%z3(ji,jj,1) * utau(ji,jj) * zcoef 
     1049                  frcv(jpr_oty1)%z3(ji,jj,1) = zrhoa * frcv(jpr_wdrag)%z3(ji,jj,1) * vtau(ji,jj) * zcoef 
     1050                  utau(ji,jj) = frcv(jpr_otx1)%z3(ji,jj,1) 
     1051                  vtau(ji,jj) = frcv(jpr_oty1)%z3(ji,jj,1) 
     1052               END DO 
     1053            END DO 
     1054            llnewtx = .TRUE. 
     1055         ELSE 
    10411056         frcv(jpr_otx1)%z3(:,:,1) = 0.e0                               ! here simply set to zero  
    10421057         frcv(jpr_oty1)%z3(:,:,1) = 0.e0                               ! an external read in a file can be added instead 
    10431058         llnewtx = .TRUE. 
     1059         ENDIF 
    10441060         ! 
    10451061      ENDIF 
     
    10611077            END DO 
    10621078            CALL lbc_lnk( frcv(jpr_taum)%z3(:,:,1), 'T', 1. ) 
     1079            IF( .NOT. srcv(jpr_otx1)%laction .AND. srcv(jpr_wdrag)%laction .AND. & 
     1080                                ln_shelf_flx .AND. ln_cdgw .AND. nn_drag == jp_std ) & 
     1081               taum(:,:) = frcv(jpr_taum)%z3(:,:,1) 
    10631082            llnewtau = .TRUE. 
    10641083         ELSE 
     
    10751094      !                                                      ! ========================= ! 
    10761095      !                                                      !      10 m wind speed      !   (wndm) 
     1096      !                                                      !   include wave drag coef  !   (wndm) 
    10771097      !                                                      ! ========================= ! 
    10781098      ! 
     
    10851105!CDIR NOVERRCHK 
    10861106               DO ji = 1, jpi  
     1107                  IF( ln_shelf_flx ) THEN   ! the 10 wind module is properly calculated before if ln_shelf_flx 
     1108                     frcv(jpr_w10m)%z3(ji,jj,1) = wndm(ji,jj) 
     1109                  ELSE 
    10871110                  frcv(jpr_w10m)%z3(ji,jj,1) = SQRT( frcv(jpr_taum)%z3(ji,jj,1) * zcoef ) 
     1111                  ENDIF 
    10881112               END DO 
    10891113            END DO 
     
    10951119      IF( MOD( kt-1, k_fsbc ) == 0 ) THEN 
    10961120         ! 
     1121         ! if ln_wavcpl, the fields already contain the right information from forcing even if not ln_mixcpl 
    10971122         IF( ln_mixcpl ) THEN 
    10981123            IF( srcv(jpr_otx1)%laction ) THEN 
     
    11001125               vtau(:,:) = vtau(:,:) * xcplmask(:,:,0) + frcv(jpr_oty1)%z3(:,:,1) * zmsk(:,:) 
    11011126            ENDIF 
    1102             IF( srcv(jpr_taum)%laction .OR. (.NOT.srcv(jpr_taum)%laction .AND. srcv(jpr_otx1)%laction .AND. llnewtx ))   & 
     1127            IF( srcv(jpr_taum)%laction )   & 
    11031128               taum(:,:) = taum(:,:) * xcplmask(:,:,0) + frcv(jpr_taum)%z3(:,:,1) * zmsk(:,:) 
    1104             IF( srcv(jpr_w10m)%laction .OR. (.NOT.srcv(jpr_w10m)%laction .AND. llnewtau .AND.                            & 
    1105                (srcv(jpr_taum)%laction .OR. (.NOT.srcv(jpr_taum)%laction .AND. srcv(jpr_otx1)%laction .AND. llnewtx )))) & 
     1129            IF( srcv(jpr_w10m)%laction )   & 
    11061130               wndm(:,:) = wndm(:,:) * xcplmask(:,:,0) + frcv(jpr_w10m)%z3(:,:,1) * zmsk(:,:) 
    11071131         ELSE IF( ll_purecpl ) THEN 
     
    11721196      IF( srcv(jpr_wstrf)%laction .AND. ln_tauoc ) tauoc_wave(:,:) = frcv(jpr_wstrf)%z3(:,:,1)  
    11731197       
    1174       !                                                      ! ========================= !   
    1175       !                                                      !   Wave drag coefficient   !  
    1176       !                                                      ! ========================= !   
    1177       IF( srcv(jpr_wdrag)%laction .AND. ln_cdgw ) cdn_wave(:,:) = frcv(jpr_wdrag)%z3(:,:,1) 
    1178  
    11791198      !  Fields received by SAS when OASIS coupling 
    11801199      !  (arrays no more filled at sbcssm stage) 
  • branches/UKMO/r6232_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90

    r7470 r7717  
    2222   USE lib_mpp         ! distribued memory computing library 
    2323   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
     24   USE sbcwave         ! wave physics 
    2425 
    2526   IMPLICIT NONE 
     
    3536   INTEGER , PARAMETER ::   jp_emp  = 5   ! index of evaporation-precipation file 
    3637   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read) 
     38   LOGICAL , PUBLIC    ::   ln_shelf_flx = .FALSE. ! UKMO SHELF specific flux flag 
     39   INTEGER             ::   jpfld_local   ! maximum number of files to read (locally modified depending on ln_shelf_flx)  
    3740 
    3841   !! * Substitutions 
     
    8184      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3 
    8285      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient 
     86      REAL(wp) ::   totwind               ! UKMO SHELF: Module of wind speed 
    8387      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables 
    8488      !! 
    8589      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files 
     90      NAMELIST/namsbc_flx/ ln_shelf_flx                           ! Put here to allow merging with another UKMO branch 
    8691      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                    ! array of namelist information structures 
    8792      TYPE(FLD_N) ::   sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp  ! informations about the fields to be read 
     
    140145            END DO 
    141146         END DO 
     147         !                                                        ! add modification due to drag coefficient read from wave forcing 
     148         !                                                        ! this code is inefficient but put here to allow merging with another UKMO branch 
     149         IF( ln_shelf_flx .AND. ln_cdgw .AND. nn_drag == jp_std ) THEN 
     150            IF( cpl_wdrag ) THEN  
     151               ! reset utau and vtau to the wind components: the momentum will 
     152               ! be calculated from the coupled value of the drag coefficient 
     153               DO jj = 1, jpj 
     154                  DO ji = 1, jpi 
     155                     utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1) 
     156                     vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1) 
     157                  END DO 
     158               END DO 
     159            ELSE 
     160               DO jj = 1, jpj 
     161                  DO ji = 1, jpi 
     162                     totwind = sqrt((sf(jp_utau)%fnow(ji,jj,1))**2.0 + (sf(jp_vtau)%fnow(ji,jj,1))**2.0) 
     163                     utau(ji,jj) = zrhoa * cdn_wave(ji,jj) * sf(jp_utau)%fnow(ji,jj,1) * totwind 
     164                     vtau(ji,jj) = zrhoa * cdn_wave(ji,jj) * sf(jp_vtau)%fnow(ji,jj,1) * totwind 
     165                  END DO 
     166               END DO 
     167            ENDIF 
     168         ENDIF 
    142169         !                                                        ! add to qns the heat due to e-p 
    143170         qns(:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp        ! mass flux is at SST 
     
    153180               zmod = 0.5 * SQRT( ztx * ztx + zty * zty ) 
    154181               taum(ji,jj) = zmod 
     182               IF( ln_shelf_flx ) THEN 
     183                  ztx = sf(jp_utau)%fnow(ji-1,jj  ) + sf(jp_utau)%fnow(ji,jj) 
     184                  zty = sf(jp_vtau)%fnow(ji  ,jj-1) + sf(jp_vtau)%fnow(ji,jj) 
     185                  wndm(ji,jj) = 0.5 * SQRT( ztx * ztx + zty * zty ) 
     186               ELSE 
    155187               wndm(ji,jj) = SQRT( zmod * zcoef ) 
     188               ENDIF 
    156189            END DO 
    157190         END DO 
  • branches/UKMO/r6232_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r7672 r7717  
    137137         WRITE(numout,*) '                 wave modified ocean stress              ln_tauoc    = ', ln_tauoc  
    138138         WRITE(numout,*) '                 Stokes coriolis term                    ln_stcor    = ', ln_stcor  
    139          WRITE(numout,*) '                 neutral drag coefficient (CORE, MFS)    ln_cdgw     = ', ln_cdgw 
     139         WRITE(numout,*) '                 neutral drag coefficient                ln_cdgw     = ', ln_cdgw 
    140140         WRITE(numout,*) '              OASIS coupling (with atm or sas)           lk_oasis    = ', lk_oasis 
    141141         WRITE(numout,*) '              components of your executable              nn_components = ', nn_components 
     
    225225         IF ( .NOT.(ln_cdgw .OR. ln_sdw .OR. ln_tauoc .OR. ln_stcor ) )   THEN   
    226226             CALL ctl_warn( 'Ask for wave coupling but ln_cdgw=F, ln_sdw=F, ln_tauoc=F, ln_stcor=F')  
    227          !drag coefficient read from wave model definable only with mfs bulk formulae and core 
    228          ELSEIF (ln_cdgw .AND. .NOT.(ln_blk_mfs .OR. ln_blk_core) )       THEN        
    229              CALL ctl_stop( 'drag coefficient read from wave model definable only with mfs bulk formulae and core') 
    230227         ELSEIF (ln_stcor .AND. .NOT. ln_sdw) THEN   
    231228             CALL ctl_stop( 'Stokes-Coriolis term calculated only if activated Stokes Drift ln_sdw=T') 
  • branches/UKMO/r6232_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90

    r7606 r7717  
    6363   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)   ::   ut0sd, vt0sd        !: surface Stokes drift velocities at t-point 
    6464   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) ::   usd  , vsd  , wsd   !: Stokes drift velocities at u-, v- & w-points, resp. 
     65 
     66   INTEGER, PUBLIC            ::   nn_drag       ! type of formula to calculate wind stress from wind components 
     67   INTEGER, PUBLIC, PARAMETER ::   jp_ukmo = 0        ! UKMO SHELF formulation 
     68   INTEGER, PUBLIC, PARAMETER ::   jp_std  = 1        ! standard formulation:  
    6569 
    6670   !! * Substitutions 
     
    210214         CALL fld_read( kt, nn_fsbc, sf_cd )             ! read from external forcing 
    211215         cdn_wave(:,:) = sf_cd(1)%fnow(:,:,1) 
     216         ! make sure that the interpolation does not write silly fill values in case it fails in a grid point 
     217         where( cdn_wave > 1.0 ) cdn_wave = 1.5e-3  
    212218      ENDIF 
    213219 
     
    265271                             &   sn_hsw, sn_wmp, sn_wnum, sn_tauoc      ! informations about the fields to be read 
    266272      ! 
    267       NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wnum, sn_tauoc 
     273      NAMELIST/namsbc_wave/  sn_cdg, cn_dir, sn_usd, sn_vsd, sn_hsw, sn_wmp, sn_wnum, sn_tauoc, nn_drag 
    268274      !!--------------------------------------------------------------------- 
    269275      ! 
     
    278284      ! 
    279285      IF( ln_cdgw ) THEN 
     286         ! check the value of nn_drag 
     287         IF( .NOT. ( nn_drag == jp_ukmo .OR. nn_drag == jp_std )) THEN 
     288            CALL ctl_stop( 'sbc_wave_init: nn_drag does not specify a valid drag formulation' ) 
     289            RETURN   
     290         ENDIF 
     291            
    280292         IF( .NOT. cpl_wdrag ) THEN 
    281293            ALLOCATE( sf_cd(1), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg 
Note: See TracChangeset for help on using the changeset viewer.