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 5053 for branches/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90 – NEMO

Ignore:
Timestamp:
2015-02-03T18:11:02+01:00 (9 years ago)
Author:
clem
Message:

LIM3 cleaning continues. No change in the physics besides the introduction of the monocategory sea ice

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r5051 r5053  
    3939   USE limtrp          ! Ice transport 
    4040   USE limthd          ! Ice thermodynamics 
    41    USE limitd_th       ! Thermodynamics on ice thickness distribution  
    4241   USE limitd_me       ! Mechanics on ice thickness distribution 
    4342   USE limsbc          ! sea surface boundary condition 
     
    109108      INTEGER, INTENT(in) ::   kblk    ! type of bulk (=3 CLIO, =4 CORE, =5 COUPLED) 
    110109      !! 
    111       INTEGER  ::   jl      ! dummy loop index 
    112       REAL(wp) ::   zcoef   ! local scalar 
     110      INTEGER  ::   jl                 ! dummy loop index 
    113111      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zalb_os, zalb_cs  ! ice albedo under overcast/clear sky 
    114112      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zalb_ice          ! mean ice albedo (for coupled) 
     
    117115      IF( nn_timing == 1 )  CALL timing_start('sbc_ice_lim') 
    118116 
    119       !                                        !----------------------! 
    120       IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !  Ice time-step only  ! 
    121          !                                     !----------------------! 
    122          !                                           !  Bulk Formulae ! 
    123          !                                           !----------------! 
    124          ! 
     117      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !  Ice time-step only 
     118         !-----------------------!                                            
     119         ! --- Bulk Formulae --- !                                            
     120         !-----------------------! 
    125121         u_oce(:,:) = ssu_m(:,:) * umask(:,:,1)      ! mean surface ocean current at ice velocity point 
    126122         v_oce(:,:) = ssv_m(:,:) * vmask(:,:,1)      ! (C-grid dynamics :  U- & V-points as the ocean) 
     
    133129         CALL albedo_ice( t_su, ht_i, ht_s, zalb_cs, zalb_os )  ! cloud-sky and overcast-sky ice albedos 
    134130 
     131         ! CORE and COUPLED bulk formulations 
    135132         SELECT CASE( kblk ) 
    136          CASE( jp_core , jp_cpl )   ! CORE and COUPLED bulk formulations 
     133         CASE( jp_core , jp_cpl ) 
    137134 
    138135            ! albedo depends on cloud fraction because of non-linear spectral effects 
     
    183180         END SELECT 
    184181          
    185          !                                           !----------------------! 
    186          !                                           ! LIM-3  time-stepping ! 
    187          !                                           !----------------------! 
    188          !  
     182         !------------------------------! 
     183         ! --- LIM-3 main time-step --- ! 
     184         !------------------------------! 
    189185         numit = numit + nn_fsbc                     ! Ice model time step 
    190186         ! 
     
    200196         v_ice_b(:,:)     = v_ice(:,:) 
    201197 
    202                           CALL sbc_lim_flx0          ! set diag of mass, heat and salt fluxes to 0 
     198                          CALL sbc_lim_diag0         ! set diag of mass, heat and salt fluxes to 0 
    203199 
    204200                          CALL lim_rst_opn( kt )     ! Open Ice restart file 
    205201         ! 
    206          IF( ln_nicep )   CALL lim_prt( kt, jiindx, jjindx, 1, ' - Beginning the time step - ' )   ! control print 
    207202         ! ---------------------------------------------- 
    208203         ! ice dynamics and transport (except in 1D case) 
     
    211206 
    212207                          CALL lim_dyn( kt )              ! Ice dynamics    ( rheology/dynamics ) 
     208 
    213209                          CALL lim_trp( kt )              ! Ice transport   ( Advection/diffusion ) 
    214                           CALL lim_var_glo2eqv            ! equivalent variables, requested for rafting 
    215          IF( ln_nicep )   CALL lim_prt( kt, jiindx, jjindx,-1, ' - ice dyn & trp - ' )   ! control print 
     210 
    216211         IF( nn_monocat /= 2 )   & 
    217212            &             CALL lim_itd_me                 ! Mechanical redistribution ! (ridging/rafting) 
    218                           CALL lim_var_agg( 1 )  
     213 
    219214#if defined key_bdy 
    220215                          ! bdy ice thermo  
     
    225220         IF( ln_nicep )   CALL lim_prt( kt, jiindx, jjindx, 1, ' - ice thermo bdy - ' )   ! control print 
    226221#endif 
    227                           CALL lim_update1 
     222 
     223                          CALL lim_update1( kt ) 
     224 
    228225         ENDIF 
    229 !                         !- Change old values for new values 
    230                           u_ice_b(:,:)     = u_ice(:,:) 
    231                           v_ice_b(:,:)     = v_ice(:,:) 
    232                           a_i_b  (:,:,:)   = a_i  (:,:,:) 
    233                           v_s_b  (:,:,:)   = v_s  (:,:,:) 
    234                           v_i_b  (:,:,:)   = v_i  (:,:,:) 
    235                           e_s_b  (:,:,:,:) = e_s  (:,:,:,:) 
    236                           e_i_b  (:,:,:,:) = e_i  (:,:,:,:) 
    237                           oa_i_b (:,:,:)   = oa_i (:,:,:) 
    238                           smv_i_b(:,:,:)   = smv_i(:,:,:) 
     226 
     227         !- Change old values for new values 
     228         u_ice_b(:,:)     = u_ice(:,:) 
     229         v_ice_b(:,:)     = v_ice(:,:) 
     230         a_i_b  (:,:,:)   = a_i  (:,:,:) 
     231         v_s_b  (:,:,:)   = v_s  (:,:,:) 
     232         v_i_b  (:,:,:)   = v_i  (:,:,:) 
     233         e_s_b  (:,:,:,:) = e_s  (:,:,:,:) 
     234         e_i_b  (:,:,:,:) = e_i  (:,:,:,:) 
     235         oa_i_b (:,:,:)   = oa_i (:,:,:) 
     236         smv_i_b(:,:,:)   = smv_i(:,:,:) 
    239237  
    240238         ! ---------------------------------------------- 
     
    253251                             IF( nn_limflx == 2 )   CALL ice_lim_flx( t_su, zalb_ice, qns_ice, qsr_ice ,   & 
    254252                          &                                           dqns_ice, qla_ice, dqla_ice, nn_limflx ) 
    255                            ! Latent heat flux is forced to 0 in coupled : 
    256                            !  it is included in qns (non-solar heat flux) 
     253                             ! Latent heat flux is forced to 0 in coupled: it is included in qns (non-solar heat flux) 
    257254                             qla_ice  (:,:,:) = 0._wp 
    258255                             dqla_ice (:,:,:) = 0._wp 
    259256                          END SELECT 
    260257                          ! 
    261                           CALL lim_var_bv                 ! bulk brine volume (diag) 
    262258                          CALL lim_thd( kt )              ! Ice thermodynamics  
    263                           zcoef = rdt_ice /rday           !  Ice natural aging 
    264                           oa_i(:,:,:) = oa_i(:,:,:) + a_i(:,:,:) * zcoef 
    265          IF( ln_nicep )   CALL lim_prt( kt, jiindx, jjindx, 1, ' - ice thermodyn. - ' )   ! control print 
    266                           CALL lim_itd_th( kt )           !  Remap ice categories, lateral accretion 
    267                           CALL lim_update2                ! Global variables update 
    268  
    269          IF( ln_nicep )   CALL lim_prt( kt, jiindx, jjindx, 2, ' - Final state - ' )   ! control print 
    270          ! 
    271                           CALL lim_sbc_flx( kt )     ! Update surface ocean mass, heat and salt fluxes 
    272          ! 
    273          IF( ln_nicep )   CALL lim_prt( kt, jiindx, jjindx, 3, ' - Final state lim_sbc - ' )   ! control print 
     259 
     260                          CALL lim_update2( kt )          ! Global variables update 
     261         ! 
     262                          CALL lim_sbc_flx( kt )          ! Update surface ocean mass, heat and salt fluxes 
    274263         ! 
    275264         IF(ln_limdiaout) CALL lim_diahsb                 ! Diagnostics and outputs  
    276265 
    277                           CALL lim_wri( 1  )              ! Ice outputs  
     266                          CALL lim_wri( 1 )               ! Ice outputs  
    278267 
    279268         IF( kt == nit000 .AND. ln_rstart )   & 
    280             &             CALL iom_close( numrir )        ! clem: close input ice restart file 
     269            &             CALL iom_close( numrir )        ! close input ice restart file 
    281270         ! 
    282271         IF( lrst_ice )   CALL lim_rst_write( kt )        ! Ice restart file  
     
    315304      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~   via Louvain la Neuve Ice Model (LIM-3) time stepping' 
    316305      ! 
    317       ! 
    318306      !                                ! Allocate the ice arrays 
    319307      ierr =        ice_alloc        ()      ! ice variables 
     
    343331      CALL lim_thd_sal_init            ! set ice salinity parameters 
    344332      ! 
    345       rdt_ice   = nn_fsbc * rdttra(1)  ! sea-ice timestep 
    346       r1_rdtice = 1._wp / rdt_ice      ! sea-ice timestep inverse 
    347       ! 
    348333      CALL lim_msh                     ! ice mesh initialization 
    349334      ! 
    350       CALL lim_itd_init                 ! ice thickness distribution initialization 
     335      CALL lim_itd_init                ! ice thickness distribution initialization 
    351336      ! 
    352337      CALL lim_itd_me_init             ! ice thickness distribution initialization 
     
    356341         numit = nit000 - 1 
    357342         CALL lim_istate 
    358          CALL lim_var_agg(1) 
    359          CALL lim_var_glo2eqv 
    360343      ELSE                                    ! start from a restart file 
    361344         CALL lim_rst_read 
    362345         numit = nit000 - 1 
    363          CALL lim_var_agg(1) 
    364          CALL lim_var_glo2eqv 
    365346      ENDIF 
     347      CALL lim_var_agg(1) 
     348      CALL lim_var_glo2eqv 
    366349      ! 
    367350      CALL lim_sbc_init                 ! ice surface boundary condition    
     
    390373      !! ** input   :   Namelist namicerun 
    391374      !!------------------------------------------------------------------- 
    392       NAMELIST/namicerun/ cn_icerst_in, cn_icerst_out, ln_limdyn, amax, ln_nicep, ln_limdiahsb, ln_limdiaout 
     375!clem      NAMELIST/namicerun/ jpl, nlay_i, nlay_s, cn_icerst_in, cn_icerst_out,   & 
     376!clem         &                ln_limdyn, amax, ln_nicep, ln_limdiahsb, ln_limdiaout 
     377      NAMELIST/namicerun/ cn_icerst_in, cn_icerst_out,   & 
     378         &                ln_limdyn, amax, ln_nicep, ln_limdiahsb, ln_limdiaout 
    393379      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    394380      !!------------------------------------------------------------------- 
     
    408394         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice' 
    409395         WRITE(numout,*) ' ~~~~~~' 
     396!clem         WRITE(numout,*) '   number of ice  categories                               = ', jpl 
     397!clem         WRITE(numout,*) '   number of ice  layers                                   = ', nlay_i 
     398!clem         WRITE(numout,*) '   number of snow layers                                   = ', nlay_s 
    410399         WRITE(numout,*) '   switch for ice dynamics (1) or not (0)      ln_limdyn   = ', ln_limdyn 
    411400         WRITE(numout,*) '   maximum ice concentration                               = ', amax  
     
    423412         IF(lwp) WRITE(numout,*) ' The debugging point is : jiindx : ',jiindx, ' jjindx : ',jjindx 
    424413      ENDIF 
     414      ! 
     415      ! sea-ice timestep and inverse 
     416      rdt_ice   = nn_fsbc * rdttra(1)   
     417      r1_rdtice = 1._wp / rdt_ice  
    425418      ! 
    426419   END SUBROUTINE ice_run 
     
    577570   END SUBROUTINE ice_lim_flx 
    578571 
    579    SUBROUTINE sbc_lim_flx0 
     572   SUBROUTINE sbc_lim_diag0 
    580573      !!---------------------------------------------------------------------- 
    581574      !!                  ***  ROUTINE sbc_lim_flx0  *** 
     
    610603      afx_dyn(:,:) = 0._wp   ;   afx_thd(:,:) = 0._wp 
    611604       
    612    END SUBROUTINE sbc_lim_flx0 
     605   END SUBROUTINE sbc_lim_diag0 
    613606       
    614607   FUNCTION fice_cell_ave ( ptab ) 
     
    623616       
    624617      DO jl = 1, jpl 
    625          fice_cell_ave (:,:) = fice_cell_ave (:,:) & 
    626             &                  + a_i (:,:,jl) * ptab (:,:,jl) 
     618         fice_cell_ave (:,:) = fice_cell_ave (:,:) + a_i (:,:,jl) * ptab (:,:,jl) 
    627619      END DO 
    628620       
Note: See TracChangeset for help on using the changeset viewer.