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

Changeset 5196


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

Location:
branches/2012/dev_v3_4_STABLE_2012/NEMOGCM
Files:
4 added
5 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/CONFIG/cfg.txt

    r4142 r5196  
    88ORCA2_LIM OPA_SRC LIM_SRC_2 NST_SRC 
    99ORCA2_OFF_PISCES OPA_SRC OFF_SRC TOP_SRC 
     10SEABASS OPA_SRC 
  • branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/OPA_SRC/DOM/istate.F90

    r5169 r5196  
    113113         ELSEIF( cp_cfg == 'gyre' ) THEN 
    114114            CALL istate_gyre                     ! GYRE  configuration : start from pre-defined T-S fields 
     115         ELSEIF( cp_cfg == 'seabass' ) THEN 
     116            CALL istate_seabass 
    115117         ELSEIF( ln_tsd_init      ) THEN         ! Initial T-S fields read in files 
    116118            CALL dta_tsd( nit000, tsb )                  ! read 3D T and S data at nit000 
     
    412414 
    413415 
     416 
     417   SUBROUTINE istate_seabass 
     418      !!---------------------------------------------------------------------- 
     419      !!                   ***  ROUTINE istate_seabass  *** 
     420      !! 
     421      !! ** Purpose :   Initialization of the dynamics and tracers for seabass 
     422      !!      configuration (double gyre) 
     423      !! 
     424      !! ** Method  : - set temperature field following Chassignet and Gent, JPO 
     425      !!                    21, pp1290-1299, 1991, and the law 
     426      !!                    rho/rho0=1-2.e-4(T-T0) 
     427      !!              - set salinity field constant 
     428      !! 
     429      !!---------------------------------------------------------------------- 
     430      !! * Local variables 
     431      INTEGER :: ji, jj, jk     ! dummy loop indices 
     432      REAL(wp) ::   zsal = 35.5 
     433      !!---------------------------------------------------------------------- 
     434 
     435      IF(lwp) WRITE(numout,*) 
     436      IF(lwp) WRITE(numout,*) 'istate_seabass : initial analytical T and constant S profiles ' 
     437      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
     438 
     439      DO jk = 1, jpk 
     440         DO jj = 1, jpj 
     441            DO ji = 1, jpi 
     442               tsn(ji,jj,jk,jp_tem) = ( 25.+5.9e-5*800./9.81/2.e-4*   & 
     443               &    (exp(-gdept_0(jk)/800.)-1.))  * tmask(ji,jj,jk) 
     444               tsb(ji,jj,jk,jp_tem) = tsn(ji,jj,jk, jp_tem) 
     445          END DO 
     446        END DO 
     447      END DO 
     448 
     449      tsn(:,:,:,jp_sal) = zsal  * tmask(:,:,:) 
     450      tsb(:,:,:,jp_sal) = tsn(:,:,:,jp_sal) 
     451 
     452      IF(lwp) THEN 
     453         WRITE(numout,*) 
     454         WRITE(numout,*) '              Initial temperature and salinity profiles:' 
     455         WRITE(numout, "(9x,' level   gdept   temperature   salinity   ')" ) 
     456         WRITE(numout, "(10x, i4, 3f10.2)" ) ( jk, gdept_0(jk), tsn(2,2,jk,jp_tem), tsn(2,2,jk,jp_sal), jk = 1, jpk ) 
     457      ENDIF 
     458 
     459 
     460   END SUBROUTINE istate_seabass 
     461 
     462 
     463 
    414464   SUBROUTINE istate_uvg 
    415465      !!---------------------------------------------------------------------- 
  • 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 
  • branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r3690 r5196  
    101101        IF( lk_cice )   nn_ice      = 4 
    102102      ENDIF 
    103       IF( cp_cfg == 'gyre' ) THEN            ! GYRE configuration 
     103      IF( cp_cfg == 'gyre' .OR. cp_cfg == 'seabass' ) THEN            ! GYRE configuration 
    104104          ln_ana      = .TRUE.    
    105105          nn_ice      =   0 
     
    178178      IF( ln_blk_mfs      ) THEN   ;   nsbc =  6   ; icpt = icpt + 1   ;   ENDIF       ! MFS  bulk       formulation 
    179179      IF( ln_cpl          ) THEN   ;   nsbc =  5   ; icpt = icpt + 1   ;   ENDIF       ! Coupled         formulation 
    180       IF( cp_cfg == 'gyre') THEN   ;   nsbc =  0                       ;   ENDIF       ! GYRE analytical formulation 
     180      IF( cp_cfg == 'gyre' .OR. cp_cfg == 'seabass' ) THEN   ;   nsbc =  0                       ;   ENDIF       ! GYRE analytical formulation 
    181181      IF( lk_esopa        )            nsbc = -1                                       ! esopa test, ALL formulations 
    182182      ! 
     
    256256      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition 
    257257      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, emps) 
    258       CASE(  0 )   ;   CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration 
     258      CASE(  0 )   ;                                     ! analytical formulation : GYRE or  
     259                                                         ! SEABASS configurations 
     260         IF (cp_cfg == 'gyre') THEN 
     261            CALL sbc_gyre    ( kt )                    ! analytical formulation : GYRE configuration 
     262         ELSEIF (cp_cfg == 'seabass') THEN 
     263            CALL sbc_seabass     ( kt ) 
     264         ENDIF 
    259265      CASE(  1 )   ;   CALL sbc_ana     ( kt )                    ! analytical formulation : uniform sbc 
    260266      CASE(  2 )   ;   CALL sbc_flx     ( kt )                    ! flux formulation 
  • branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/OPA_SRC/par_oce.F90

    r3294 r5196  
    7676   !!--------------------------------------------------------------------- 
    7777#             include "par_GYRE.h90" 
     78#elif defined key_seabass 
     79   !!--------------------------------------------------------------------- 
     80   !!   'key_seabass'      :                  mid-latitude basin : SEABASS 
     81   !!--------------------------------------------------------------------- 
     82#             include "par_SEABASS.h90" 
    7883#elif defined key_pomme_r025 
    7984   !!--------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.