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 14072 for NEMO/trunk/src/ICE/icevar.F90 – NEMO

Ignore:
Timestamp:
2020-12-04T08:48:38+01:00 (4 years ago)
Author:
laurent
Message:

Merging branch "2020/dev_r13648_ASINTER-04_laurent_bulk_ice", ticket #2369

File:
1 edited

Legend:

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

    r14005 r14072  
    3434   !!                        - st_i(jpi,jpj) 
    3535   !!                        - et_s(jpi,jpj)  total snow heat content 
    36    !!                        - et_i(jpi,jpj)  total ice thermal content  
     36   !!                        - et_i(jpi,jpj)  total ice thermal content 
    3737   !!                        - sm_i(jpi,jpj)  mean ice salinity 
    3838   !!                        - tm_i(jpi,jpj)  mean ice temperature 
     
    5555   !!---------------------------------------------------------------------- 
    5656   USE dom_oce        ! ocean space and time domain 
    57    USE phycst         ! physical constants (ocean directory)  
     57   USE phycst         ! physical constants (ocean directory) 
    5858   USE sbc_oce , ONLY : sss_m, ln_ice_embd, nn_fsbc 
    5959   USE ice            ! sea-ice: variables 
     
    6767   PRIVATE 
    6868 
    69    PUBLIC   ice_var_agg           
    70    PUBLIC   ice_var_glo2eqv       
    71    PUBLIC   ice_var_eqv2glo       
    72    PUBLIC   ice_var_salprof       
    73    PUBLIC   ice_var_salprof1d     
     69   PUBLIC   ice_var_agg 
     70   PUBLIC   ice_var_glo2eqv 
     71   PUBLIC   ice_var_eqv2glo 
     72   PUBLIC   ice_var_salprof 
     73   PUBLIC   ice_var_salprof1d 
    7474   PUBLIC   ice_var_zapsmall 
    7575   PUBLIC   ice_var_zapneg 
    7676   PUBLIC   ice_var_roundoff 
    77    PUBLIC   ice_var_bv            
    78    PUBLIC   ice_var_enthalpy            
     77   PUBLIC   ice_var_bv 
     78   PUBLIC   ice_var_enthalpy 
    7979   PUBLIC   ice_var_sshdyn 
    8080   PUBLIC   ice_var_itd 
     
    108108      !!                ***  ROUTINE ice_var_agg  *** 
    109109      !! 
    110       !! ** Purpose :   aggregates ice-thickness-category variables to  
     110      !! ** Purpose :   aggregates ice-thickness-category variables to 
    111111      !!              all-ice variables, i.e. it turns VGLO into VAGG 
    112112      !!------------------------------------------------------------------- 
     
    130130      vt_il(:,:) = SUM( v_il(:,:,:), dim=3 ) 
    131131      ! 
    132       ato_i(:,:) = 1._wp - at_i(:,:)         ! open water fraction   
     132      ato_i(:,:) = 1._wp - at_i(:,:)         ! open water fraction 
    133133      ! 
    134134      !!GS: tm_su always needed by ABL over sea-ice 
     
    155155         hm_i(:,:) = vt_i(:,:) * z1_at_i(:,:) 
    156156         hm_s(:,:) = vt_s(:,:) * z1_at_i(:,:) 
    157          !          
     157         ! 
    158158         !                          ! mean temperature (K), salinity and age 
    159159         tm_si(:,:) = SUM( t_si(:,:,:) * a_i(:,:,:) , dim=3 ) * z1_at_i(:,:) 
     
    182182         WHERE( at_ip(:,:) > epsi20 )   ;   hm_ip(:,:) = vt_ip(:,:) / at_ip(:,:)   ;   hm_il(:,:) = vt_il(:,:) / at_ip(:,:) 
    183183         ELSEWHERE                      ;   hm_ip(:,:) = 0._wp                     ;   hm_il(:,:) = 0._wp 
    184          END WHERE          
     184         END WHERE 
    185185         ! 
    186186         DEALLOCATE( z1_vt_i , z1_vt_s ) 
     
    197197      !!                ***  ROUTINE ice_var_glo2eqv *** 
    198198      !! 
    199       !! ** Purpose :   computes equivalent variables as function of   
     199      !! ** Purpose :   computes equivalent variables as function of 
    200200      !!              global variables, i.e. it turns VGLO into VEQV 
    201201      !!------------------------------------------------------------------- 
     
    210210      !!------------------------------------------------------------------- 
    211211 
    212 !!gm Question 2:  It is possible to define existence of sea-ice in a common way between  
     212!!gm Question 2:  It is possible to define existence of sea-ice in a common way between 
    213213!!                ice area and ice volume ? 
    214214!!                the idea is to be able to define one for all at the begining of this routine 
     
    234234 
    235235      zhmax    =          hi_max(jpl) 
    236       z1_zhmax =  1._wp / hi_max(jpl)                
     236      z1_zhmax =  1._wp / hi_max(jpl) 
    237237      WHERE( h_i(:,:,jpl) > zhmax )   ! bound h_i by hi_max (i.e. 99 m) with associated update of ice area 
    238238         h_i   (:,:,jpl) = zhmax 
    239          a_i   (:,:,jpl) = v_i(:,:,jpl) * z1_zhmax  
     239         a_i   (:,:,jpl) = v_i(:,:,jpl) * z1_zhmax 
    240240         z1_a_i(:,:,jpl) = zhmax * z1_v_i(:,:,jpl) 
    241241      END WHERE 
    242242      !                                           !--- snow thickness 
    243243      h_s(:,:,:) = v_s (:,:,:) * z1_a_i(:,:,:) 
    244       !                                           !--- ice age       
     244      !                                           !--- ice age 
    245245      o_i(:,:,:) = oa_i(:,:,:) * z1_a_i(:,:,:) 
    246       !                                           !--- pond and lid thickness       
     246      !                                           !--- pond and lid thickness 
    247247      h_ip(:,:,:) = v_ip(:,:,:) * z1_a_ip(:,:,:) 
    248248      h_il(:,:,:) = v_il(:,:,:) * z1_a_ip(:,:,:) 
     
    258258      a_ip_eff = MIN( a_ip_eff, 1._wp - za_s_fra )   ! make sure (a_ip_eff + a_s_fra) <= 1 
    259259      ! 
    260       !                                           !---  salinity (with a minimum value imposed everywhere)      
     260      !                                           !---  salinity (with a minimum value imposed everywhere) 
    261261      IF( nn_icesal == 2 ) THEN 
    262262         WHERE( v_i(:,:,:) > epsi20 )   ;   s_i(:,:,:) = MAX( rn_simin , MIN( rn_simax, sv_i(:,:,:) * z1_v_i(:,:,:) ) ) 
     
    272272      DO jl = 1, jpl 
    273273         DO_3D( 1, 1, 1, 1, 1, nlay_i ) 
    274             IF ( v_i(ji,jj,jl) > epsi20 ) THEN     !--- icy area  
     274            IF ( v_i(ji,jj,jl) > epsi20 ) THEN     !--- icy area 
    275275               ! 
    276276               ze_i             =   e_i (ji,jj,jk,jl) * z1_v_i(ji,jj,jl) * zlay_i             ! Energy of melting e(S,T) [J.m-3] 
     
    300300      END DO 
    301301      ! 
    302       ! integrated values  
     302      ! integrated values 
    303303      vt_i (:,:) = SUM( v_i , dim=3 ) 
    304304      vt_s (:,:) = SUM( v_s , dim=3 ) 
     
    312312      !!                ***  ROUTINE ice_var_eqv2glo *** 
    313313      !! 
    314       !! ** Purpose :   computes global variables as function of  
     314      !! ** Purpose :   computes global variables as function of 
    315315      !!              equivalent variables,  i.e. it turns VEQV into VGLO 
    316316      !!------------------------------------------------------------------- 
     
    329329      !!                ***  ROUTINE ice_var_salprof *** 
    330330      !! 
    331       !! ** Purpose :   computes salinity profile in function of bulk salinity      
    332       !! 
    333       !! ** Method  : If bulk salinity greater than zsi1,  
     331      !! ** Purpose :   computes salinity profile in function of bulk salinity 
     332      !! 
     333      !! ** Method  : If bulk salinity greater than zsi1, 
    334334      !!              the profile is assumed to be constant (S_inf) 
    335335      !!              If bulk salinity lower than zsi0, 
     
    348348      !!------------------------------------------------------------------- 
    349349 
    350 !!gm Question: Remove the option 3 ?  How many years since it last use ?  
     350!!gm Question: Remove the option 3 ?  How many years since it last use ? 
    351351 
    352352      SELECT CASE ( nn_icesal ) 
     
    369369            END DO 
    370370         END DO 
    371          !                                      ! Slope of the linear profile  
     371         !                                      ! Slope of the linear profile 
    372372         WHERE( h_i(:,:,:) > epsi20 )   ;   z_slope_s(:,:,:) = 2._wp * s_i(:,:,:) / h_i(:,:,:) 
    373373         ELSEWHERE                      ;   z_slope_s(:,:,:) = 0._wp 
     
    379379               zalpha(ji,jj,jl) = MAX(  0._wp , MIN( ( zsi1 - s_i(ji,jj,jl) ) * z1_dS , 1._wp )  ) 
    380380               !                             ! force a constant profile when SSS too low (Baltic Sea) 
    381                IF( 2._wp * s_i(ji,jj,jl) >= sss_m(ji,jj) )   zalpha(ji,jj,jl) = 0._wp   
     381               IF( 2._wp * s_i(ji,jj,jl) >= sss_m(ji,jj) )   zalpha(ji,jj,jl) = 0._wp 
    382382            END_2D 
    383383         END DO 
     
    448448         ALLOCATE( z_slope_s(jpij), zalpha(jpij) ) 
    449449         ! 
    450          !                                      ! Slope of the linear profile  
     450         !                                      ! Slope of the linear profile 
    451451         WHERE( h_i_1d(1:npti) > epsi20 )   ;   z_slope_s(1:npti) = 2._wp * s_i_1d(1:npti) / h_i_1d(1:npti) 
    452452         ELSEWHERE                          ;   z_slope_s(1:npti) = 0._wp 
    453453         END WHERE 
    454           
     454 
    455455         z1_dS = 1._wp / ( zsi1 - zsi0 ) 
    456456         DO ji = 1, npti 
     
    557557         END_2D 
    558558         ! 
    559       END DO  
     559      END DO 
    560560 
    561561      ! to be sure that at_i is the sum of a_i(jl) 
     
    648648         END_2D 
    649649         ! 
    650       END DO  
     650      END DO 
    651651      ! 
    652652      WHERE( pato_i(:,:)   < 0._wp )   pato_i(:,:)   = 0._wp 
     
    693693      ! 
    694694   END SUBROUTINE ice_var_roundoff 
    695     
     695 
    696696 
    697697   SUBROUTINE ice_var_bv 
     
    713713      DO jl = 1, jpl 
    714714         DO jk = 1, nlay_i 
    715             WHERE( t_i(:,:,jk,jl) < rt0 - epsi10 )    
     715            WHERE( t_i(:,:,jk,jl) < rt0 - epsi10 ) 
    716716               bv_i(:,:,jl) = bv_i(:,:,jl) - rTmlt * sz_i(:,:,jk,jl) * r1_nlay_i / ( t_i(:,:,jk,jl) - rt0 ) 
    717717            END WHERE 
     
    727727   SUBROUTINE ice_var_enthalpy 
    728728      !!------------------------------------------------------------------- 
    729       !!                   ***  ROUTINE ice_var_enthalpy ***  
    730       !!                  
     729      !!                   ***  ROUTINE ice_var_enthalpy *** 
     730      !! 
    731731      !! ** Purpose :   Computes sea ice energy of melting q_i (J.m-3) from temperature 
    732732      !! 
     
    734734      !!------------------------------------------------------------------- 
    735735      INTEGER  ::   ji, jk   ! dummy loop indices 
    736       REAL(wp) ::   ztmelts  ! local scalar  
     736      REAL(wp) ::   ztmelts  ! local scalar 
    737737      !!------------------------------------------------------------------- 
    738738      ! 
     
    741741            ztmelts      = - rTmlt  * sz_i_1d(ji,jk) 
    742742            t_i_1d(ji,jk) = MIN( t_i_1d(ji,jk), ztmelts + rt0 ) ! Force t_i_1d to be lower than melting point => likely conservation issue 
    743                                                                 !   (sometimes zdf scheme produces abnormally high temperatures)    
     743                                                                !   (sometimes zdf scheme produces abnormally high temperatures) 
    744744            e_i_1d(ji,jk) = rhoi * ( rcpi  * ( ztmelts - ( t_i_1d(ji,jk) - rt0 ) )           & 
    745745               &                   + rLfus * ( 1._wp - ztmelts / ( t_i_1d(ji,jk) - rt0 ) )   & 
     
    755755   END SUBROUTINE ice_var_enthalpy 
    756756 
    757     
     757 
    758758   FUNCTION ice_var_sshdyn(pssh, psnwice_mass, psnwice_mass_b) 
    759759      !!--------------------------------------------------------------------- 
    760760      !!                   ***  ROUTINE ice_var_sshdyn  *** 
    761       !!                      
     761      !! 
    762762      !! ** Purpose :  compute the equivalent ssh in lead when sea ice is embedded 
    763763      !! 
     
    765765      !! 
    766766      !! ** Reference : Jean-Michel Campin, John Marshall, David Ferreira, 
    767       !!                Sea ice-ocean coupling using a rescaled vertical coordinate z*,  
     767      !!                Sea ice-ocean coupling using a rescaled vertical coordinate z*, 
    768768      !!                Ocean Modelling, Volume 24, Issues 1-2, 2008 
    769769      !!---------------------------------------------------------------------- 
     
    783783      ! compute ice load used to define the equivalent ssh in lead 
    784784      IF( ln_ice_embd ) THEN 
    785          !                                             
     785         ! 
    786786         ! average interpolation coeff as used in dynspg = (1/nn_fsbc)   * {SUM[n/nn_fsbc], n=0,nn_fsbc-1} 
    787787         !                                               = (1/nn_fsbc)^2 * {SUM[n]        , n=0,nn_fsbc-1} 
     
    802802   END FUNCTION ice_var_sshdyn 
    803803 
    804     
     804 
    805805   !!------------------------------------------------------------------- 
    806806   !!                ***  INTERFACE ice_var_itd   *** 
     
    831831      ph_ip(:) = phtip(:) 
    832832      ph_il(:) = phtil(:) 
    833        
     833 
    834834   END SUBROUTINE ice_var_itd_1c1c 
    835835 
     
    846846      REAL(wp), ALLOCATABLE, DIMENSION(:) ::   z1_ai, z1_vi, z1_vs 
    847847      ! 
    848       INTEGER ::   idim   
     848      INTEGER ::   idim 
    849849      !!------------------------------------------------------------------- 
    850850      ! 
     
    888888      ! 
    889889   END SUBROUTINE ice_var_itd_Nc1c 
    890     
     890 
    891891   SUBROUTINE ice_var_itd_1cMc( phti, phts, pati ,                             ph_i, ph_s, pa_i, & 
    892892      &                         ptmi, ptms, ptmsu, psmi, patip, phtip, phtil,  pt_i, pt_s, pt_su, ps_i, pa_ip, ph_ip, ph_il ) 
     
    898898      !! ** Method:   ice thickness distribution follows a gamma function from Abraham et al. (2015) 
    899899      !!              it has the property of conserving total concentration and volume 
    900       !!               
     900      !! 
    901901      !! 
    902902      !! ** Arguments : phti: 1-cat ice thickness 
     
    904904      !!                pati: 1-cat ice concentration 
    905905      !! 
    906       !! ** Output    : jpl-cat  
     906      !! ** Output    : jpl-cat 
    907907      !! 
    908908      !!  Abraham, C., Steiner, N., Monahan, A. and Michel, C., 2015. 
    909909      !!               Effects of subgrid‐scale snow thickness variability on radiative transfer in sea ice. 
    910       !!               Journal of Geophysical Research: Oceans, 120(8), pp.5597-5614  
     910      !!               Journal of Geophysical Research: Oceans, 120(8), pp.5597-5614 
    911911      !!------------------------------------------------------------------- 
    912912      REAL(wp), DIMENSION(:),   INTENT(in)    ::   phti, phts, pati    ! input  ice/snow variables 
     
    987987               ! In case snow load is in excess that would lead to transformation from snow to ice 
    988988               ! Then, transfer the snow excess into the ice (different from icethd_dh) 
    989                zdh = MAX( 0._wp, ( rhos * ph_s(ji,jl) + ( rhoi - rho0 ) * ph_i(ji,jl) ) * r1_rho0 )  
     989               zdh = MAX( 0._wp, ( rhos * ph_s(ji,jl) + ( rhoi - rho0 ) * ph_i(ji,jl) ) * r1_rho0 ) 
    990990               ! recompute h_i, h_s avoiding out of bounds values 
    991991               ph_i(ji,jl) = MIN( hi_max(jl), ph_i(ji,jl) + zdh ) 
     
    10471047      !! 
    10481048      !! ** Method:   Iterative procedure 
    1049       !!                 
     1049      !! 
    10501050      !!               1) Fill ice cat that correspond to input thicknesses 
    10511051      !!                  Find the lowest(jlmin) and highest(jlmax) cat that are filled 
    10521052      !! 
    10531053      !!               2) Expand the filling to the cat jlmin-1 and jlmax+1 
    1054       !!                   by removing 25% ice area from jlmin and jlmax (resp.)  
    1055       !!               
    1056       !!               3) Expand the filling to the empty cat between jlmin and jlmax  
     1054      !!                   by removing 25% ice area from jlmin and jlmax (resp.) 
     1055      !! 
     1056      !!               3) Expand the filling to the empty cat between jlmin and jlmax 
    10571057      !!                   by a) removing 25% ice area from the lower cat (ascendant loop jlmin=>jlmax) 
    10581058      !!                      b) removing 25% ice area from the higher cat (descendant loop jlmax=>jlmin) 
     
    10621062      !!                pati: N-cat ice concentration 
    10631063      !! 
    1064       !! ** Output    : jpl-cat  
    1065       !! 
    1066       !!  (Example of application: BDY forcings when inputs have N-cat /= jpl)   
     1064      !! ** Output    : jpl-cat 
     1065      !! 
     1066      !!  (Example of application: BDY forcings when inputs have N-cat /= jpl) 
    10671067      !!------------------------------------------------------------------- 
    10681068      REAL(wp), DIMENSION(:,:), INTENT(in)    ::   phti, phts, pati    ! input  ice/snow variables 
     
    10771077      REAL(wp), PARAMETER ::   ztrans = 0.25_wp 
    10781078      INTEGER  ::   ji, jl, jl1, jl2 
    1079       INTEGER  ::   idim, icat   
     1079      INTEGER  ::   idim, icat 
    10801080      !!------------------------------------------------------------------- 
    10811081      ! 
     
    11161116      ELSE                              ! input cat /= output cat ! 
    11171117         !                              ! ----------------------- ! 
    1118           
     1118 
    11191119         ALLOCATE( jlfil(idim,jpl), jlfil2(idim,jpl) )       ! allocate arrays 
    11201120         ALLOCATE( jlmin(idim), jlmax(idim) ) 
     
    11261126         ! 
    11271127         ! --- fill the categories --- ! 
    1128          !     find where cat-input = cat-output and fill cat-output fields   
     1128         !     find where cat-input = cat-output and fill cat-output fields 
    11291129         jlmax(:) = 0 
    11301130         jlmin(:) = 999 
     
    11471147         END DO 
    11481148         ! 
    1149          ! --- fill the gaps between categories --- !   
     1149         ! --- fill the gaps between categories --- ! 
    11501150         !     transfer from categories filled at the previous step to the empty ones in between 
    11511151         DO ji = 1, idim 
     
    11681168         END DO 
    11691169         ! 
    1170          jlfil2(:,:) = jlfil(:,:)  
     1170         jlfil2(:,:) = jlfil(:,:) 
    11711171         ! fill categories from low to high 
    11721172         DO jl = 2, jpl-1 
     
    11891189                  ! fill low 
    11901190                  pa_i(ji,jl) = pa_i(ji,jl) + ztrans * pa_i(ji,jl+1) 
    1191                   ph_i(ji,jl) = hi_mean(jl)  
     1191                  ph_i(ji,jl) = hi_mean(jl) 
    11921192                  jlfil2(ji,jl) = jl 
    11931193                  ! remove high 
     
    12791279   !!               we argue that snow does not cover the whole ice because 
    12801280   !!               of wind blowing... 
    1281    !!                 
     1281   !! 
    12821282   !! ** Arguments : ph_s: snow thickness 
    1283    !!                 
     1283   !! 
    12841284   !! ** Output    : pa_s_fra: fraction of ice covered by snow 
    12851285   !! 
     
    13261326      ENDIF 
    13271327   END SUBROUTINE ice_var_snwfra_1d 
    1328     
     1328 
    13291329   !!-------------------------------------------------------------------------- 
    13301330   !! INTERFACE ice_var_snwblow 
     
    13361336   !!                If snow fall was uniform, a fraction (1-at_i) would fall into leads 
    13371337   !!                but because of the winds, more snow falls on leads than on sea ice 
    1338    !!                and a greater fraction (1-at_i)^beta of the total mass of snow  
     1338   !!                and a greater fraction (1-at_i)^beta of the total mass of snow 
    13391339   !!                (beta < 1) falls in leads. 
    1340    !!                In reality, beta depends on wind speed,  
    1341    !!                and should decrease with increasing wind speed but here, it is  
     1340   !!                In reality, beta depends on wind speed, 
     1341   !!                and should decrease with increasing wind speed but here, it is 
    13421342   !!                considered as a constant. an average value is 0.66 
    13431343   !!-------------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.