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 branches/2017/dev_merge_2017/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/LIM_SRC_3/icethd_zdf.F90 @ 9119

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

Fix longer lines so should be harmless (passed SETTE compilations)

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