MODULE icethd_zdf !!====================================================================== !! *** MODULE icethd_zdf *** !! sea-ice: vertical heat diffusion in sea ice (computation of temperatures) !!====================================================================== !! History : LIM ! 02-2003 (M. Vancoppenolle) original 1D code !! ! 06-2005 (M. Vancoppenolle) 3d version !! ! 11-2006 (X Fettweis) Vectorization by Xavier !! ! 04-2007 (M. Vancoppenolle) Energy conservation !! 4.0 ! 2011-02 (G. Madec) dynamical allocation !! - ! 2012-05 (C. Rousset) add penetration solar flux !!---------------------------------------------------------------------- #if defined key_lim3 !!---------------------------------------------------------------------- !! 'key_lim3' ESIM sea-ice model !!---------------------------------------------------------------------- !! ice_thd_zdf : select the appropriate routine for vertical heat diffusion calculation !! ice_thd_zdf_BL99 : !! ice_thd_zdf_init : !!---------------------------------------------------------------------- USE dom_oce ! ocean space and time domain USE phycst ! physical constants (ocean directory) USE ice ! sea-ice: variables USE icethd_zdf_BL99 ! sea-ice: vertical diffusion (Bitz and Lipscomb, 1999) ! USE in_out_manager ! I/O manager USE lib_mpp ! MPP library USE lib_fortran ! fortran utilities (glob_sum + no signed zero) IMPLICIT NONE PRIVATE PUBLIC ice_thd_zdf ! called by icethd PUBLIC ice_thd_zdf_init ! called by icestp INTEGER :: nice_zdf ! Choice of the type of vertical heat diffusion formulation ! ! associated indices: INTEGER, PARAMETER :: np_BL99 = 1 ! Bitz and Lipscomb (1999) !! INTEGER, PARAMETER :: np_XXXX = 2 !!** namelist (namthd_zdf) ** LOGICAL :: ln_zdf_BL99 ! Heat diffusion follows Bitz and Lipscomb (1999) !!---------------------------------------------------------------------- !! NEMO/ICE 4.0 , NEMO Consortium (2017) !! $Id: icethd_zdf.F90 8420 2017-08-08 12:18:46Z clem $ !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE ice_thd_zdf !!------------------------------------------------------------------- !! *** ROUTINE ice_thd_zdf *** !! !! ** Purpose : select the appropriate routine for the computation !! of vertical diffusion !!------------------------------------------------------------------- SELECT CASE ( nice_zdf ) ! Choose the vertical heat diffusion solver ! ! !-------------! CASE( np_BL99 ) ! BL99 solver ! ! !-------------! SELECT CASE( nice_jules ) ! ! No Jules coupler ==> default option CASE( np_jules_OFF ) ; CALL ice_thd_zdf_BL99 ( np_jules_OFF ) ! ! ! Jules coupler is emulated => 1st call to get the needed fields (conduction...) ! 2nd call to use these fields to calculate heat diffusion CASE( np_jules_EMULE ) ; CALL ice_thd_zdf_BL99 ( np_jules_EMULE ) CALL ice_thd_zdf_BL99 ( np_jules_ACTIVE ) ! ! ! Jules coupler is active ==> Met Office default option CASE( np_jules_ACTIVE ) ; CALL ice_thd_zdf_BL99 ( np_jules_ACTIVE ) ! END SELECT ! END SELECT END SUBROUTINE ice_thd_zdf SUBROUTINE ice_thd_zdf_init !!----------------------------------------------------------------------- !! *** ROUTINE ice_thd_zdf_init *** !! !! ** Purpose : Physical constants and parameters associated with !! ice thermodynamics !! !! ** Method : Read the namthd_zdf namelist and check the parameters !! called at the first timestep (nit000) !! !! ** input : Namelist namthd_zdf !!------------------------------------------------------------------- INTEGER :: ios, ioptio ! Local integer !! NAMELIST/namthd_zdf/ ln_zdf_BL99, ln_cndi_U64, ln_cndi_P07, rn_cnd_s, rn_kappa_i !!------------------------------------------------------------------- ! REWIND( numnam_ice_ref ) ! Namelist namthd_zdf in reference namelist : Ice thermodynamics READ ( numnam_ice_ref, namthd_zdf, IOSTAT = ios, ERR = 901) 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd_zdf in reference namelist', lwp ) REWIND( numnam_ice_cfg ) ! Namelist namthd_zdf in configuration namelist : Ice thermodynamics READ ( numnam_ice_cfg, namthd_zdf, IOSTAT = ios, ERR = 902 ) 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd_zdf in configuration namelist', lwp ) IF(lwm) WRITE ( numoni, namthd_zdf ) ! ! IF(lwp) THEN ! control print WRITE(numout,*) 'ice_thd_zdf_init: Ice vertical heat diffusion' WRITE(numout,*) '~~~~~~~~~~~~~~~~' WRITE(numout,*) ' Namelist namthd_zdf:' WRITE(numout,*) ' Bitz and Lipscomb (1999) formulation ln_zdf_BL99 = ', ln_zdf_BL99 WRITE(numout,*) ' thermal conductivity in the ice (Untersteiner 1964) ln_cndi_U64 = ', ln_cndi_U64 WRITE(numout,*) ' thermal conductivity in the ice (Pringle et al 2007) ln_cndi_P07 = ', ln_cndi_P07 WRITE(numout,*) ' thermal conductivity in the snow rn_cnd_s = ', rn_cnd_s WRITE(numout,*) ' extinction radiation parameter in sea ice rn_kappa_i = ', rn_kappa_i ENDIF ! IF ( ( ln_cndi_U64 .AND. ln_cndi_P07 ) .OR. ( .NOT.ln_cndi_U64 .AND. .NOT.ln_cndi_P07 ) ) THEN CALL ctl_stop( 'ice_thd_zdf_init: choose one and only one formulation for thermal conduction (ln_cndi_U64 or ln_cndi_P07)' ) ENDIF ! !== set the choice of ice vertical thermodynamic formulation ==! ioptio = 0 IF( ln_zdf_BL99 ) THEN ; ioptio = ioptio + 1 ; nice_zdf = np_BL99 ; ENDIF ! BL99 thermodynamics (linear liquidus + constant thermal properties) !! IF( ln_zdf_XXXX ) THEN ; ioptio = ioptio + 1 ; nice_zdf = np_XXXX ; ENDIF IF( ioptio /= 1 ) CALL ctl_stop( 'ice_thd_init: one and only one ice thermo option has to be defined ' ) ! END SUBROUTINE ice_thd_zdf_init #else !!---------------------------------------------------------------------- !! Default option Dummy Module No ESIM sea-ice model !!---------------------------------------------------------------------- #endif !!====================================================================== END MODULE icethd_zdf