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/r6232_INGV1_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90 – NEMO

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

Add surface drag coefficient direct forcing and coupling

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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 
Note: See TracChangeset for help on using the changeset viewer.