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 7792 for branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90 – NEMO

Ignore:
Timestamp:
2017-03-14T16:47:48+01:00 (7 years ago)
Author:
jcastill
Message:

Changes as in branch branches/UKMO/r6232_INGV1_WAVE-coupling@7763

File:
1 edited

Legend:

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

    r7470 r7792  
    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 
     
    3233   INTEGER , PARAMETER ::   jp_vtau = 2   ! index of wind stress (j-component) file 
    3334   INTEGER , PARAMETER ::   jp_qtot = 3   ! index of total (non solar+solar) heat file 
     35 
     36   ! These lines are here just to allow merging with another branch 
     37   INTEGER, PUBLIC            ::   nn_drag        ! type of formula to calculate wind stress from wind components 
     38   INTEGER, PUBLIC, PARAMETER ::   jp_ukmo  = 0        ! UKMO SHELF formulation 
     39   INTEGER, PUBLIC, PARAMETER ::   jp_std   = 1        ! standard formulation with forced or coupled drag coefficient  
     40   INTEGER, PUBLIC, PARAMETER ::   jp_const = 2        ! standard formulation with constant drag coefficient  
     41 
    3442   INTEGER , PARAMETER ::   jp_qsr  = 4   ! index of solar heat file 
    3543   INTEGER , PARAMETER ::   jp_emp  = 5   ! index of evaporation-precipation file 
    3644   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read) 
     45   LOGICAL , PUBLIC    ::   ln_shelf_flx = .FALSE. ! UKMO SHELF specific flux flag 
     46   INTEGER             ::   jpfld_local   ! maximum number of files to read (locally modified depending on ln_shelf_flx)  
    3747 
    3848   !! * Substitutions 
     
    8191      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3 
    8292      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient 
     93      REAL(wp) ::   totwind               ! UKMO SHELF: Module of wind speed 
    8394      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables 
    8495      !! 
    8596      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files 
     97      NAMELIST/namsbc_flx/ ln_shelf_flx                           ! Put here to allow merging with another UKMO branch 
    8698      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                    ! array of namelist information structures 
    8799      TYPE(FLD_N) ::   sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp  ! informations about the fields to be read 
     
    140152            END DO 
    141153         END DO 
     154         !                                                        ! add modification due to drag coefficient read from wave forcing 
     155         !                                                        ! this code is inefficient but put here to allow merging with another UKMO branch 
     156         IF( ln_shelf_flx ) THEN 
     157            IF( ln_cdgw .AND. nn_drag == jp_std ) THEN 
     158               IF( cpl_wdrag ) THEN  
     159                  ! reset utau and vtau to the wind components: the momentum will 
     160                  ! be calculated from the coupled value of the drag coefficient 
     161                  DO jj = 1, jpj 
     162                     DO ji = 1, jpi 
     163                        utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1) 
     164                        vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1) 
     165                     END DO 
     166                  END DO 
     167               ELSE 
     168                  DO jj = 1, jpj 
     169                     DO ji = 1, jpi 
     170                        totwind = sqrt((sf(jp_utau)%fnow(ji,jj,1))**2.0 + (sf(jp_vtau)%fnow(ji,jj,1))**2.0) 
     171                        utau(ji,jj) = zrhoa * cdn_wave(ji,jj) * sf(jp_utau)%fnow(ji,jj,1) * totwind 
     172                        vtau(ji,jj) = zrhoa * cdn_wave(ji,jj) * sf(jp_vtau)%fnow(ji,jj,1) * totwind 
     173                     END DO 
     174                  END DO 
     175               ENDIF 
     176            ELSE IF( nn_drag == jp_const ) THEN 
     177               DO jj = 1, jpj 
     178                  DO ji = 1, jpi 
     179                     totwind = sqrt((sf(jp_utau)%fnow(ji,jj,1))**2.0 + (sf(jp_vtau)%fnow(ji,jj,1))**2.0) 
     180                     utau(ji,jj) = zrhoa * zcdrag * sf(jp_utau)%fnow(ji,jj,1) * totwind 
     181                     vtau(ji,jj) = zrhoa * zcdrag * sf(jp_vtau)%fnow(ji,jj,1) * totwind 
     182                  END DO 
     183               END DO 
     184            ENDIF 
     185         ENDIF 
    142186         !                                                        ! add to qns the heat due to e-p 
    143187         qns(:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp        ! mass flux is at SST 
     
    153197               zmod = 0.5 * SQRT( ztx * ztx + zty * zty ) 
    154198               taum(ji,jj) = zmod 
     199               IF( ln_shelf_flx ) THEN 
     200                  ztx = sf(jp_utau)%fnow(ji-1,jj  ) + sf(jp_utau)%fnow(ji,jj) 
     201                  zty = sf(jp_vtau)%fnow(ji  ,jj-1) + sf(jp_vtau)%fnow(ji,jj) 
     202                  wndm(ji,jj) = 0.5 * SQRT( ztx * ztx + zty * zty ) 
     203               ELSE 
    155204               wndm(ji,jj) = SQRT( zmod * zcoef ) 
     205               ENDIF 
    156206            END DO 
    157207         END DO 
Note: See TracChangeset for help on using the changeset viewer.