MODULE iceini !!====================================================================== !! *** MODULE iceini *** !! Sea-ice model : LIM Sea ice model Initialization !!====================================================================== !! History : 1.0 ! 02-08 (G. Madec) F90: Free form and modules !! 2.0 ! 03-08 (C. Ethe) add ice_run !!---------------------------------------------------------------------- #if defined key_ice_lim !!---------------------------------------------------------------------- !! 'key_ice_lim' : LIM sea-ice model !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! ice_init : sea-ice model initialization !! ice_run : Definition some run parameter for ice model !!---------------------------------------------------------------------- USE dom_oce USE dom_ice USE in_out_manager USE ice_oce ! ice variables USE flx_oce USE phycst ! Define parameters for the routines USE ocfzpt USE ice USE limmsh USE limistate USE limrst USE ini1d ! initialization of the 1D configuration IMPLICIT NONE PRIVATE PUBLIC ice_init ! called by opa.F90 LOGICAL , PUBLIC :: ln_limdyn = .TRUE. !: flag for ice dynamics (T) or not (F) REAL(wp), PUBLIC :: hsndif = 0.e0 !: computation of temp. in snow (0) or not (9999) REAL(wp), PUBLIC :: hicdif = 0.e0 !: computation of temp. in ice (0) or not (9999) REAL(wp), PUBLIC, DIMENSION(2) :: acrit = (/ 1.e-06 , 1.e-06 /) !: minimum fraction for leads in ! ! north and south hemisphere !!---------------------------------------------------------------------- !! LIM 2.0, UCL-LOCEAN-IPSL (2005) !! $Header$ !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt !!---------------------------------------------------------------------- CONTAINS SUBROUTINE ice_init !!---------------------------------------------------------------------- !! *** ROUTINE ice_init *** !! !! ** purpose : !!---------------------------------------------------------------------- CHARACTER(len=80) :: namelist_icename !!---------------------------------------------------------------------- ! ! Open the namelist file namelist_icename = 'namelist_ice' CALL ctlopn(numnam_ice,namelist_icename,'OLD', 'FORMATTED', 'SEQUENTIAL', & 1,numout,.FALSE.,1) CALL ice_run ! read in namelist some run parameters ! Louvain la Neuve Ice model IF( nacc == 1 ) THEN dtsd2 = nfice * rdtmin * 0.5 rdt_ice = nfice * rdtmin ELSE dtsd2 = nfice * rdt * 0.5 rdt_ice = nfice * rdt ENDIF CALL lim_msh ! ice mesh initialization ! Initial sea-ice state IF( .NOT.ln_rstart ) THEN CALL lim_istate ! start from rest: sea-ice deduced from sst ELSE CALL lim_rst_read ! start from a restart file ENDIF tn_ice(:,:) = sist(:,:) ! initialisation of ice temperature freeze(:,:) = 1.0 - frld(:,:) ! initialisation of sea/ice cover # if defined key_coupled alb_ice(:,:) = albege(:,:) ! sea-ice albedo # endif ! END SUBROUTINE ice_init SUBROUTINE ice_run !!------------------------------------------------------------------- !! *** ROUTINE ice_run *** !! !! ** Purpose : Definition some run parameter for ice model !! !! ** Method : Read the namicerun namelist and check the parameter !! values called at the first timestep (nit000) !! !! ** input : Namelist namicerun !!------------------------------------------------------------------- NAMELIST/namicerun/ ln_limdyn, ln_limdmp, acrit, hsndif, hicdif !!------------------------------------------------------------------- ! REWIND ( numnam_ice ) ! Read Namelist namicerun READ ( numnam_ice , namicerun ) IF( lk_cfg_1d ) ln_limdyn = .FALSE. ! No ice transport in 1D configuration IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice' WRITE(numout,*) ' ~~~~~~' WRITE(numout,*) ' switch for ice dynamics (1) or not (0) ln_limdyn = ', ln_limdyn WRITE(numout,*) ' Ice damping ln_limdmp = ', ln_limdmp WRITE(numout,*) ' minimum fraction for leads in the NH (SH) acrit(1/2) = ', acrit(:) WRITE(numout,*) ' computation of temp. in snow (=0) or not (=9999) hsndif = ', hsndif WRITE(numout,*) ' computation of temp. in ice (=0) or not (=9999) hicdif = ', hicdif ENDIF ! END SUBROUTINE ice_run #else !!---------------------------------------------------------------------- !! Default option : Empty module NO LIM sea-ice model !!---------------------------------------------------------------------- CONTAINS SUBROUTINE ice_init ! Empty routine END SUBROUTINE ice_init #endif !!====================================================================== END MODULE iceini