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.
icethd_zdf.F90 in NEMO/trunk/src/ICE – NEMO

source: NEMO/trunk/src/ICE/icethd_zdf.F90 @ 10410

Last change on this file since 10410 was 10069, checked in by nicolasmartin, 6 years ago

Fix mistakes of previous commit on SVN keywords property

  • Property svn:keywords set to Id
File size: 6.9 KB
RevLine 
[8586]1MODULE icethd_zdf
2   !!======================================================================
3   !!                       ***  MODULE icethd_zdf ***
[9604]4   !!   sea-ice: master routine for vertical heat diffusion in sea ice
[8586]5   !!======================================================================
[9604]6   !! History :  4.0  !  2018     (C. Rousset)      Original code SI3
[8586]7   !!----------------------------------------------------------------------
[9570]8#if defined key_si3
[8586]9   !!----------------------------------------------------------------------
[9570]10   !!   'key_si3'                                       SI3 sea-ice model
[8586]11   !!----------------------------------------------------------------------
[8813]12   !!  ice_thd_zdf      : select the appropriate routine for vertical heat diffusion calculation
[9604]13   !!  ice_thd_zdf_BL99 : heat diffusion from Bitz and Lipscomb 1999
14   !!  ice_thd_zdf_init : initialization
[8813]15   !!----------------------------------------------------------------------
[8984]16   USE dom_oce         ! ocean space and time domain
17   USE phycst          ! physical constants (ocean directory)
18   USE ice             ! sea-ice: variables
19   USE icethd_zdf_BL99 ! sea-ice: vertical diffusion (Bitz and Lipscomb, 1999)
[8586]20   !
[8984]21   USE in_out_manager  ! I/O manager
22   USE lib_mpp         ! MPP library
23   USE lib_fortran     ! fortran utilities (glob_sum + no signed zero)
[8586]24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   ice_thd_zdf        ! called by icethd
29   PUBLIC   ice_thd_zdf_init   ! called by icestp
30
[8984]31   INTEGER ::   nice_zdf       ! Choice of the type of vertical heat diffusion formulation
32   !                                 ! associated indices:
33   INTEGER, PARAMETER ::   np_BL99 = 1   ! Bitz and Lipscomb (1999)
34!! INTEGER, PARAMETER ::   np_XXXX = 2
35
[8586]36   !!** namelist (namthd_zdf) **
[8984]37   LOGICAL ::   ln_zdf_BL99    ! Heat diffusion follows Bitz and Lipscomb (1999)
[8586]38
39   !!----------------------------------------------------------------------
[9598]40   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
[10069]41   !! $Id$
[10068]42   !! Software governed by the CeCILL license (see ./LICENSE)
[8586]43   !!----------------------------------------------------------------------
44CONTAINS
45
46   SUBROUTINE ice_thd_zdf
47      !!-------------------------------------------------------------------
48      !!                ***  ROUTINE ice_thd_zdf  ***
49      !!
[8813]50      !! ** Purpose :   select the appropriate routine for the computation
51      !!              of vertical diffusion
52      !!-------------------------------------------------------------------
[9124]53      !
[8813]54      SELECT CASE ( nice_zdf )      ! Choose the vertical heat diffusion solver
55      !
[8984]56      !                             !-------------!     
57      CASE( np_BL99 )               ! BL99 solver !
58         !                          !-------------!
[8813]59         SELECT CASE( nice_jules )
[8984]60         !                         ! No Jules coupler ==> default option
61         CASE( np_jules_OFF    )   ;   CALL ice_thd_zdf_BL99 ( np_jules_OFF    )
[8813]62         !
[8984]63         !                         ! Jules coupler is emulated => 1st call to get the needed fields (conduction...)
64         !                                                        2nd call to use these fields to calculate heat diffusion   
65         CASE( np_jules_EMULE  )   ;   CALL ice_thd_zdf_BL99 ( np_jules_EMULE  )
66                                       CALL ice_thd_zdf_BL99 ( np_jules_ACTIVE )
[8813]67         !
[8984]68         !                         ! Jules coupler is active ==> Met Office default option
69         CASE( np_jules_ACTIVE )   ;   CALL ice_thd_zdf_BL99 ( np_jules_ACTIVE )
[8813]70         !
[8586]71         END SELECT
72         !
[8984]73      END SELECT
[9124]74      !
[8984]75   END SUBROUTINE ice_thd_zdf
[8813]76   
[8984]77   
[8586]78   SUBROUTINE ice_thd_zdf_init
79      !!-----------------------------------------------------------------------
80      !!                   ***  ROUTINE ice_thd_zdf_init ***
81      !!                 
82      !! ** Purpose :   Physical constants and parameters associated with
83      !!                ice thermodynamics
84      !!
85      !! ** Method  :   Read the namthd_zdf namelist and check the parameters
86      !!                called at the first timestep (nit000)
87      !!
88      !! ** input   :   Namelist namthd_zdf
89      !!-------------------------------------------------------------------
[8813]90      INTEGER  ::   ios, ioptio   ! Local integer
[8586]91      !!
[8813]92      NAMELIST/namthd_zdf/ ln_zdf_BL99, ln_cndi_U64, ln_cndi_P07, rn_cnd_s, rn_kappa_i
[8586]93      !!-------------------------------------------------------------------
94      !
95      REWIND( numnam_ice_ref )              ! Namelist namthd_zdf in reference namelist : Ice thermodynamics
96      READ  ( numnam_ice_ref, namthd_zdf, IOSTAT = ios, ERR = 901)
[9169]97901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namthd_zdf in reference namelist', lwp )
[8586]98      REWIND( numnam_ice_cfg )              ! Namelist namthd_zdf in configuration namelist : Ice thermodynamics
99      READ  ( numnam_ice_cfg, namthd_zdf, IOSTAT = ios, ERR = 902 )
[9169]100902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namthd_zdf in configuration namelist', lwp )
101      IF(lwm) WRITE( numoni, namthd_zdf )
[8586]102      !
103      IF(lwp) THEN                          ! control print
[9169]104         WRITE(numout,*)
[8586]105         WRITE(numout,*) 'ice_thd_zdf_init: Ice vertical heat diffusion'
106         WRITE(numout,*) '~~~~~~~~~~~~~~~~'
107         WRITE(numout,*) '   Namelist namthd_zdf:'
[8813]108         WRITE(numout,*) '      Bitz and Lipscomb (1999) formulation                    ln_zdf_BL99  = ', ln_zdf_BL99
[8586]109         WRITE(numout,*) '      thermal conductivity in the ice (Untersteiner 1964)     ln_cndi_U64  = ', ln_cndi_U64
110         WRITE(numout,*) '      thermal conductivity in the ice (Pringle et al 2007)    ln_cndi_P07  = ', ln_cndi_P07
111         WRITE(numout,*) '      thermal conductivity in the snow                        rn_cnd_s     = ', rn_cnd_s
112         WRITE(numout,*) '      extinction radiation parameter in sea ice               rn_kappa_i   = ', rn_kappa_i
[8984]113      ENDIF
[8586]114      !
[9119]115      IF ( ( ln_cndi_U64 .AND. ln_cndi_P07 ) .OR. ( .NOT. ln_cndi_U64 .AND. .NOT. ln_cndi_P07 ) ) THEN
116         CALL ctl_stop( 'ice_thd_zdf_init: choose 1 and only 1 formulation for thermal conduction (ln_cndi_U64 or ln_cndi_P07)' )
[8586]117      ENDIF
[8813]118      !                             !== set the choice of ice vertical thermodynamic formulation ==!
119      ioptio = 0 
[8984]120      IF( ln_zdf_BL99 ) THEN   ;   ioptio = ioptio + 1   ;   nice_zdf = np_BL99   ;   ENDIF   ! BL99 thermodynamics (linear liquidus + constant thermal properties)
121!!    IF( ln_zdf_XXXX ) THEN   ;   ioptio = ioptio + 1   ;   nice_zdf = np_XXXX   ;   ENDIF
122      IF( ioptio /= 1 )   CALL ctl_stop( 'ice_thd_init: one and only one ice thermo option has to be defined ' )
[8586]123      !
124   END SUBROUTINE ice_thd_zdf_init
125
126#else
127   !!----------------------------------------------------------------------
[9570]128   !!   Default option       Dummy Module             No SI3 sea-ice model
[8586]129   !!----------------------------------------------------------------------
130#endif
131
132   !!======================================================================
133END MODULE icethd_zdf
Note: See TracBrowser for help on using the repository browser.