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 8486 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd.F90 – NEMO

Ignore:
Timestamp:
2017-09-01T15:49:35+02:00 (7 years ago)
Author:
clem
Message:

changes in style - part1 - (now the code looks better txs to Gurvan's comments)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd.F90

    r8483 r8486  
    1515#if defined key_lim3 
    1616   !!---------------------------------------------------------------------- 
    17    !!   'key_lim3'                                      LIM3 sea-ice model 
     17   !!   'key_lim3'                                       LIM3 sea-ice model 
    1818   !!---------------------------------------------------------------------- 
    1919   !!   ice_thd       : thermodynamic of sea ice 
     
    2323   USE dom_oce        ! ocean space and time domain variables 
    2424   USE ice            ! sea-ice variables 
     25!!gm list trop longue ==>>> why not passage en argument d'appel ? 
    2526   USE sbc_oce , ONLY : sss_m, sst_m, e3t_m, utau, vtau, ssu_m, ssv_m, frq_m, qns_tot, qsr_tot, sprecip, ln_cpl 
    2627   USE sbc_ice , ONLY : qsr_oce, qns_oce, qemp_oce, qsr_ice, qns_ice, dqns_ice, evap_ice, qprec_ice, qevap_ice, & 
     
    5354#  include "vectopt_loop_substitute.h90" 
    5455   !!---------------------------------------------------------------------- 
    55    !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2010) 
     56   !! NEMO/ICE 4.0 , NEMO Consortium (2017) 
    5657   !! $Id: icethd.F90 8420 2017-08-08 12:18:46Z clem $ 
    5758   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    7576      !!             - call ice_thd_temp to  retrieve temperature from ice enthalpy 
    7677      !!             - back to the geographic grid 
    77       !!      
    78       !! ** References :  
    7978      !!--------------------------------------------------------------------- 
    8079      INTEGER, INTENT(in) :: kt    ! number of iteration 
     
    9392      IF( kt == nit000 .AND. lwp ) THEN 
    9493         WRITE(numout,*) 
    95          WRITE(numout,*)' icethd ' 
    96          WRITE(numout,*)' ~~~~~~~' 
     94         WRITE(numout,*)' icethd : sea-ice thermodynamics' 
     95         WRITE(numout,*)' ~~~~~~~~' 
    9796      ENDIF 
    9897       
    9998      ! conservation test 
    100       IF( ln_limdiachk ) CALL ice_cons_hsm(0, 'icethd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 
     99      IF( ln_limdiachk )   CALL ice_cons_hsm( 0, 'icethd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b ) 
    101100 
    102101      CALL ice_var_glo2eqv 
     
    231230            dh_snowice(1:nidx) = 0._wp ; dh_i_sub (1:nidx) = 0._wp 
    232231            ! 
    233             IF( ln_limdH )    CALL ice_thd_dif                      ! --- Ice/Snow Temperature profile --- ! 
    234             ! 
    235             IF( ln_limdH )    CALL ice_thd_dh                       ! --- Ice/Snow thickness --- !     
    236             ! 
    237             IF( ln_limdH )    CALL ice_thd_ent( e_i_1d(1:nidx,:) )  ! --- Ice enthalpy remapping --- ! 
     232            IF( ln_limdH ) THEN                                     ! --- growing/melting --- ! 
     233                              CALL ice_thd_dif                             ! Ice/Snow Temperature profile 
     234                              CALL ice_thd_dh                              ! Ice/Snow thickness    
     235                              CALL ice_thd_ent( e_i_1d(1:nidx,:) )         ! Ice enthalpy remapping 
     236            ENDIF 
    238237            ! 
    239238                              CALL ice_thd_sal                      ! --- Ice salinity --- !     
     
    241240                              CALL ice_thd_temp                     ! --- temperature update --- ! 
    242241            ! 
     242!!gm please create a new logical (l_thd_lam or a better explicit name) set one for all in icestp.F90 module 
     243!!gm        l_thd_lam = ln_limdH .AND. ( ( nn_monocat == 1 .OR. nn_monocat == 4 ) .AND. jpl == 1 ) 
     244!!gm        by the way, the different options associated with nn_monocat =1 to 4  are quite impossible to identify 
     245!!gm        more comment to add when ready the namelist, with an explicit print in the ocean.output 
    243246            IF( ln_limdH ) THEN 
    244247               IF ( ( nn_monocat == 1 .OR. nn_monocat == 4 ) .AND. jpl == 1 ) THEN 
     
    259262      oa_i(:,:,:) = o_i(:,:,:) * a_i(:,:,:) 
    260263 
    261       IF( ln_limdiachk ) CALL ice_cons_hsm(1, 'icethd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b) 
    262       ! 
    263                          CALL ice_var_zapsmall           ! --- remove very small ice concentration (<1e-10) --- ! 
    264       !                                                  !     & make sure at_i=SUM(a_i) & ato_i=1 where at_i=0 
     264      IF( ln_limdiachk )   CALL ice_cons_hsm( 1, 'icethd', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b ) 
     265      ! 
     266                           CALL ice_var_zapsmall           ! --- remove very small ice concentration (<1e-10) --- ! 
     267      !                                                    !     & make sure at_i=SUM(a_i) & ato_i=1 where at_i=0 
    265268      !                    
    266       IF( jpl > 1 )      CALL ice_itd_rem( kt )          ! --- Transport ice between thickness categories --- ! 
    267       ! 
    268       IF( ln_limdO )     CALL ice_thd_lac                ! --- frazil ice growing in leads --- ! 
    269       ! 
    270       IF( ln_limctl )    CALL ice_prt( kt, iiceprt, jiceprt, 1, ' - ice thermodyn. - ' )   ! control print 
    271       IF( ln_ctl )       CALL ice_prt3D( 'icethd' )      ! Control print 
     269      IF( jpl > 1 )        CALL ice_itd_rem( kt )          ! --- Transport ice between thickness categories --- ! 
     270      ! 
     271      IF( ln_limdO )       CALL ice_thd_lac                ! --- frazil ice growing in leads --- ! 
     272      ! 
     273      IF( ln_limctl )      CALL ice_prt( kt, iiceprt, jiceprt, 1, ' - ice thermodyn. - ' )   ! control print 
     274      IF( ln_ctl )         CALL ice_prt3D( 'icethd' )      ! Control print 
    272275      ! 
    273276      IF( nn_timing == 1 )  CALL timing_stop('icethd') 
    274  
     277      ! 
    275278   END SUBROUTINE ice_thd  
    276279 
     
    341344 
    342345 
    343    SUBROUTINE ice_thd_1d2d( jl, kn ) 
     346   SUBROUTINE ice_thd_1d2d( kl, kn ) 
    344347      !!----------------------------------------------------------------------- 
    345348      !!                   ***  ROUTINE ice_thd_1d2d ***  
     
    347350      !! ** Purpose :   move arrays from 1d to 2d and the reverse 
    348351      !!----------------------------------------------------------------------- 
    349       INTEGER, INTENT(in) ::   jl       ! ice cat 
    350       INTEGER, INTENT(in) ::   kn       ! 1= from 2D to 1D   ;   2= from 1D to 2D 
    351       ! 
    352       INTEGER             ::   jk       ! dummy loop indices 
     352      INTEGER, INTENT(in) ::   kl   ! index of the ice category  
     353      INTEGER, INTENT(in) ::   kn   ! 1= from 2D to 1D   ;   2= from 1D to 2D 
     354      ! 
     355      INTEGER ::   jk   ! dummy loop indices 
    353356      !!----------------------------------------------------------------------- 
    354357      ! 
    355358      SELECT CASE( kn ) 
    356       ! 
    357       CASE( 1 )            ! from 2D to 1D 
    358          ! 
     359      !                    !---------------------! 
     360      CASE( 1 )            !==  from 2D to 1D  ==! 
     361         !                 !---------------------! 
    359362         CALL tab_2d_1d( nidx, idxice(1:nidx), at_i_1d(1:nidx), at_i             ) 
    360          CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i(:,:,jl)      ) 
    361          CALL tab_2d_1d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:,jl)     ) 
    362          CALL tab_2d_1d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:,jl)     ) 
    363          CALL tab_2d_1d( nidx, idxice(1:nidx), t_su_1d(1:nidx), t_su(:,:,jl)     ) 
    364          CALL tab_2d_1d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:,jl)     ) 
     363         CALL tab_2d_1d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i (:,:,kl)     ) 
     364         CALL tab_2d_1d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:,kl)     ) 
     365         CALL tab_2d_1d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:,kl)     ) 
     366         CALL tab_2d_1d( nidx, idxice(1:nidx), t_su_1d(1:nidx), t_su(:,:,kl)     ) 
     367         CALL tab_2d_1d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:,kl)     ) 
    365368         DO jk = 1, nlay_s 
    366             CALL tab_2d_1d( nidx, idxice(1:nidx), t_s_1d(1:nidx,jk), t_s(:,:,jk,jl)   ) 
    367             CALL tab_2d_1d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,jl)   ) 
     369            CALL tab_2d_1d( nidx, idxice(1:nidx), t_s_1d(1:nidx,jk), t_s(:,:,jk,kl)   ) 
     370            CALL tab_2d_1d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,kl)   ) 
    368371         END DO 
    369372         DO jk = 1, nlay_i 
    370             CALL tab_2d_1d( nidx, idxice(1:nidx), t_i_1d(1:nidx,jk), t_i(:,:,jk,jl)   ) 
    371             CALL tab_2d_1d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,jl)   ) 
    372             CALL tab_2d_1d( nidx, idxice(1:nidx), s_i_1d(1:nidx,jk), s_i(:,:,jk,jl)   ) 
     373            CALL tab_2d_1d( nidx, idxice(1:nidx), t_i_1d(1:nidx,jk), t_i(:,:,jk,kl)   ) 
     374            CALL tab_2d_1d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,kl)   ) 
     375            CALL tab_2d_1d( nidx, idxice(1:nidx), s_i_1d(1:nidx,jk), s_i(:,:,jk,kl)   ) 
    373376         END DO 
    374377         ! 
    375378         CALL tab_2d_1d( nidx, idxice(1:nidx), qprec_ice_1d(1:nidx), qprec_ice        ) 
    376          CALL tab_2d_1d( nidx, idxice(1:nidx), qsr_ice_1d  (1:nidx), qsr_ice(:,:,jl) ) 
     379         CALL tab_2d_1d( nidx, idxice(1:nidx), qsr_ice_1d  (1:nidx), qsr_ice (:,:,kl) ) 
    377380         CALL tab_2d_1d( nidx, idxice(1:nidx), fr1_i0_1d   (1:nidx), fr1_i0           ) 
    378381         CALL tab_2d_1d( nidx, idxice(1:nidx), fr2_i0_1d   (1:nidx), fr2_i0           ) 
    379          CALL tab_2d_1d( nidx, idxice(1:nidx), qns_ice_1d  (1:nidx), qns_ice(:,:,jl) ) 
    380          CALL tab_2d_1d( nidx, idxice(1:nidx), ftr_ice_1d  (1:nidx), ftr_ice(:,:,jl) ) 
    381          CALL tab_2d_1d( nidx, idxice(1:nidx), evap_ice_1d (1:nidx), evap_ice(:,:,jl) ) 
    382          CALL tab_2d_1d( nidx, idxice(1:nidx), dqns_ice_1d (1:nidx), dqns_ice(:,:,jl) ) 
     382         CALL tab_2d_1d( nidx, idxice(1:nidx), qns_ice_1d  (1:nidx), qns_ice (:,:,kl) ) 
     383         CALL tab_2d_1d( nidx, idxice(1:nidx), ftr_ice_1d  (1:nidx), ftr_ice (:,:,kl) ) 
     384         CALL tab_2d_1d( nidx, idxice(1:nidx), evap_ice_1d (1:nidx), evap_ice(:,:,kl) ) 
     385         CALL tab_2d_1d( nidx, idxice(1:nidx), dqns_ice_1d (1:nidx), dqns_ice(:,:,kl) ) 
    383386         CALL tab_2d_1d( nidx, idxice(1:nidx), t_bo_1d     (1:nidx), t_bo             ) 
    384387         CALL tab_2d_1d( nidx, idxice(1:nidx), sprecip_1d  (1:nidx), sprecip          )  
     
    435438         DO jk = 1, nlay_i 
    436439            WHERE( ht_i_1d(1:nidx)>0._wp ) e_i_1d(1:nidx,jk) = e_i_1d(1:nidx,jk) / (ht_i_1d(1:nidx) * a_i_1d(1:nidx)) * nlay_i 
    437          ENDDO 
     440         END DO 
    438441         DO jk = 1, nlay_s 
    439442            WHERE( ht_s_1d(1:nidx)>0._wp ) e_s_1d(1:nidx,jk) = e_s_1d(1:nidx,jk) / (ht_s_1d(1:nidx) * a_i_1d(1:nidx)) * nlay_s 
    440          ENDDO 
    441          ! 
    442       CASE( 2 )            ! from 1D to 2D 
    443          ! 
     443         END DO 
     444         ! 
     445         !                 !---------------------! 
     446      CASE( 2 )            !==  from 1D to 2D  ==! 
     447         !                 !---------------------! 
    444448         ! --- Change units of e_i, e_s from J/m3 to J/m2 --- ! 
    445449         DO jk = 1, nlay_i 
    446450            e_i_1d(1:nidx,jk) = e_i_1d(1:nidx,jk) * ht_i_1d(1:nidx) * a_i_1d(1:nidx) * r1_nlay_i 
    447          ENDDO 
     451         END DO 
    448452         DO jk = 1, nlay_s 
    449453            e_s_1d(1:nidx,jk) = e_s_1d(1:nidx,jk) * ht_s_1d(1:nidx) * a_i_1d(1:nidx) * r1_nlay_s 
    450          ENDDO 
     454         END DO 
    451455         ! 
    452456         ! Change thickness to volume 
     
    456460          
    457461         CALL tab_1d_2d( nidx, idxice(1:nidx), at_i_1d(1:nidx), at_i             ) 
    458          CALL tab_1d_2d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i(:,:,jl)      ) 
    459          CALL tab_1d_2d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:,jl)     ) 
    460          CALL tab_1d_2d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:,jl)     ) 
    461          CALL tab_1d_2d( nidx, idxice(1:nidx), t_su_1d(1:nidx), t_su(:,:,jl)     ) 
    462          CALL tab_1d_2d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:,jl)     ) 
     462         CALL tab_1d_2d( nidx, idxice(1:nidx), a_i_1d (1:nidx), a_i (:,:,kl)     ) 
     463         CALL tab_1d_2d( nidx, idxice(1:nidx), ht_i_1d(1:nidx), ht_i(:,:,kl)     ) 
     464         CALL tab_1d_2d( nidx, idxice(1:nidx), ht_s_1d(1:nidx), ht_s(:,:,kl)     ) 
     465         CALL tab_1d_2d( nidx, idxice(1:nidx), t_su_1d(1:nidx), t_su(:,:,kl)     ) 
     466         CALL tab_1d_2d( nidx, idxice(1:nidx), sm_i_1d(1:nidx), sm_i(:,:,kl)     ) 
    463467         DO jk = 1, nlay_s 
    464             CALL tab_1d_2d( nidx, idxice(1:nidx), t_s_1d(1:nidx,jk), t_s(:,:,jk,jl)  ) 
    465             CALL tab_1d_2d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,jl)  ) 
     468            CALL tab_1d_2d( nidx, idxice(1:nidx), t_s_1d(1:nidx,jk), t_s(:,:,jk,kl) ) 
     469            CALL tab_1d_2d( nidx, idxice(1:nidx), e_s_1d(1:nidx,jk), e_s(:,:,jk,kl) ) 
    466470         END DO 
    467471         DO jk = 1, nlay_i 
    468             CALL tab_1d_2d( nidx, idxice(1:nidx), t_i_1d(1:nidx,jk), t_i(:,:,jk,jl)  ) 
    469             CALL tab_1d_2d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,jl)  ) 
    470             CALL tab_1d_2d( nidx, idxice(1:nidx), s_i_1d(1:nidx,jk), s_i(:,:,jk,jl)  ) 
    471          END DO 
    472          ! 
    473          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sni_1d(1:nidx), wfx_snw_sni   ) 
    474          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sum_1d(1:nidx), wfx_snw_sum   ) 
    475          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sub_1d    (1:nidx), wfx_sub       ) 
    476          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sub_1d(1:nidx), wfx_snw_sub   ) 
    477          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_ice_sub_1d(1:nidx), wfx_ice_sub   ) 
    478          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_err_sub_1d(1:nidx), wfx_err_sub   ) 
    479          ! 
    480          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_bog_1d (1:nidx), wfx_bog          ) 
    481          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_bom_1d (1:nidx), wfx_bom          ) 
    482          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sum_1d (1:nidx), wfx_sum          ) 
    483          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sni_1d (1:nidx), wfx_sni          ) 
    484          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_res_1d (1:nidx), wfx_res          ) 
    485          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_spr_1d (1:nidx), wfx_spr          ) 
    486          CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_lam_1d (1:nidx), wfx_lam          ) 
    487          ! 
    488          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bog_1d (1:nidx), sfx_bog          ) 
    489          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bom_1d (1:nidx), sfx_bom          ) 
    490          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sum_1d (1:nidx), sfx_sum          ) 
    491          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sni_1d (1:nidx), sfx_sni          ) 
    492          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bri_1d (1:nidx), sfx_bri          ) 
    493          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_res_1d (1:nidx), sfx_res          ) 
    494          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sub_1d (1:nidx), sfx_sub          ) 
    495          CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_lam_1d (1:nidx), sfx_lam          ) 
    496          ! 
    497          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_thd_1d (1:nidx), hfx_thd          ) 
    498          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_spr_1d (1:nidx), hfx_spr          ) 
    499          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_sum_1d (1:nidx), hfx_sum          ) 
    500          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_bom_1d (1:nidx), hfx_bom          ) 
    501          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_bog_1d (1:nidx), hfx_bog          ) 
    502          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_dif_1d (1:nidx), hfx_dif          ) 
    503          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_opw_1d (1:nidx), hfx_opw          ) 
    504          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_snw_1d (1:nidx), hfx_snw          ) 
    505          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_sub_1d (1:nidx), hfx_sub          ) 
    506          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_1d (1:nidx), hfx_err          ) 
    507          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_res_1d (1:nidx), hfx_res          ) 
    508          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_dif_1d(1:nidx), hfx_err_dif   ) 
    509          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_rem_1d(1:nidx), hfx_err_rem   ) 
    510          CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_out_1d (1:nidx), hfx_out          ) 
    511          ! 
    512          CALL tab_1d_2d( nidx, idxice(1:nidx), qns_ice_1d  (1:nidx), qns_ice(:,:,jl) ) 
    513          CALL tab_1d_2d( nidx, idxice(1:nidx), ftr_ice_1d  (1:nidx), ftr_ice(:,:,jl) ) 
     472            CALL tab_1d_2d( nidx, idxice(1:nidx), t_i_1d(1:nidx,jk), t_i(:,:,jk,kl) ) 
     473            CALL tab_1d_2d( nidx, idxice(1:nidx), e_i_1d(1:nidx,jk), e_i(:,:,jk,kl) ) 
     474            CALL tab_1d_2d( nidx, idxice(1:nidx), s_i_1d(1:nidx,jk), s_i(:,:,jk,kl) ) 
     475         END DO 
     476         ! 
     477         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sni_1d(1:nidx), wfx_snw_sni ) 
     478         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sum_1d(1:nidx), wfx_snw_sum ) 
     479         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sub_1d    (1:nidx), wfx_sub     ) 
     480         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_snw_sub_1d(1:nidx), wfx_snw_sub ) 
     481         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_ice_sub_1d(1:nidx), wfx_ice_sub ) 
     482         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_err_sub_1d(1:nidx), wfx_err_sub ) 
     483         ! 
     484         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_bog_1d (1:nidx), wfx_bog        ) 
     485         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_bom_1d (1:nidx), wfx_bom        ) 
     486         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sum_1d (1:nidx), wfx_sum        ) 
     487         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_sni_1d (1:nidx), wfx_sni        ) 
     488         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_res_1d (1:nidx), wfx_res        ) 
     489         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_spr_1d (1:nidx), wfx_spr        ) 
     490         CALL tab_1d_2d( nidx, idxice(1:nidx), wfx_lam_1d (1:nidx), wfx_lam        ) 
     491         ! 
     492         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bog_1d (1:nidx), sfx_bog        ) 
     493         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bom_1d (1:nidx), sfx_bom        ) 
     494         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sum_1d (1:nidx), sfx_sum        ) 
     495         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sni_1d (1:nidx), sfx_sni        ) 
     496         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_bri_1d (1:nidx), sfx_bri        ) 
     497         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_res_1d (1:nidx), sfx_res        ) 
     498         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_sub_1d (1:nidx), sfx_sub        ) 
     499         CALL tab_1d_2d( nidx, idxice(1:nidx), sfx_lam_1d (1:nidx), sfx_lam        ) 
     500         ! 
     501         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_thd_1d (1:nidx), hfx_thd        ) 
     502         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_spr_1d (1:nidx), hfx_spr        ) 
     503         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_sum_1d (1:nidx), hfx_sum        ) 
     504         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_bom_1d (1:nidx), hfx_bom        ) 
     505         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_bog_1d (1:nidx), hfx_bog        ) 
     506         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_dif_1d (1:nidx), hfx_dif        ) 
     507         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_opw_1d (1:nidx), hfx_opw        ) 
     508         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_snw_1d (1:nidx), hfx_snw        ) 
     509         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_sub_1d (1:nidx), hfx_sub        ) 
     510         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_1d (1:nidx), hfx_err        ) 
     511         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_res_1d (1:nidx), hfx_res        ) 
     512         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_dif_1d(1:nidx), hfx_err_dif ) 
     513         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_err_rem_1d(1:nidx), hfx_err_rem ) 
     514         CALL tab_1d_2d( nidx, idxice(1:nidx), hfx_out_1d (1:nidx), hfx_out        ) 
     515         ! 
     516         CALL tab_1d_2d( nidx, idxice(1:nidx), qns_ice_1d(1:nidx), qns_ice(:,:,kl) ) 
     517         CALL tab_1d_2d( nidx, idxice(1:nidx), ftr_ice_1d(1:nidx), ftr_ice(:,:,kl) ) 
    514518         ! 
    515519         ! SIMIP diagnostics          
    516          CALL tab_1d_2d( nidx, idxice(1:nidx), t_si_1d      (1:nidx), t_si(:,:,jl)      ) 
    517          CALL tab_1d_2d( nidx, idxice(1:nidx), diag_fc_bo_1d(1:nidx), diag_fc_bo        ) 
    518          CALL tab_1d_2d( nidx, idxice(1:nidx), diag_fc_su_1d(1:nidx), diag_fc_su        ) 
     520         CALL tab_1d_2d( nidx, idxice(1:nidx), t_si_1d      (1:nidx), t_si(:,:,kl) ) 
     521         CALL tab_1d_2d( nidx, idxice(1:nidx), diag_fc_bo_1d(1:nidx), diag_fc_bo   ) 
     522         CALL tab_1d_2d( nidx, idxice(1:nidx), diag_fc_su_1d(1:nidx), diag_fc_su   ) 
    519523         ! extensive variables 
    520          CALL tab_1d_2d( nidx, idxice(1:nidx), v_i_1d  (1:nidx), v_i  (:,:,jl) ) 
    521          CALL tab_1d_2d( nidx, idxice(1:nidx), v_s_1d  (1:nidx), v_s  (:,:,jl) ) 
    522          CALL tab_1d_2d( nidx, idxice(1:nidx), smv_i_1d(1:nidx), smv_i(:,:,jl) ) 
     524         CALL tab_1d_2d( nidx, idxice(1:nidx), v_i_1d  (1:nidx), v_i  (:,:,kl) ) 
     525         CALL tab_1d_2d( nidx, idxice(1:nidx), v_s_1d  (1:nidx), v_s  (:,:,kl) ) 
     526         CALL tab_1d_2d( nidx, idxice(1:nidx), smv_i_1d(1:nidx), smv_i(:,:,kl) ) 
     527         ! 
    523528      END SELECT 
    524529      ! 
     
    538543      !! ** input   :   Namelist namicether 
    539544      !!------------------------------------------------------------------- 
    540       INTEGER  ::   ios                 ! Local integer output status for namelist read 
     545      INTEGER  ::   ios   ! Local integer output status for namelist read 
     546      !! 
    541547      NAMELIST/namicethd/ rn_kappa_i, nn_ice_thcon, ln_dqnsice, rn_cdsn,                                  & 
    542548         &                ln_limdH, rn_betas,                                                             & 
     
    559565         WRITE(numout,*) 'ice_thd_init : Ice Thermodynamics' 
    560566         WRITE(numout,*) '~~~~~~~~~~~~~' 
     567         WRITE(numout,*)'   Namelist namicethd' 
    561568         WRITE(numout,*)'   -- icethd_dif --' 
    562569         WRITE(numout,*)'      extinction radiation parameter in sea ice               rn_kappa_i   = ', rn_kappa_i 
     
    573580         WRITE(numout,*)'   -- icethd_lac --' 
    574581         WRITE(numout,*)'      activate ice growth in open-water (T) or not (F)        ln_limdO     = ', ln_limdO 
    575          WRITE(numout,*)'      ice thick. for lateral accretion                        rn_hnewice   = ', rn_hnewice 
     582         WRITE(numout,*)'      ice thickness for lateral accretion                     rn_hnewice   = ', rn_hnewice 
    576583         WRITE(numout,*)'      Frazil ice thickness as a function of wind or not       ln_frazil    = ', ln_frazil 
    577584         WRITE(numout,*)'      Maximum proportion of frazil ice collecting at bottom   rn_maxfrazb  = ', rn_maxfrazb 
    578          WRITE(numout,*)'      Thresold relative drift speed for collection of frazil rn_vfrazb    = ', rn_vfrazb 
     585         WRITE(numout,*)'      Threshold relative drift speed for collection of frazil rn_vfrazb    = ', rn_vfrazb 
    579586         WRITE(numout,*)'      Squeezing coefficient for collection of frazil          rn_Cfrazb    = ', rn_Cfrazb 
    580587         WRITE(numout,*)'   -- iceitd --' 
     
    588595      IF(lwp) WRITE(numout,*) 
    589596      SELECT CASE( nn_limflx )         ! LIM3 Multi-category heat flux formulation 
    590       CASE ( -1 ) 
     597      CASE( -1 ) 
    591598         IF(lwp) WRITE(numout,*) '   LIM3: use per-category fluxes (nn_limflx = -1) ' 
    592          IF( ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
    593       CASE ( 0  ) 
     599         IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
     600      CASE( 0  ) 
    594601         IF(lwp) WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_limflx = 0) ' 
    595       CASE ( 1  ) 
     602      CASE( 1  ) 
    596603         IF(lwp) WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_limflx = 1) ' 
    597          IF( ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
    598       CASE ( 2  ) 
     604         IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_limflx for LIM3 in coupled mode must be 0 or 2' ) 
     605      CASE( 2  ) 
    599606         IF(lwp) WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_limflx = 2) ' 
    600          IF( .NOT. ln_cpl )   CALL ctl_stop( 'sbc_init : the chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
     607         IF( .NOT. ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_limflx for LIM3 in forced mode cannot be 2' ) 
    601608      CASE DEFAULT 
    602          CALL ctl_stop( 'sbcmod: LIM3 option, nn_limflx, should be between -1 and 2' ) 
     609         CALL ctl_stop( 'ice_thd_init: LIM3 option, nn_limflx, should be between -1 and 2' ) 
    603610      END SELECT 
    604611      ! 
Note: See TracChangeset for help on using the changeset viewer.