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 3419 for branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM – NEMO

Ignore:
Timestamp:
2012-06-20T18:16:33+02:00 (12 years ago)
Author:
acc
Message:

Branch: dev_r3385_NOCS04_HAMF; #665. Stage 4 of 2012 development: Changes to get LIM3 working with embedded sea-ice. Working with a reduced (halved) timestep but exhibiting the same stability problems as LIM2_EVP with standard ORCA2 settings.

Location:
branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r3402 r3419  
    3434   USE prtctl           ! Print control 
    3535   USE cpl_oasis3, ONLY : lk_cpl 
     36   USE oce, ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass 
     37   USE dom_ice, ONLY : tms 
    3638 
    3739   IMPLICIT NONE 
     
    230232               &   + tprecip(ji,jj) *         at_i(ji,jj)             &   ! all precipitation reach the ocean 
    231233               &   - sprecip(ji,jj) * ( 1. - (pfrld(ji,jj)**betas) )  &   ! except solid precip intercepted by sea-ice 
    232                &   - rdmsnif(ji,jj) * r1_rdtice                       &   ! freshwaterflux due to snow melting  
     234               &   - rdm_snw(ji,jj) * r1_rdtice                       &   ! freshwaterflux due to snow melting  
    233235               &   + fmmec(ji,jj)                                         ! snow falling when ridging 
    234236 
     
    236238            !  computing salt exchanges at the ice/ocean interface 
    237239            !  sice should be the same as computed with the ice model 
    238             zfons =  ( soce_0(ji,jj) - sice_0(ji,jj) ) * rdmicif(ji,jj) * r1_rdtice  
     240            zfons =  ( soce_0(ji,jj) - sice_0(ji,jj) ) * rdm_ice(ji,jj) * r1_rdtice  
    239241            ! SOCE 
    240             zfons =  ( sss_m (ji,jj) - sice_0(ji,jj) ) * rdmicif(ji,jj) * r1_rdtice 
     242            zfons =  ( sss_m (ji,jj) - sice_0(ji,jj) ) * rdm_ice(ji,jj) * r1_rdtice 
    241243 
    242244            !CT useless            !  salt flux for constant salinity 
     
    266268      ELSE                         ! constant ice salinity: 
    267269         sfx (:,:) =              fseqv(:,:) + fsalt_res(:,:) + fsalt_rpo(:,:) + emp(:,:) 
     270      ENDIF 
     271      !-----------------------------------------------! 
     272      !   mass of snow and ice per unit area          ! 
     273      !-----------------------------------------------! 
     274      IF( nn_ice_embd /= 0 ) THEN                               ! embedded sea-ice (mass required) 
     275         snwice_mass_b(:,:) = snwice_mass(:,:)                  ! save mass from the previous ice time step 
     276         !                                                      ! new mass per unit area 
     277         snwice_mass  (:,:) = tms(:,:) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )  
     278         !                                                      ! time evolution of snow+ice mass 
     279         snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) / rdt_ice 
    268280      ENDIF 
    269281 
     
    404416      !                                      ! embedded sea ice 
    405417      IF( nn_ice_embd /= 0 ) THEN            ! mass exchanges between ice and ocean (case 1 or 2) set the snow+ice mass 
    406          snwice_mass  (:,:) = tms(:,:) * ( rhosn * hsnif(:,:) + rhoic * hicif(:,:)  ) * ( 1.0 - frld(:,:) ) 
     418         snwice_mass  (:,:) = tms(:,:) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:) ) 
    407419         snwice_mass_b(:,:) = snwice_mass(:,:) 
    408420      ELSE 
    409          snwice_mass  (:,:) = 0.e0           ! no mass exchanges 
    410          snwice_mass_b(:,:) = 0.e0           ! no mass exchanges 
    411       ENDIF 
    412       IF( nn_ice_embd == 2 .AND.             ! full embedment (case 2) & no restart :  
     421         snwice_mass  (:,:) = 0.0_wp         ! no mass exchanges 
     422         snwice_mass_b(:,:) = 0.0_wp         ! no mass exchanges 
     423      ENDIF 
     424      IF( nn_ice_embd == 2 .AND.          &  ! full embedment (case 2) & no restart :  
    413425         &   .NOT.ln_rstart ) THEN           ! deplete the initial ssh belew sea-ice area 
    414426         sshn(:,:) = sshn(:,:) - snwice_mass(:,:) * r1_rau0 
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/LIM_SRC_3/limthd.F90

    r3294 r3419  
    88   !!            3.0  ! 2005-11 (M. Vancoppenolle)  LIM-3 : Multi-layer thermodynamics + salinity variations 
    99   !!             -   ! 2007-04 (M. Vancoppenolle) add lim_thd_glohec, lim_thd_con_dh and lim_thd_con_dif 
    10    !!            3.2  ! 2009-07 (M. Vancoppenolle, Y. Aksenov, G. Madec) bug correction in rdmsnif 
     10   !!            3.2  ! 2009-07 (M. Vancoppenolle, Y. Aksenov, G. Madec) bug correction in rdm_snw 
    1111   !!            3.3  ! 2010-11 (G. Madec) corrected snow melting heat (due to factor betas) 
    1212   !!            4.0  ! 2011-02 (G. Madec) dynamical allocation 
     
    140140      ffltbif(:,:) = 0.e0   ! linked with fstric 
    141141      qfvbq  (:,:) = 0.e0   ! linked with fstric 
    142       rdmsnif(:,:) = 0.e0   ! variation of snow mass per unit area 
    143       rdmicif(:,:) = 0.e0   ! variation of ice mass per unit area 
     142      rdm_snw(:,:) = 0.e0   ! variation of snow mass per unit area 
     143      rdm_ice(:,:) = 0.e0   ! variation of ice mass per unit area 
    144144      hicifp (:,:) = 0.e0   ! daily thermodynamic ice production.  
    145145      fsbri  (:,:) = 0.e0   ! brine flux contribution to salt flux to the ocean 
     
    284284            CALL tab_2d_1d( nbpb, fbif_1d    (1:nbpb), fbif       , jpi, jpj, npb(1:nbpb) ) 
    285285            CALL tab_2d_1d( nbpb, qldif_1d   (1:nbpb), qldif      , jpi, jpj, npb(1:nbpb) ) 
    286             CALL tab_2d_1d( nbpb, rdmicif_1d (1:nbpb), rdmicif    , jpi, jpj, npb(1:nbpb) ) 
    287             CALL tab_2d_1d( nbpb, rdmsnif_1d (1:nbpb), rdmsnif    , jpi, jpj, npb(1:nbpb) ) 
     286            CALL tab_2d_1d( nbpb, rdmicif_1d (1:nbpb), rdm_ice    , jpi, jpj, npb(1:nbpb) ) 
     287            CALL tab_2d_1d( nbpb, rdmsnif_1d (1:nbpb), rdm_snw    , jpi, jpj, npb(1:nbpb) ) 
    288288            CALL tab_2d_1d( nbpb, dmgwi_1d   (1:nbpb), dmgwi      , jpi, jpj, npb(1:nbpb) ) 
    289289            CALL tab_2d_1d( nbpb, qlbbq_1d   (1:nbpb), zqlbsbq    , jpi, jpj, npb(1:nbpb) ) 
     
    352352            CALL tab_1d_2d( nbpb, qldif  , npb, qldif_1d  (1:nbpb), jpi, jpj ) 
    353353            CALL tab_1d_2d( nbpb, qfvbq  , npb, qfvbq_1d  (1:nbpb), jpi, jpj ) 
    354             CALL tab_1d_2d( nbpb, rdmicif, npb, rdmicif_1d(1:nbpb), jpi, jpj ) 
    355             CALL tab_1d_2d( nbpb, rdmsnif, npb, rdmsnif_1d(1:nbpb), jpi, jpj ) 
     354            CALL tab_1d_2d( nbpb, rdm_ice, npb, rdmicif_1d(1:nbpb), jpi, jpj ) 
     355            CALL tab_1d_2d( nbpb, rdm_snw, npb, rdmsnif_1d(1:nbpb), jpi, jpj ) 
    356356            CALL tab_1d_2d( nbpb, dmgwi  , npb, dmgwi_1d  (1:nbpb), jpi, jpj ) 
    357357            CALL tab_1d_2d( nbpb, rdvosif, npb, dvsbq_1d  (1:nbpb), jpi, jpj ) 
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/LIM_SRC_3/limtrp.F90

    r3294 r3419  
    128128         zusnit = 1.0 / REAL( initad )  
    129129         IF( zcfl > 0.5 .AND. lwp )   & 
    130             WRITE(numout,*) 'lim_trp_2 : CFL violation at day ', nday, ', cfl = ', zcfl,   & 
     130            WRITE(numout,*) 'lim_trp  : CFL violation at day ', nday, ', cfl = ', zcfl,   & 
    131131               &                        ': the ice time stepping is split in two' 
    132132 
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/LIM_SRC_3/limupdate.F90

    r3294 r3419  
    622622                     + ze_s * v_s(ji,jj,jl) / rdt_ice 
    623623                  ! release mass 
    624                   rdmsnif(ji,jj) =  rdmsnif(ji,jj) + rhosn * v_s(ji,jj,jl) 
     624                  rdm_snw(ji,jj) =  rdm_snw(ji,jj) + rhosn * v_s(ji,jj,jl) 
    625625               ENDIF 
    626626            END DO 
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r3402 r3419  
    696696      !!---------------------------------------------------------------------- 
    697697      !  
    698       IF( nn_timing == 1 )   CALL timing_start('dia_wri_state') 
     698!     IF( nn_timing == 1 )   CALL timing_start('dia_wri_state') ! not sure this works for routines not called in first timestep 
    699699 
    700700      ! 0. Initialisation 
     
    793793#endif 
    794794        
    795       IF( nn_timing == 1 )   CALL timing_stop('dia_wri_state') 
     795!     IF( nn_timing == 1 )   CALL timing_stop('dia_wri_state') ! not sure this works for routines not called in first timestep 
    796796      !  
    797797 
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r3294 r3419  
    119119 
    120120   ! variables used in case of sea-ice 
    121    INTEGER, PUBLIC ::   ncomm_ice       !: communicator made by the processors with sea-ice 
     121   INTEGER, PUBLIC ::   ncomm_ice       !: communicator made by the processors with sea-ice (public so that it can be freed in limthd) 
     122   INTEGER ::   ngrp_iworld     !  group ID for the world processors (for rheology) 
    122123   INTEGER ::   ngrp_ice        !  group ID for the ice processors (for rheology) 
    123124   INTEGER ::   ndim_rank_ice   !  number of 'ice' processors 
     
    19771978      !!      ndim_rank_ice = number of processors with ice 
    19781979      !!      nrank_ice (ndim_rank_ice) = ice processors 
    1979       !!      ngrp_world = group ID for the world processors 
     1980      !!      ngrp_iworld = group ID for the world processors 
    19801981      !!      ngrp_ice = group ID for the ice processors 
    19811982      !!      ncomm_ice = communicator for the ice procs. 
     
    20262027 
    20272028      ! Create the world group 
    2028       CALL MPI_COMM_GROUP( mpi_comm_opa, ngrp_world, ierr ) 
     2029      CALL MPI_COMM_GROUP( mpi_comm_opa, ngrp_iworld, ierr ) 
    20292030 
    20302031      ! Create the ice group from the world group 
    2031       CALL MPI_GROUP_INCL( ngrp_world, ndim_rank_ice, nrank_ice, ngrp_ice, ierr ) 
     2032      CALL MPI_GROUP_INCL( ngrp_iworld, ndim_rank_ice, nrank_ice, ngrp_ice, ierr ) 
    20322033 
    20332034      ! Create the ice communicator , ie the pool of procs with sea-ice 
     
    20362037      ! Find proc number in the world of proc 0 in the north 
    20372038      ! The following line seems to be useless, we just comment & keep it as reminder 
    2038       ! CALL MPI_GROUP_TRANSLATE_RANKS(ngrp_ice,1,0,ngrp_world,n_ice_root,ierr) 
    2039       ! 
     2039      ! CALL MPI_GROUP_TRANSLATE_RANKS(ngrp_ice,1,0,ngrp_iworld,n_ice_root,ierr) 
     2040      ! 
     2041      CALL MPI_GROUP_FREE(ngrp_ice, ierr) 
     2042      CALL MPI_GROUP_FREE(ngrp_iworld, ierr) 
     2043 
    20402044      DEALLOCATE(kice, zwork) 
    20412045      ! 
Note: See TracChangeset for help on using the changeset viewer.