source: branches/2016/dev_v3.20_2016_platelet/SOURCES/source_3.20/ice_th.f @ 34

Last change on this file since 34 was 29, checked in by vancop, 8 years ago

Add ice_sal_adv routine for GN13

File size: 5.7 KB
Line 
1      SUBROUTINE ice_th(nlay_i,nlay_s)
2
3        !!------------------------------------------------------------------
4        !!                ***         ROUTINE ice_th       ***
5        !! ** Purpose :
6        !!           Ice thermodynamics
7        !! ** Method  :
8        !!    This routine calls the thermodynamic and biological routines
9        !!
10        !! ** Arguments :
11        !!           nlay_i, nlay_s
12        !!
13        !! ** Inputs / Ouputs : (global commons)
14        !!
15        !! ** External :
16        !!
17        !! ** References : Vancoppenolle et al., JGR 2007
18        !!
19        !! ** History :
20        !!       (1) CLIO, Goosse and Fichefet, JGR, 1999.
21        !!       (2) LIM-1D, Vancoppenolle et al., JGR, 2007.
22        !!       (3) BIO-LIM, Martin Vancoppenolle, 2008
23        !!
24        !!------------------------------------------------------------------
25        !! * Arguments
26
27      INCLUDE 'type.com'
28      INCLUDE 'para.com'
29      INCLUDE 'const.com'
30      INCLUDE 'ice.com'
31      INCLUDE 'thermo.com'
32      INCLUDE 'bio.com'
33
34      ! Energy conservation
35      LOGICAL con_i
36
37      zeps0 = 1.0e-16
38      zeps1 = 1.0e-20
39      zeps2 = 1.0e-04
40
41      con_i = .true. ! conservation check in the ice or not
42      jl = 1         ! category number (temporary)
43      ji = 1         ! ji index
44
45      WRITE(numout,*) ' * ice_th : '
46      WRITE(numout,*) ' ~~~~~~~~~~ '
47      WRITE(numout,*) 
48      WRITE(numout,*) ' nlay_i : ', nlay_i
49      WRITE(numout,*) ' nlay_s : ', nlay_s
50      WRITE(numout,*) 
51!
52!-------------------------------------------------------------------------------
53!  1) Initialize sea ice
54!-------------------------------------------------------------------------------
55!
56
57      IF ( numit .EQ. nstart ) THEN
58         CALL ice_phy_ini( 1 , 1 , nlay_s, nlay_i)
59
60         IF ( c_bio_model .EQ. 'KRILL' )
61     &   CALL ice_bio_ini( 1 , 1 , nlay_i )                     ! Bio initialization - KRILL
62
63      ENDIF
64!
65!-------------------------------------------------------------------------------
66!  2) Consistency & Energetic checks
67!-------------------------------------------------------------------------------
68!
69
70      DO layer = 1, nlay_s
71         t_s_b(ji,layer)  =  MIN( tpw , t_s_b(ji,layer) )
72      END DO
73
74      DO layer = 1, nlay_i
75         tmelts           =  - tmut*s_i_b(ji,layer) + tpw
76         t_i_b(ji,layer)  =  MIN(tmelts,t_i_b(ji,layer))
77      END DO
78
79      CALL ice_th_enmelt(1,1, nlay_s, nlay_i) ! ice enthalpy
80
81      ! Initialize total heat content
82      IF ( con_i ) CALL ice_th_glohec( qt_i_in , qt_s_in ,             
83     &                                 q_i_layer_in , 1 , 1 , jl, 
84     &                                 nlay_s , nlay_i )
85!
86!-------------------------------------------------------------------------------
87!  3) Model routines
88!-------------------------------------------------------------------------------
89!
90      CALL forcing                                              ! Compute forcing
91
92      CALL ice_rad( nlay_s , nlay_i , 1 , 1 )                   ! Radiative transfer
93
94      CALL ice_th_diff( nlay_s , nlay_i , 1 , 1 )               ! Heat diffusion
95
96      IF ( con_i ) THEN                                         ! Conservation test
97         CALL ice_th_glohec( qt_i_fin , qt_s_fin , q_i_layer_fin ,
98     &                       1 , 1 , jl , nlay_s , nlay_i )
99         CALL ice_th_con_dif( 1 , 1 , nlay_s , nlay_i , jl )
100      ENDIF
101
102      IF ( c_gravdr .EQ. 'CW' )
103     &   CALL ice_sal_diff_CW(nlay_i,1,1)                       ! Salt transport (Cox and Weeks)
104
105      IF ( c_gravdr .EQ. 'RA' )
106     &   CALL ice_sal_diff(nlay_i,1,1)                          ! Salt transport (Rayleigh-number based)
107
108      IF ( c_gravdr .EQ. 'AD' ) 
109     &   CALL ice_sal_adv(nlay_i,1,1)                           ! Salt transport (Advection-based)
110
111      IF ( ( c_bio_model .EQ. 'KRILL' ) .AND. ln_trdiff )
112     &   CALL ice_bio_diff( 1 , 1 , nlay_i )                    ! Bio transport
113
114      IF ( c_bio_model .EQ. 'KRILL' )
115     &   CALL ice_bio_sms(nlay_i,1,1)                           ! KRILL source minus sinks
116     
117      IF ( ln_ikaite ) 
118     &   CALL ice_ikaite(nlay_i)                                ! Ikaite precipitation and dissolution
119
120      CALL ice_gas(nlay_i,1,1)                                  ! Gases
121
122      CALL ice_th_dh(nlay_s,nlay_i,1,1)                         ! Growth and melt
123
124      CALL ice_phy_remap(nlay_s,nlay_i,1,1)                     ! Remap heat and salt
125
126      IF ( con_i ) THEN                                         ! Heat and salt conservation test
127         CALL ice_th_glohec( qt_i_fin , qt_s_fin , q_i_layer_fin ,
128     &                       1 , 1 , jl, nlay_s, nlay_i )
129         CALL ice_th_con_dh(1,1,nlay_s,nlay_i,jl)
130      ENDIF
131
132      IF ( ln_trremp )     
133     &   CALL ice_bio_remap(nlay_s, nlay_i, 1, 1)               ! Remap tracers
134
135      CALL ice_bio_column(kideb,kiut,ntra_bio,ct_i_bio,cbu_i_bio,
136     &                    deltaz_i_bio, .FALSE.)
137     
138      !---------------
139      ! Chlorophyll a
140      !---------------
141      IF ( c_bio_model .EQ. 'KRILL' ) THEN
142         DO layer = 1, nlay_bio
143            chla_i_bio(layer) = cbu_i_bio(4,layer) * chlC_bio(layer) *
144     &                          c_molar
145         END DO
146      ENDIF ! c_bio_model
147
148      IF ( c_bio_model .NE. 'NOBIO' ) 
149     &   WRITE(numout,*) ' chla_i_bio : ', ( chla_i_bio(layer), 
150     &                   layer = 1, nlay_bio )
151
152!-------------------------------------------------------------------------------
153!  4) Outputs
154!-------------------------------------------------------------------------------
155!
156      !---------------
157      ! Netcdf Output
158      !---------------
159      CALL ice_output(nlay_i,nlay_s)
160
161      RETURN
162!
163!------------------------------------------------------------------------------
164!- end of ice_th
165      END
Note: See TracBrowser for help on using the repository browser.