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 8061 for branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limmp.F90 – NEMO

Ignore:
Timestamp:
2017-05-24T10:02:23+02:00 (7 years ago)
Author:
vancop
Message:

Quick commit on empirical melt ponds

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limmp.F90

    r8060 r8061  
    8383      !!------------------------------------------------------------------- 
    8484      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    85       NAMELIST/namicemp/  ln_limMP, nn_limMP 
     85      NAMELIST/namicemp/  ln_pnd, nn_pnd_scheme, nn_pnd_cpl, rn_apnd 
    8686      !!------------------------------------------------------------------- 
    8787 
     
    9999         WRITE(numout,*) 'lim_mp_init : ice parameters for melt ponds' 
    100100         WRITE(numout,*) '~~~~~~~~~~~~' 
    101          WRITE(numout,*)'    Activate melt ponds                                         ln_limMP      = ', ln_limMP   
    102          WRITE(numout,*)'    Type of melt pond implementation (1=all,2=rad, 3=fw, 4=no)  nn_limMP      = ', nn_limMP   
     101         WRITE(numout,*)'    Activate melt ponds                                         ln_pnd        = ', ln_pnd 
     102         WRITE(numout,*)'    Type of melt pond scheme =0 presc, =1 empirical = 2 topo    nn_pnd_scheme = ', nn_pnd_scheme 
     103         WRITE(numout,*)'    Type of melt pond coupling =0 pass., =1 full, =2 rad, 3=fw  nn_pnd_cpl    = ', nn_pnd_cp 
     104         WRITE(numout,*)'    Prescribed pond fraction                                    rn_apnd       = ', rn_apnd 
    103105      ENDIF 
    104106      ! 
    105107   END SUBROUTINE lim_mp_init 
     108 
     109 
    106110 
    107111   SUBROUTINE lim_mp( kt ) 
     
    128132      IF( nn_timing == 1 )  CALL timing_start('lim_mp') 
    129133 
    130       CALL lim_mp_cesm ! test routine with hyper simple melt ponds 
    131  
    132       !CALL lim_mp_topo    (at_i, a_i,                                       & 
    133       !          &          vt_i, v_i, v_s,            t_i, s_i, a_ip_frac,  & 
    134       !          &          h_ip,     t_su) 
    135  
     134      SELECT CASE ( nn_pnd_scheme ) 
     135 
     136          CASE (1) 
     137 
     138             CALL lim_mp_cesm ! empirical melt ponds 
     139 
     140          CASE (2) 
     141 
     142             CALL lim_mp_topo    (at_i, a_i,                                       & 
     143                       &          vt_i, v_i, v_s,            t_i, s_i, a_ip_frac,  & 
     144                       &          h_ip,     t_su) 
     145 
     146      END SELECT 
    136147 
    137148      ! we should probably not aggregate here since we do it in lim_var_agg 
     
    142153 
    143154   END SUBROUTINE lim_mp  
     155 
     156 
    144157 
    145158   SUBROUTINE lim_mp_cesm 
     
    149162       !! ** Purpose    : Compute melt pond evolution 
    150163       !! 
    151        !! ** Method     : Accumulation of meltwater and exponential release 
     164       !! ** Method     : Empirical method. A fraction of meltwater is accumulated  
     165       !!                 in pond volume. It is then released exponentially when 
     166       !!                 surface is freezingAccumulation of meltwater and exponential release 
    152167       !! 
    153168       !! ** Tunable parameters : 
     
    155170       !!  
    156171       !! ** Note       : Stolen from CICE for quick test of the melt pond 
    157        !!                 interface 
     172       !!                 radiation and freshwater interfaces 
    158173       !! 
    159174       !! ** References : Holland, M. M. et al (J Clim 2012) 
     
    161176       !!------------------------------------------------------------------- 
    162177 
    163        INTEGER, POINTER, DIMENSION(:,:)    :: indxi             ! compressed indices for cells with ice melting 
    164        INTEGER, POINTER, DIMENSION(:,:)    :: indxj             ! 
     178       INTEGER, POINTER, DIMENSION(:    :: indxi             ! compressed indices for cells with ice melting 
     179       INTEGER, POINTER, DIMENSION(:    :: indxj             ! 
    165180 
    166181       REAL(wp), POINTER, DIMENSION(:,:)   :: zwfx_mlw          ! available meltwater for melt ponding 
     
    175190       REAL(wp)                            :: zhs               ! dummy snow depth 
    176191       REAL(wp)                            :: zTp               ! reference temperature 
    177        REAL(wp)                            :: zrexp             ! rate constant to refreeze melt ponds 
    178192       REAL(wp)                            :: zdTs              ! dummy temperature difference 
    179193       REAL(wp)                            :: z1_rhofw          ! inverse freshwater density 
    180194       REAL(wp)                            :: z1_zpnd_aspect    ! inverse pond aspect ratio 
    181195 
     196       INTEGER                             :: ji, jj, jl, ij    ! loop indices 
     197       INTEGER                             :: icells            ! size of dummy array 
     198 
    182199       !!------------------------------------------------------------------- 
    183200 
    184        CALL wrk_alloc( jpi,jpj, zwfx_mlw ) 
    185201       CALL wrk_alloc( jpi*jpj, indxi, indxj) 
     202       CALL wrk_alloc( jpi,jpj,     zwfx_mlw ) 
     203       CALL wrk_alloc( jpi,jpj,jpl, zrfrac   ) 
    186204 
    187205       z1_rhofw       = 1. / rhofw  
    188206       z1_zpnd_aspect = 1. / zpnd_aspect 
    189        zTp            = -2 + rt0. 
     207       zTp            = -2.  
    190208 
    191209       !------------------------------------------------------------------ 
     
    215233               IF ( a_i(ji,jj,jl) > epsi10 ) THEN 
    216234                  icells = icells + 1 
    217                   indxi(icells) = i 
    218                   indxj(icells) = j 
     235                  indxi(icells) = ji 
     236                  indxj(icells) = jj 
    219237               ENDIF 
    220238            END DO                 ! ji 
     
    231249            IF ( zhi < rn_himin) THEN   !--- Remove ponds on thin ice if ice is too thin 
    232250 
    233                wfx_pnd(ji,jj)   = wfx_pnd(ji,jj) + v_ip(ji,jj,jl) !--- Give freshwater to the ocean 
    234  
    235                a_ip(ji,jj,jl)      = 0._wp                        !--- Dump ponds 
     251               a_ip(ji,jj,jl)      = 0._wp                               !--- Dump ponds 
    236252               v_ip(ji,jj,jl)      = 0._wp 
    237253               a_ip_frac(ji,jj,jl) = 0._wp 
    238254               h_ip(ji,jj,jl)      = 0._wp 
    239255 
     256               IF ( ( nn_pnd_cpl .EQ. 1 ) .OR. ( nn_pnd_cpl .EQ. 3 ) ) & !--- Give freshwater to the ocean 
     257                  wfx_pnd(ji,jj)   = wfx_pnd(ji,jj) + v_ip(ji,jj,jl)  
     258 
     259 
    240260            ELSE                        !--- Update pond characteristics 
    241261 
    242262               !--- Add retained melt water 
    243                v_ip(ji,jj,jl) = v_ip(ji,jj,jl) + rfrac(ji,jj,jl) * z1_rhofw * zwfx_mlw(ji,jj) * a_i(ji,jj,jl) 
     263               v_ip(ji,jj,jl)      = v_ip(ji,jj,jl) + zrfrac(ji,jj,jl) * z1_rhofw * zwfx_mlw(ji,jj) * a_i(ji,jj,jl) * rdt_ice 
    244264 
    245265               !--- Shrink pond due to refreezing 
    246                zdTs = MAX ( zTp - t_su(ji,jj,jl) , 0. ) 
     266               zdTs                = MAX ( zTp - t_su(ji,jj,jl) + rt0 , 0. ) 
    247267                
    248                v_ip(ji,jj,jl) = v_ip(ji,jj,jl) * EXP( rexp * zdTs / zTp ) 
    249             
     268               zvpold              = v_ip(ji,jj,jl) 
     269 
     270               v_ip(ji,jj,jl)      = v_ip(ji,jj,jl) * EXP( zrexp * zdTs / zTp ) 
     271 
     272               !--- Dump meltwater due to refreezing ( of course this is wrong 
     273               !--- but this parameterization is too simple ) 
     274               IF ( ( nn_pnd_cpl .EQ. 1 ) .OR. ( nn_pnd_cpl .EQ. 3 ) ) THEN 
     275 
     276                  wfx_pnd(ji,jj)   = wfx_pnd(ji,jj) + rhofw * ( v_ip(ji,jj,jl) - zvpold ) * r1_rdtice 
     277 
     278               ENDIF 
     279 
    250280               a_ip_frac(ji,jj,jl) = MIN( 1._wp , SQRT( v_ip(ji,jj,jl) * z1_zpnd_aspect / a_i(ji,jj,jl) ) ) 
    251281 
     
    263293            ENDIF 
    264294 
    265          END DO 
    266  
    267       END DO ! jpl 
     295          END DO 
     296 
     297       END DO ! jpl 
     298 
     299       !--- Remove retained meltwater from surface fluxes  
     300 
     301       IF ( ( nn_pnd_cpl .EQ. 1 ) .OR. ( nn_pnd_cpl .EQ. 3 ) ) THEN 
     302 
     303           wfx_snw(:,:) = wfx_snw(:,:) *  ( 1. - zrmin - ( zrmax - zrmin ) * at_i(:,:) ) 
     304 
     305           wfx_sum(:,:) = wfx_sum(:,:) *  ( 1. - zrmin - ( zrmax - zrmin ) * at_i(:,:) ) 
     306 
     307       ENDIF 
    268308 
    269309   END SUBROUTINE lim_mp_cesm 
Note: See TracChangeset for help on using the changeset viewer.