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

Changeset 6311


Ignore:
Timestamp:
2016-02-15T12:28:31+01:00 (8 years ago)
Author:
cetlod
Message:

3.6 stable : have 2 different values for open lead fraction in LIM3 to enhance ventilation in southern ocean, see ticket #1678

Location:
branches/2015/nemo_v3_6_STABLE/NEMOGCM
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/CONFIG/SHARED/namelist_ice_lim3_ref

    r5429 r6311  
    2121   cn_icerst_outdir = "."          !  directory in which to write output ice restarts 
    2222   ln_limdyn     = .true.          !  ice dynamics (T) or thermodynamics only (F) 
    23    rn_amax       = 0.999           !  maximum tolerated ice concentration  
     23   rn_amax_n     = 0.999           !  maximum tolerated ice concentration NH 
     24   rn_amax_s     = 0.999           !  maximum tolerated ice concentration SH 
    2425   ln_limdiahsb  = .false.         !  check the heat and salt budgets (T) or not (F) 
    2526   ln_limdiaout  = .true.          !  output the heat and salt budgets (T) or not (F) 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/ice.F90

    r5341 r6311  
    301301 
    302302   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ftr_ice   !: transmitted solar radiation under ice 
     303   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d  !: maximum ice concentration 2d array 
    303304 
    304305   !!-------------------------------------------------------------------------- 
     
    372373   INTEGER          , PUBLIC ::   nlay_i          !: number of ice  layers  
    373374   INTEGER          , PUBLIC ::   nlay_s          !: number of snow layers  
    374    CHARACTER(len=32), PUBLIC ::   cn_icerst_in    !: suffix of ice restart name (input) 
     375   CHARACTER(len=80), PUBLIC ::   cn_icerst_in    !: suffix of ice restart name (input) 
    375376   CHARACTER(len=256), PUBLIC ::   cn_icerst_indir !: ice restart input directory 
    376    CHARACTER(len=32), PUBLIC ::   cn_icerst_out   !: suffix of ice restart name (output) 
     377   CHARACTER(len=80), PUBLIC ::   cn_icerst_out   !: suffix of ice restart name (output) 
    377378   CHARACTER(len=256), PUBLIC ::   cn_icerst_outdir!: ice restart output directory 
    378379   LOGICAL          , PUBLIC ::   ln_limdyn       !: flag for ice dynamics (T) or not (F) 
    379380   LOGICAL          , PUBLIC ::   ln_icectl       !: flag for sea-ice points output (T) or not (F) 
    380    REAL(wp)         , PUBLIC ::   rn_amax         !: maximum ice concentration 
     381   REAL(wp)         , PUBLIC ::   rn_amax_n       !: maximum ice concentration Northern hemisphere 
     382   REAL(wp)         , PUBLIC ::   rn_amax_s       !: maximum ice concentration Southern hemisphere 
    381383   INTEGER          , PUBLIC ::   iiceprt         !: debug i-point 
    382384   INTEGER          , PUBLIC ::   jiceprt         !: debug j-point 
     
    438440         &      afx_tot(jpi,jpj) , afx_thd(jpi,jpj),  afx_dyn(jpi,jpj) ,                        & 
    439441         &      fhtur  (jpi,jpj) , ftr_ice(jpi,jpj,jpl), qlead  (jpi,jpj) ,                     & 
     442         &      rn_amax_2d(jpi,jpj),                                                            & 
    440443         &      sfx_res(jpi,jpj) , sfx_bri(jpi,jpj) , sfx_dyn(jpi,jpj) ,                        & 
    441444         &      sfx_bog(jpi,jpj) , sfx_bom(jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) ,    & 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limcons.F90

    r5183 r6311  
    256256            ENDIF 
    257257            IF (     zvmin   < -epsi10 ) WRITE(numout,*) 'violation v_i<0  [m]          (',cd_routine,') = ',zvmin 
    258             IF (     zamax   > rn_amax+epsi10 .AND. cd_routine /= 'limtrp' .AND. cd_routine /= 'limitd_me' ) THEN 
     258            IF (     zamax   > MAX( rn_amax_n, rn_amax_s ) + epsi10 .AND. & 
     259               &                         cd_routine /= 'limtrp' .AND. cd_routine /= 'limitd_me' ) THEN 
    259260                                         WRITE(numout,*) 'violation a_i>amax            (',cd_routine,') = ',zamax 
    260261            ENDIF 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limthd_lac.F90

    r5202 r6311  
    297297         END DO 
    298298 
    299          CALL tab_2d_1d( nbpac, qlead_1d  (1:nbpac)     , qlead  , jpi, jpj, npac(1:nbpac) ) 
    300          CALL tab_2d_1d( nbpac, t_bo_1d   (1:nbpac)     , t_bo   , jpi, jpj, npac(1:nbpac) ) 
    301          CALL tab_2d_1d( nbpac, sfx_opw_1d(1:nbpac)     , sfx_opw, jpi, jpj, npac(1:nbpac) ) 
    302          CALL tab_2d_1d( nbpac, wfx_opw_1d(1:nbpac)     , wfx_opw, jpi, jpj, npac(1:nbpac) ) 
    303          CALL tab_2d_1d( nbpac, hicol_1d  (1:nbpac)     , hicol  , jpi, jpj, npac(1:nbpac) ) 
    304          CALL tab_2d_1d( nbpac, zvrel_1d  (1:nbpac)     , zvrel  , jpi, jpj, npac(1:nbpac) ) 
    305  
    306          CALL tab_2d_1d( nbpac, hfx_thd_1d(1:nbpac)     , hfx_thd, jpi, jpj, npac(1:nbpac) ) 
    307          CALL tab_2d_1d( nbpac, hfx_opw_1d(1:nbpac)     , hfx_opw, jpi, jpj, npac(1:nbpac) ) 
     299         CALL tab_2d_1d( nbpac, qlead_1d  (1:nbpac), qlead     , jpi, jpj, npac(1:nbpac) ) 
     300         CALL tab_2d_1d( nbpac, t_bo_1d   (1:nbpac), t_bo      , jpi, jpj, npac(1:nbpac) ) 
     301         CALL tab_2d_1d( nbpac, sfx_opw_1d(1:nbpac), sfx_opw   , jpi, jpj, npac(1:nbpac) ) 
     302         CALL tab_2d_1d( nbpac, wfx_opw_1d(1:nbpac), wfx_opw   , jpi, jpj, npac(1:nbpac) ) 
     303         CALL tab_2d_1d( nbpac, hicol_1d  (1:nbpac), hicol     , jpi, jpj, npac(1:nbpac) ) 
     304         CALL tab_2d_1d( nbpac, zvrel_1d  (1:nbpac), zvrel     , jpi, jpj, npac(1:nbpac) ) 
     305 
     306         CALL tab_2d_1d( nbpac, hfx_thd_1d(1:nbpac), hfx_thd   , jpi, jpj, npac(1:nbpac) ) 
     307         CALL tab_2d_1d( nbpac, hfx_opw_1d(1:nbpac), hfx_opw   , jpi, jpj, npac(1:nbpac) ) 
     308         CALL tab_2d_1d( nbpac, rn_amax_1d(1:nbpac), rn_amax_2d, jpi, jpj, npac(1:nbpac) ) 
    308309 
    309310         !------------------------------------------------------------------------------! 
     
    409410         ! we keep the excessive volume in memory and attribute it later to bottom accretion 
    410411         DO ji = 1, nbpac 
    411             IF ( za_newice(ji) >  ( rn_amax - zat_i_1d(ji) ) ) THEN 
    412                zda_res(ji)   = za_newice(ji) - ( rn_amax - zat_i_1d(ji) ) 
     412            IF ( za_newice(ji) >  ( rn_amax_1d(ji) - zat_i_1d(ji) ) ) THEN 
     413               zda_res(ji)   = za_newice(ji) - ( rn_amax_1d(ji) - zat_i_1d(ji) ) 
    413414               zdv_res(ji)   = zda_res  (ji) * zh_newice(ji)  
    414415               za_newice(ji) = za_newice(ji) - zda_res  (ji) 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limtrp.F90

    r5202 r6311  
    422422            DO jj = 1, jpj 
    423423               DO ji = 1, jpi 
    424                   a_i(ji,jj,1)  = MIN( a_i(ji,jj,1), rn_amax ) 
     424                  a_i(ji,jj,1)  = MIN( a_i(ji,jj,1), rn_amax_2d(ji,jj) ) 
    425425               END DO 
    426426            END DO 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limupdate1.F90

    r5215 r6311  
    8080         DO jj = 1, jpj 
    8181            DO ji = 1, jpi 
    82                IF( at_i(ji,jj) > rn_amax .AND. a_i(ji,jj,jl) > 0._wp ) THEN 
    83                   a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax / at_i(ji,jj) ) ) 
    84                   oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax / at_i(ji,jj) ) ) 
     82               IF( at_i(ji,jj) > rn_amax_2d(ji,jj) .AND. a_i(ji,jj,jl) > 0._wp ) THEN 
     83                  a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 
     84                  oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 
    8585               ENDIF 
    8686            END DO 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/limupdate2.F90

    r5410 r6311  
    9494         DO jj = 1, jpj 
    9595            DO ji = 1, jpi 
    96                IF( at_i(ji,jj) > rn_amax .AND. a_i(ji,jj,jl) > 0._wp ) THEN 
    97                   a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax / at_i(ji,jj) ) ) 
    98                   oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax / at_i(ji,jj) ) ) 
     96               IF( at_i(ji,jj) > rn_amax_2d(ji,jj) .AND. a_i(ji,jj,jl) > 0._wp ) THEN 
     97                  a_i (ji,jj,jl) = a_i (ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 
     98                  oa_i(ji,jj,jl) = oa_i(ji,jj,jl) * ( 1._wp - ( 1._wp - rn_amax_2d(ji,jj) / at_i(ji,jj) ) ) 
    9999               ENDIF 
    100100            END DO 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/LIM_SRC_3/thd_ice.F90

    r5407 r6311  
    5151   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hfx_dif_1d 
    5252   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hfx_opw_1d 
     53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   rn_amax_1d 
    5354   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hfx_snw_1d 
    5455   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hfx_err_1d 
     
    144145         &      hfx_sum_1d(jpij) , hfx_bom_1d(jpij) ,hfx_bog_1d(jpij) ,    &  
    145146         &      hfx_dif_1d(jpij) , hfx_opw_1d(jpij) ,                      & 
     147         &      rn_amax_1d(jpij) ,                                         & 
    146148         &      hfx_thd_1d(jpij) , hfx_spr_1d(jpij) ,                      & 
    147149         &      hfx_snw_1d(jpij) , hfx_sub_1d(jpij) , hfx_err_1d(jpij) ,   & 
  • branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r5540 r6311  
    265265      !!---------------------------------------------------------------------- 
    266266      INTEGER :: ierr 
     267      INTEGER :: ji, jj 
    267268      !!---------------------------------------------------------------------- 
    268269      IF(lwp) WRITE(numout,*) 
     
    321322      tn_ice(:,:,:) = t_su(:,:,:)       ! initialisation of surface temp for coupled simu 
    322323      ! 
     324      DO jj = 1, jpj 
     325         DO ji = 1, jpi 
     326            IF( gphit(ji,jj) > 0._wp ) THEN  ;  rn_amax_2d(ji,jj) = rn_amax_n  ! NH 
     327            ELSE                             ;  rn_amax_2d(ji,jj) = rn_amax_s  ! SH 
     328            ENDIF 
     329        ENDDO 
     330      ENDDO  
     331      ! 
    323332      nstart = numit  + nn_fsbc       
    324333      nitrun = nitend - nit000 + 1  
     
    343352      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    344353      NAMELIST/namicerun/ jpl, nlay_i, nlay_s, cn_icerst_in, cn_icerst_indir, cn_icerst_out, cn_icerst_outdir,  & 
    345          &                ln_limdyn, rn_amax, ln_limdiahsb, ln_limdiaout, ln_icectl, iiceprt, jiceprt   
     354         &                ln_limdyn, rn_amax_n, rn_amax_s, ln_limdiahsb, ln_limdiaout, ln_icectl, iiceprt, jiceprt   
    346355      !!------------------------------------------------------------------- 
    347356      !                     
     
    364373         WRITE(numout,*) '   number of snow layers                                   = ', nlay_s 
    365374         WRITE(numout,*) '   switch for ice dynamics (1) or not (0)      ln_limdyn   = ', ln_limdyn 
    366          WRITE(numout,*) '   maximum ice concentration                               = ', rn_amax  
     375         WRITE(numout,*) '   maximum ice concentration for NH                        = ', rn_amax_n  
     376         WRITE(numout,*) '   maximum ice concentration for SH                        = ', rn_amax_s 
    367377         WRITE(numout,*) '   Diagnose heat/salt budget or not          ln_limdiahsb  = ', ln_limdiahsb 
    368378         WRITE(numout,*) '   Output   heat/salt budget or not          ln_limdiaout  = ', ln_limdiaout 
Note: See TracChangeset for help on using the changeset viewer.