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 8765 – NEMO

Changeset 8765


Ignore:
Timestamp:
2017-11-21T14:15:42+01:00 (6 years ago)
Author:
jcastill
Message:

Keep reading the wind stress in forced mode in order to calculate the 10m winds, which is needed for ice calculations

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/r8727_WAVE-2_Clementi_add_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90

    r8755 r8765  
    2929   PUBLIC sbc_flx       ! routine called by step.F90 
    3030 
    31    INTEGER             ::   jpfld         ! maximum number of files to read  
    32    INTEGER             ::   jp_utau       ! index of wind stress (i-component) file 
    33    INTEGER             ::   jp_vtau       ! index of wind stress (j-component) file 
    34    INTEGER             ::   jp_qtot       ! index of total (non solar+solar) heat file 
    35    INTEGER             ::   jp_qsr        ! index of solar heat file 
    36    INTEGER             ::   jp_emp        ! index of evaporation-precipation file 
     31   INTEGER , PARAMETER ::   jpfld   = 5   ! maximum number of files to read  
     32   INTEGER , PARAMETER ::   jp_utau = 1   ! index of wind stress (i-component) file 
     33   INTEGER , PARAMETER ::   jp_vtau = 2   ! index of wind stress (j-component) file 
     34   INTEGER , PARAMETER ::   jp_qtot = 3   ! index of total (non solar+solar) heat file 
     35   INTEGER , PARAMETER ::   jp_qsr  = 4   ! index of solar heat file 
     36   INTEGER , PARAMETER ::   jp_emp  = 5   ! index of evaporation-precipation file 
    3737   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read) 
    3838 
     
    8282      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient 
    8383      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables 
    84       LOGICAL  ::   ln_readtau            ! Is it necessary to read utau, vtau from file? 
    8584      !! 
    8685      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files 
     
    9190      ! 
    9291      IF( kt == nit000 ) THEN                ! First call kt=nit000   
    93          ln_readtau = .NOT. (ln_wave .AND. ln_tauw ) 
    94  
    95          ! prepare the index of the fields that have to be read 
    96          jpfld = 0 
    97          IF( ln_readtau ) THEN 
    98             jp_utau = jpfld+1 
    99             jp_vtau = jpfld+2 
    100             jpfld = jpfld+2 
    101          ELSE 
    102             jp_utau = 0   ;  jp_vtau = 0 
    103          ENDIF 
    104          jp_qtot = jpfld+1 
    105          jp_qsr = jpfld+2 
    106          jp_emp = jpfld+3 
    107          jpfld = jpfld+3 
    108  
    10992         ! set file information 
    11093         REWIND( numnam_ref )              ! Namelist namsbc_flx in reference namelist : Files for fluxes 
     
    122105         ! 
    123106         !                                         ! store namelist information in an array 
    124          IF( ln_readtau ) THEN 
    125             slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau 
    126          ENDIF 
     107         slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau 
    127108         slf_i(jp_qtot) = sn_qtot   ;   slf_i(jp_qsr ) = sn_qsr  
    128109         slf_i(jp_emp ) = sn_emp 
     
    152133         DO jj = 1, jpj                                           ! set the ocean fluxes from read fields 
    153134            DO ji = 1, jpi 
    154                IF( ln_readtau ) THEN 
    155                   utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1) 
    156                   vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1) 
    157                ENDIF 
     135               utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1) 
     136               vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1) 
    158137               qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj,1) - sf(jp_qsr)%fnow(ji,jj,1) 
    159138               emp (ji,jj) = sf(jp_emp )%fnow(ji,jj,1) 
     
    164143         ! 
    165144         !                                                        ! module of wind stress and wind speed at T-point 
    166          IF( ln_readtau ) THEN 
    167             zcoef = 1. / ( zrhoa * zcdrag ) 
    168             DO jj = 2, jpjm1 
    169                DO ji = fs_2, fs_jpim1   ! vect. opt. 
    170                   ztx = utau(ji-1,jj  ) + utau(ji,jj)  
    171                   zty = vtau(ji  ,jj-1) + vtau(ji,jj)  
    172                   zmod = 0.5 * SQRT( ztx * ztx + zty * zty ) 
    173                   taum(ji,jj) = zmod 
    174                   wndm(ji,jj) = SQRT( zmod * zcoef ) 
    175                END DO 
     145         zcoef = 1. / ( zrhoa * zcdrag ) 
     146         DO jj = 2, jpjm1 
     147            DO ji = fs_2, fs_jpim1   ! vect. opt. 
     148               ztx = utau(ji-1,jj  ) + utau(ji,jj)  
     149               zty = vtau(ji  ,jj-1) + vtau(ji,jj)  
     150               zmod = 0.5 * SQRT( ztx * ztx + zty * zty ) 
     151               taum(ji,jj) = zmod 
     152               wndm(ji,jj) = SQRT( zmod * zcoef ) 
    176153            END DO 
    177             taum(:,:) = taum(:,:) * tmask(:,:,1) ; wndm(:,:) = wndm(:,:) * tmask(:,:,1) 
    178             CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. ) 
    179          ENDIF 
     154         END DO 
     155         taum(:,:) = taum(:,:) * tmask(:,:,1) ; wndm(:,:) = wndm(:,:) * tmask(:,:,1) 
     156         CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. ) 
    180157 
    181158         IF( nitend-nit000 <= 100 .AND. lwp ) THEN                ! control print (if less than 100 time-step asked) 
Note: See TracChangeset for help on using the changeset viewer.