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 5196 for branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/OPA_SRC/SBC/sbcana.F90 – NEMO

Ignore:
Timestamp:
2015-04-07T10:28:07+02:00 (9 years ago)
Author:
pabouttier
Message:

Add SEABASS reference configuration for this NEMO version for now; See Ticket #1505

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/OPA_SRC/SBC/sbcana.F90

    r4602 r5196  
    2626   PUBLIC   sbc_ana    ! routine called in sbcmod module 
    2727   PUBLIC   sbc_gyre   ! routine called in sbcmod module 
     28   PUBLIC   sbc_seabass   ! routine called in sbcmod module 
    2829 
    2930   !                                !!* Namelist namsbc_ana * 
     
    323324   END SUBROUTINE sbc_gyre 
    324325 
     326   SUBROUTINE sbc_seabass( kt ) 
     327      !!--------------------------------------------------------------------- 
     328      !!                    ***  ROUTINE sbc_seabass *** 
     329      !! 
     330      !! ** Purpose :   provide at each time-step the ocean surface boundary 
     331      !!      condition, i.e. the momentum, heat and freshwater fluxes. 
     332      !! 
     333      !! ** Method  :   Constant and uniform surface forcing specified from 
     334      !!      namsbc_ana namelist parameters. All the fluxes are time inde- 
     335      !!      pendant except the stresses which increase from zero during 
     336      !!      the first nn_tau000 time-step 
     337      !!      * C A U T I O N : never mask the surface stress field ! 
     338      !! 
     339      !! ** Action  : - set the ocean surface boundary condition, i.e. 
     340      !!                   utau, vtau, qns, qsr, emp, emps 
     341      !!---------------------------------------------------------------------- 
     342      INTEGER, INTENT(in) ::   kt       ! ocean time step 
     343      !! 
     344      INTEGER             ::   ji, jj          ! dummy loop indices 
     345      REAL(wp)            ::   zfacto          ! local scalar 
     346      REAL(wp) ::   zrhoa  = 1.22_wp      ! Air density kg/m3 
     347      REAL(wp) ::   zcdrag = 1.5e-3_wp    ! drag coefficient 
     348      REAL(wp)            ::   ztx, zty, ztau  ! local scalar 
     349      !! 
     350      NAMELIST/namsbc_ana/ nn_tau000, rn_utau0, rn_vtau0, rn_qns0, rn_qsr0, rn_emp0 
     351      !!--------------------------------------------------------------------- 
     352      ! 
     353      IF( kt == nit000 ) THEN 
     354         ! 
     355         REWIND ( numnam )                   ! Read Namelist namsbc : surface fluxes 
     356         READ   ( numnam, namsbc_ana ) 
     357         ! 
     358         IF(lwp) WRITE(numout,*)' ' 
     359         IF(lwp) WRITE(numout,*)' sbc_ana : Constant surface fluxes read in namsbc_ana namelist' 
     360         IF(lwp) WRITE(numout,*)' ~~~~~~~ ' 
     361         IF(lwp) WRITE(numout,*)'              spin up of the stress  nn_tau000 = ', nn_tau000, ' time-steps' 
     362         IF(lwp) WRITE(numout,*)'              constant i-stress      rn_utau0  = ', rn_utau0 , ' N/m2' 
     363         IF(lwp) WRITE(numout,*)'              constant j-stress      rn_vtau0  = ', rn_vtau0 , ' N/m2' 
     364         IF(lwp) WRITE(numout,*)'              non solar heat flux    rn_qns0   = ', rn_qns0  , ' W/m2' 
     365         IF(lwp) WRITE(numout,*)'              solar heat flux        rn_qsr0   = ', rn_qsr0  , ' W/m2' 
     366         IF(lwp) WRITE(numout,*)'              net heat flux          rn_emp0   = ', rn_emp0  , ' Kg/m2/s' 
     367         ! 
     368         nn_tau000 = MAX( nn_tau000, 1 )   ! must be >= 1 
     369         qns   (:,:) = rn_qns0 
     370         qsr   (:,:) = 0._wp 
     371         emp   (:,:) = 0._wp 
     372         emps  (:,:) = 0._wp 
     373         ! 
     374         IF (jphgr_msh .eq. 2 .or. jphgr_msh .eq. 3) THEN 
     375            DO jj = 1, jpj 
     376               DO ji = 1, jpi 
     377                  utau(ji,jj) = -rn_utau0 * COS(2.*rpi         & 
     378                  &             * (gphiu(ji,jj)+18.5533)/(2207.84+18.5533)) 
     379                  vtau (ji,jj) =   0. 
     380               END DO 
     381            END DO 
     382         ELSE 
     383            DO jj = 1, jpj 
     384               DO ji = 1, jpi 
     385                  utau(ji,jj) = -rn_utau0 * COS(2.*rpi         & 
     386                  &             * (gphiu(ji,jj)-24.)/(44.-24.)) 
     387                  vtau (ji,jj) =   0. 
     388               END DO 
     389            END DO 
     390         END IF 
     391 
     392 
     393         IF(lwp) WRITE(numout,*)' tau     : Constant surface wind stress read in namelist' 
     394 
     395      ENDIF 
     396 
     397      zfacto = 0.5 / ( zrhoa * zcdrag ) 
     398!CDIR NOVERRCHK 
     399      DO jj = 2, jpjm1 
     400!CDIR NOVERRCHK 
     401         DO ji = fs_2, fs_jpim1   ! vect. opt. 
     402            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
     403            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
     404            ztau = SQRT( ztx * ztx + zty * zty ) 
     405            wndm(ji,jj) = SQRT ( ztau * zfacto ) * tmask(ji,jj,1) 
     406         END DO 
     407      END DO 
     408      CALL lbc_lnk( wndm(:,:) , 'T', 1. ) 
     409      ! 
     410 
     411   END SUBROUTINE sbc_seabass 
     412 
    325413   !!====================================================================== 
    326414END MODULE sbcana 
Note: See TracChangeset for help on using the changeset viewer.