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 9750 for NEMO/trunk/src/ICE – NEMO

Changeset 9750 for NEMO/trunk/src/ICE


Ignore:
Timestamp:
2018-06-06T14:49:34+02:00 (6 years ago)
Author:
clem
Message:

make ice ponds working in debug mode

Location:
NEMO/trunk/src/ICE
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/ICE/ice1d.F90

    r9604 r9750  
    112112   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   fc_bo_i       !: Bottom  Conduction flux  
    113113   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_s_tot      !: Snow accretion/ablation        [m] 
    114    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_surf     !: Ice surface accretion/ablation [m] 
     114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_sum      !: Ice surface ablation [m] 
     115   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_itm      !: Ice internal ablation [m] 
     116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_bom      !: Ice bottom ablation  [m] 
     117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_bog      !: Ice bottom accretion  [m] 
    115118   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_sub      !: Ice surface sublimation [m] 
    116    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_i_bott     !: Ice bottom accretion/ablation  [m] 
    117119   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_s_mlt      !: Snow melt [m] 
    118120   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   dh_snowice    !: Snow ice formation             [m of ice] 
     
    203205      ! 
    204206      ii = ii + 1 
    205       ALLOCATE( t_su_1d  (jpij) , t_si_1d  (jpij) , a_i_1d    (jpij) , a_ib_1d(jpij) ,                  & 
    206          &      h_i_1d   (jpij) , h_ib_1d  (jpij) , h_s_1d    (jpij) , fc_su  (jpij) , fc_bo_i(jpij) ,  &     
    207          &      dh_s_tot (jpij) , dh_i_surf(jpij) , dh_i_sub  (jpij) ,                                  &     
    208          &      dh_i_bott(jpij) , dh_s_mlt (jpij) , dh_snowice(jpij) , s_i_1d (jpij) , s_i_new(jpij) ,  & 
    209          &      a_ip_1d  (jpij) , v_ip_1d  (jpij) , v_i_1d    (jpij) , v_s_1d (jpij) ,                  & 
    210          &      h_ip_1d  (jpij) , a_ip_frac_1d(jpij) ,                                                  & 
    211          &      sv_i_1d  (jpij) , oa_i_1d (jpij) , STAT=ierr(ii) ) 
     207      ALLOCATE( t_su_1d (jpij) , t_si_1d (jpij) , a_i_1d    (jpij) , a_ib_1d (jpij) ,                   & 
     208         &      h_i_1d  (jpij) , h_ib_1d (jpij) , h_s_1d    (jpij) , fc_su   (jpij) , fc_bo_i (jpij) ,  &     
     209         &      dh_s_tot(jpij) , dh_i_sum(jpij) , dh_i_itm  (jpij) , dh_i_bom(jpij) , dh_i_bog(jpij) ,  &     
     210         &      dh_i_sub(jpij) , dh_s_mlt(jpij) , dh_snowice(jpij) , s_i_1d  (jpij) , s_i_new (jpij) ,  & 
     211         &      a_ip_1d (jpij) , v_ip_1d (jpij) , v_i_1d    (jpij) , v_s_1d  (jpij) ,                   & 
     212         &      h_ip_1d (jpij) , a_ip_frac_1d(jpij) ,                                                   & 
     213         &      sv_i_1d (jpij) , oa_i_1d (jpij) , STAT=ierr(ii) ) 
    212214      ! 
    213215      ii = ii + 1 
  • NEMO/trunk/src/ICE/icethd.F90

    r9656 r9750  
    7777      !!                - call ice_thd_sal  for ice desalination 
    7878      !!                - call ice_thd_temp to  retrieve temperature from ice enthalpy 
    79       !!                - call ice_thd_lam for extra lateral ice melt if active virtual thickness distribution 
     79      !!                - call ice_thd_mono for extra lateral ice melt if active virtual thickness distribution 
    8080      !!                - call ice_thd_da   for lateral ice melt 
    8181      !!             - back to the geographic grid 
     
    224224            !                                                       ! --- & Change units of e_i, e_s from J/m2 to J/m3 --- ! 
    225225            ! 
    226             s_i_new   (1:npti) = 0._wp ; dh_s_tot (1:npti) = 0._wp  ! --- some init --- !  (important to have them here)  
    227             dh_i_surf (1:npti) = 0._wp ; dh_i_bott(1:npti) = 0._wp 
    228             dh_snowice(1:npti) = 0._wp ; dh_i_sub (1:npti) = 0._wp ; dh_s_mlt(1:npti) = 0._wp 
     226            s_i_new   (1:npti) = 0._wp ; dh_s_tot(1:npti) = 0._wp  ! --- some init --- !  (important to have them here)  
     227            dh_i_sum  (1:npti) = 0._wp ; dh_i_bom(1:npti) = 0._wp ; dh_i_itm  (1:npti) = 0._wp  
     228            dh_i_sub  (1:npti) = 0._wp ; dh_i_bog(1:npti) = 0._wp 
     229            dh_snowice(1:npti) = 0._wp ; dh_s_mlt(1:npti) = 0._wp 
    229230            ! 
    230231            IF( ln_icedH ) THEN                                     ! --- growing/melting --- ! 
     
    239240                              CALL ice_thd_temp                     ! --- temperature update --- ! 
    240241            ! 
    241 !!gm please create a new logical (l_thd_lam or a better explicit name) set one for all in icestp.F90 module 
    242 !!gm        l_thd_lam = ln_icedH .AND. ( ( nn_virtual_itd == 1 .OR. nn_virtual_itd == 4 ) .AND. jpl == 1 ) 
     242!!gm please create a new logical (l_thd_mono or a better explicit name) set one for all in icestp.F90 module 
     243!!gm        l_thd_mono = ln_icedH .AND. ( ( nn_virtual_itd == 1 .OR. nn_virtual_itd == 4 ) .AND. jpl == 1 ) 
    243244!!gm        by the way, the different options associated with nn_virtual_itd =1 to 4  are quite impossible to identify 
    244245!!gm        more comment to add when ready the namelist, with an explicit print in the ocean.output 
    245246            IF( ln_icedH ) THEN 
    246247               IF ( ( nn_virtual_itd == 1 .OR. nn_virtual_itd == 3 ) .AND. jpl == 1 ) THEN 
    247                               CALL ice_thd_lam                      ! --- extra lateral melting if virtual_itd --- ! 
     248                              CALL ice_thd_mono                      ! --- extra lateral melting if virtual_itd --- ! 
    248249               END IF 
    249250            END IF 
     
    307308 
    308309 
    309    SUBROUTINE ice_thd_lam 
    310       !!----------------------------------------------------------------------- 
    311       !!                   ***  ROUTINE ice_thd_lam ***  
     310   SUBROUTINE ice_thd_mono 
     311      !!----------------------------------------------------------------------- 
     312      !!                   ***  ROUTINE ice_thd_mono ***  
    312313      !!                  
    313314      !! ** Purpose :   Lateral melting in case virtual_itd 
     
    321322      ! 
    322323      DO ji = 1, npti 
    323          zdh_mel = MIN( 0._wp, dh_i_surf(ji) + dh_i_bott(ji) + dh_snowice(ji) + dh_i_sub(ji) ) 
     324         zdh_mel = MIN( 0._wp, dh_i_itm(ji) + dh_i_sum(ji) + dh_i_bom(ji) + dh_snowice(ji) + dh_i_sub(ji) ) 
    324325         IF( zdh_mel < 0._wp .AND. a_i_1d(ji) > 0._wp )  THEN 
    325326            zvi          = a_i_1d(ji) * h_i_1d(ji) 
     
    338339      END DO 
    339340      ! 
    340    END SUBROUTINE ice_thd_lam 
     341   END SUBROUTINE ice_thd_mono 
    341342 
    342343 
  • NEMO/trunk/src/ICE/icethd_dh.F90

    r9604 r9750  
    333333               zfmdt          = - zdeltah(ji,jk) * rhoic              ! Mass flux x time step > 0 
    334334                          
    335                dh_i_surf(ji)  = dh_i_surf(ji) + zdeltah(ji,jk)        ! Cumulate surface melt 
     335               dh_i_itm(ji)   = dh_i_itm(ji) + zdeltah(ji,jk)         ! Cumulate internal melting 
    336336                
    337337               zfmdt          = - rhoic * zdeltah(ji,jk)              ! Recompute mass flux [kg/m2, >0] 
     
    357357               zq_su(ji)      = MAX( 0._wp , zq_su(ji) - zdeltah(ji,jk) * rhoic * zdE ) ! update available heat 
    358358                
    359                dh_i_surf(ji)  = dh_i_surf(ji) + zdeltah(ji,jk)        ! Cumulate surface melt 
     359               dh_i_sum(ji)   = dh_i_sum(ji) + zdeltah(ji,jk)         ! Cumulate surface melt 
    360360                
    361361               zfmdt          = - rhoic * zdeltah(ji,jk)              ! Recompute mass flux [kg/m2, >0] 
     
    404404      ! update ice thickness 
    405405      DO ji = 1, npti 
    406          h_i_1d(ji) =  MAX( 0._wp , h_i_1d(ji) + dh_i_surf(ji) + dh_i_sub(ji) ) 
     406         h_i_1d(ji) =  MAX( 0._wp , h_i_1d(ji) + dh_i_sum(ji) + dh_i_itm(ji) + dh_i_sub(ji) ) 
    407407      END DO 
    408408 
     
    422422      ! If salinity varies in time, an iterative procedure is required, because 
    423423      ! the involved quantities are inter-dependent. 
    424       ! Basal growth (dh_i_bott) depends upon new ice specific enthalpy (zEi), 
    425       ! which depends on forming ice salinity (s_i_new), which depends on dh/dt (dh_i_bott) 
     424      ! Basal growth (dh_i_bog) depends upon new ice specific enthalpy (zEi), 
     425      ! which depends on forming ice salinity (s_i_new), which depends on dh/dt (dh_i_bog) 
    426426      ! -> need for an iterative procedure, which converges quickly 
    427427 
     
    437437               !--- zswi12 if 2.0e-8 < dh/dt < 3.6e-7  
    438438               !--- zswi2  if dh/dt > 3.6e-7 
    439                zgrr     = MIN( 1.0e-3, MAX ( dh_i_bott(ji) * r1_rdtice , epsi10 ) ) 
     439               zgrr     = MIN( 1.0e-3, MAX ( dh_i_bog(ji) * r1_rdtice , epsi10 ) ) 
    440440               zswi2    = MAX( 0._wp , SIGN( 1._wp , zgrr - 3.6e-7 ) ) 
    441441               zswi12   = MAX( 0._wp , SIGN( 1._wp , zgrr - 2.0e-8 ) ) * ( 1.0 - zswi2 ) 
     
    457457               zdE           = zEi - zEw                                                              ! Specific enthalpy difference (J/kg, <0) 
    458458 
    459                dh_i_bott(ji) = rdt_ice * MAX( 0._wp , zf_tt(ji) / ( zdE * rhoic ) ) 
     459               dh_i_bog(ji) = rdt_ice * MAX( 0._wp , zf_tt(ji) / ( zdE * rhoic ) ) 
    460460                
    461461            END DO 
    462462            ! Contribution to Energy and Salt Fluxes                                     
    463             zfmdt          = - rhoic * dh_i_bott(ji)                                                  ! Mass flux x time step (kg/m2, < 0) 
     463            zfmdt          = - rhoic * dh_i_bog(ji)                                                   ! Mass flux x time step (kg/m2, < 0) 
    464464             
    465465            hfx_thd_1d(ji) = hfx_thd_1d(ji) + zfmdt * a_i_1d(ji) * zEw * r1_rdtice                           ! Heat flux to the ocean [W.m-2], >0 
    466466            hfx_bog_1d(ji) = hfx_bog_1d(ji) - zfmdt * a_i_1d(ji) * zdE * r1_rdtice                           ! Heat flux used in this process [W.m-2], <0 
    467467             
    468             sfx_bog_1d(ji) = sfx_bog_1d(ji) - rhoic * a_i_1d(ji) * dh_i_bott(ji) * s_i_new(ji) * r1_rdtice   ! Salt flux, <0 
    469  
    470             wfx_bog_1d(ji) = wfx_bog_1d(ji) - rhoic * a_i_1d(ji) * dh_i_bott(ji) * r1_rdtice                 ! Mass flux, <0 
     468            sfx_bog_1d(ji) = sfx_bog_1d(ji) - rhoic * a_i_1d(ji) * dh_i_bog(ji) * s_i_new(ji) * r1_rdtice    ! Salt flux, <0 
     469 
     470            wfx_bog_1d(ji) = wfx_bog_1d(ji) - rhoic * a_i_1d(ji) * dh_i_bog(ji) * r1_rdtice                  ! Mass flux, <0 
    471471 
    472472            ! update heat content (J.m-2) and layer thickness 
    473             eh_i_old(ji,nlay_i+1) = eh_i_old(ji,nlay_i+1) + dh_i_bott(ji) * (-zEi * rhoic) 
    474             h_i_old (ji,nlay_i+1) = h_i_old (ji,nlay_i+1) + dh_i_bott(ji) 
     473            eh_i_old(ji,nlay_i+1) = eh_i_old(ji,nlay_i+1) + dh_i_bog(ji) * (-zEi * rhoic) 
     474            h_i_old (ji,nlay_i+1) = h_i_old (ji,nlay_i+1) + dh_i_bog(ji) 
    475475 
    476476         ENDIF 
     
    495495                                                                    ! this should normally not happen, but sometimes, heat diffusion leads to this 
    496496 
    497                   dh_i_bott (ji)    = dh_i_bott(ji) + zdeltah(ji,jk) 
     497                  dh_i_itm (ji)     = dh_i_itm(ji) + zdeltah(ji,jk) 
    498498 
    499499                  zfmdt             = - zdeltah(ji,jk) * rhoic      ! Mass flux x time step > 0 
     
    523523                  zq_bo(ji)       = MAX( 0._wp , zq_bo(ji) - zdeltah(ji,jk) * rhoic * zdE )   ! update available heat. MAX is necessary for roundup errors 
    524524 
    525                   dh_i_bott(ji)   = dh_i_bott(ji) + zdeltah(ji,jk)                            ! Update basal melt 
     525                  dh_i_bom(ji)    = dh_i_bom(ji) + zdeltah(ji,jk)                            ! Update basal melt 
    526526 
    527527                  zfmdt           = - zdeltah(ji,jk) * rhoic                                  ! Mass flux x time step > 0 
     
    549549      ! -------------------------- 
    550550      DO ji = 1, npti 
    551          h_i_1d(ji) = MAX( 0._wp , h_i_1d(ji) + dh_i_bott(ji) ) 
     551         h_i_1d(ji) = MAX( 0._wp , h_i_1d(ji) + dh_i_bog(ji) + dh_i_bom(ji) ) 
    552552      END DO   
    553553 
  • NEMO/trunk/src/ICE/icethd_pnd.F90

    r9656 r9750  
    157157            ! 
    158158            ! available meltwater for melt ponding [m, >0] and fraction 
    159             zdv_mlt = -( dh_i_surf(ji)*rhoic + dh_s_mlt(ji)*rhosn ) * z1_rhofw * a_i_1d(ji) 
     159            zdv_mlt = -( dh_i_sum(ji)*rhoic + dh_s_mlt(ji)*rhosn ) * z1_rhofw * a_i_1d(ji) 
    160160            zfr_mlt = zrmin + ( zrmax - zrmin ) * a_i_1d(ji)  ! from CICE doc 
    161161            !zfr_mlt = zrmin + zrmax * a_i_1d(ji)             ! from Holland paper  
  • NEMO/trunk/src/ICE/icethd_sal.F90

    r9656 r9750  
    7777            !--------------------------------------------------------- 
    7878            IF( h_i_1d(ji) > 0._wp ) THEN 
    79                zs_sni   = sss_1d(ji) * ( rhoic - rhosn ) * r1_rhoic                                 ! Salinity of snow ice 
    80                zs_i_si = ( zs_sni      - s_i_1d(ji) ) *             dh_snowice(ji) / h_i_1d(ji) ! snow-ice     
    81                zs_i_bg = ( s_i_new(ji) - s_i_1d(ji) ) * MAX( 0._wp, dh_i_bott(ji) ) / h_i_1d(ji) ! bottom growth 
     79               zs_sni   = sss_1d(ji) * ( rhoic - rhosn ) * r1_rhoic                 ! Salinity of snow ice 
     80               zs_i_si = ( zs_sni      - s_i_1d(ji) ) * dh_snowice(ji) / h_i_1d(ji) ! snow-ice     
     81               zs_i_bg = ( s_i_new(ji) - s_i_1d(ji) ) * dh_i_bog  (ji) / h_i_1d(ji) ! bottom growth 
    8282               ! Update salinity (nb: salt flux already included in icethd_dh) 
    8383               s_i_1d(ji) = s_i_1d(ji) + zs_i_bg + zs_i_si 
  • NEMO/trunk/src/ICE/iceupdate.F90

    r9604 r9750  
    263263      IF( iom_use('hfxbog'     ) )   CALL iom_put ("hfxbog"     , hfx_bog             )   ! heat flux used for ice bottom growth  
    264264      IF( iom_use('hfxbom'     ) )   CALL iom_put ("hfxbom"     , hfx_bom             )   ! heat flux used for ice bottom melt 
    265       IF( iom_use('hfxsum'     ) )   CALL iom_put ("hfxsum"     , hfx_sum             )   ! heat flux used for ice surface growth 
     265      IF( iom_use('hfxsum'     ) )   CALL iom_put ("hfxsum"     , hfx_sum             )   ! heat flux used for ice surface melt 
    266266      IF( iom_use('hfxopw'     ) )   CALL iom_put ("hfxopw"     , hfx_opw             )   ! heat flux used for ice formation in open water 
    267267      IF( iom_use('hfxdif'     ) )   CALL iom_put ("hfxdif"     , hfx_dif             )   ! heat flux used for ice temperature change 
Note: See TracChangeset for help on using the changeset viewer.