source: trunk/SOURCES/source_3.20/ice_phy_param.f @ 4

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

initial import /Users/ioulianikolskaia/Boulot/CODES/LIM1D/ARCHIVE/TMP/LIM1D_v3.20/

File size: 10.2 KB
RevLine 
[4]1      SUBROUTINE ice_phy_param
2
3        !!------------------------------------------------------------------
4        !!                ***  ROUTINE ice_phy_param ***
5        !! ** Purpose :
6        !!           Defines physical constants & params of the model
7        !! ** Method  :
8        !!           Definitions !!!
9        !!
10        !! ** Arguments :
11        !!           n99
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 'const.com'
29      INCLUDE 'para.com'
30      INCLUDE 'ice.com'
31
32      ! name of the experiment
33      CHARACTER(len=8) exp_id
34
35      ! Formats for reading the initial salinity profile
36      CHARACTER(len=1) zc1
37      CHARACTER(len=2) zc2
38      CHARACTER(len=7) zformat1
39      CHARACTER(len=7) zformat2
40      CHARACTER(len=8) zformat3
41
42!
43!-----------------------------------------------------------------------
44!  1 ) Lecture des parametres du run
45!-----------------------------------------------------------------------
46!
47      WRITE(numout,*) ' * ice_phy_param : '
48      WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~'
49
50      OPEN(unit=10,file='run.param',status='old')
51
52      READ(10,*)
53      READ(10,*)
54      READ(10,*)
55      READ(10,*)
56      READ(10,*)
57      READ(10,*)
58      READ(10,*) exp_id     ! name of the experiment
59      READ(10,*)
60      READ(10,*) ddtb       ! time step
61      READ(10,*)
62      READ(10,*) nstart     ! number of the first iteration
63      READ(10,*)
64      READ(10,*) nend       ! number of the last iteration
65      READ(10,*)
66      READ(10,*) nyear      ! initial year
67      READ(10,*)
68      READ(10,*) nfr_out    ! output frequency
69      READ(10,*)
70      READ(10,*) rlat       ! latitude
71      READ(10,*) 
72      READ(10,*) c_bio_model ! biological model
73      READ(10,*) 
74      WRITE(numout,*) ' Type of biological model ( c_bio_model ) : ', 
75     &                  c_bio_model
76      WRITE(numout,*)
77
78      nitrun    = nend - nstart + 1
79
80      CLOSE(10)
81!
82!-----------------------------------------------------------------------
83!  2 ) Mathematical constants
84!-----------------------------------------------------------------------
85!
86      c_zero  = 0.d0              ! zero
87      one     = 1.d0              ! one
88      pi     = 4.0 * atan(one)    ! pi
89      radian = pi / 180.0         ! conversion degrees to radians
90
91!------------------------------------------------------------------------------
92!  3 ) Physical constants
93!------------------------------------------------------------------------------
94
95      !-----------------------
96      ! Fundamental constants
97      !-----------------------
98      gpes   = 9.80d0             ! gravity
99      stefan = 5.6697d-08         ! stefan-boltzmann constant
100      vkarmn = 0.40d0             ! von karmann constant
101      cevap  = 2.5d+06            ! heat transfer coefficient for latent heat... check!!!
102      zemise = 0.97d0             ! R, sea water emissivity (remove also)
103
104      !---------------
105      ! Ocean physics
106      !---------------
107      tpw     = 273.16d0          ! water triple point
108      rho0    = 1025.0            ! ocean mean density
109      cpw     = 3.99d+03          ! seawater specific heat
110      oce_sal = 34.0              ! 34. is the control
111
112      visc_br = 1.79e-3           ! dynamic viscosity of water at 0C
113      beta_ocs= 0.81              ! regulates density changes due to changes in salinity
114
115      !-----------------
116      ! Sea ice physics
117      !-----------------
118 
119      !-- thermal properties
120      tfsn   = 273.16d0           ! snow melting point
121      tfsg   = 273.16d0           ! sea ice melting point
122      xkn    = 0.31d0             ! 0.31d0 ISPOL Olivier Lecomte communication ! ref value 0.31d0 ! snow thermal conductivity
123      xkg    = 2.034d0            ! pure ice thermal conductivity
124      rhog   = 917.0              ! sea ice density
125      rhon   = 330.d0             ! O. Lecomte says 355 could be used
126      cpg    = 2.062d+03          ! sea ice specific heat (J/kg/K)
127      lfus   = 3.335d+05          ! pure ice latent heat (J/kg)
128      lvap   = 2.501e+06          ! latent heat of vaporization of water (0°C J/kg)
129      lsub   = lfus  + lvap       ! sublimation latent heat
130      tmut   = 0.054d0            ! rate between seawater freezing point and salinity (linear model)
131      betak1 = 0.09d0             ! first Pringle th. cond. constant
132      betak2 = 0.011d0            ! second Pringle th. cond. constant
133!     emig   = 0.99d0             ! surface emissivity (read later)
134
135      !---------------------------
136      ! Model physical parameters
137      !---------------------------
138      OPEN(unit=25,file='icephys.param', status='old')
139
140      READ(25,*)
141      READ(25,*)
142      READ(25,*)
143      READ(25,*)
144      READ(25,*)                 
145      READ(25,*)
146      READ(25,*)
147      READ(25,*)
148      READ(25,*) 
149      READ(25,*)                 
150      READ(25,*)
151      READ(25,*)
152      READ(25,*)
153      READ(25,*)               
154      READ(25,*) n_i              ! number of layers in the ice
155      READ(25,*)
156      READ(25,*) n_s              ! number of layers in the snow
157      READ(25,*)
158      READ(25,*) parsub           ! switch for sublimation or not
159      READ(25,*)
160      READ(25,*) ln_evap          ! switch for snow evaporation or not
161      READ(25,*)                  !
162      READ(25,*) tabq_ano         ! Prescribed air temperature anomalies
163      READ(25,*)
164      READ(25,*)
165      READ(25,*)
166      READ(25,*)
167      READ(25,*)
168      READ(25,*)
169      READ(25,*) ln_grd           ! gravity drainage or not
170      READ(25,*)
171      READ(25,*) ln_flu           ! flushing or not
172      READ(25,*)
173      READ(25,*) ln_flo           ! flooding or not
174      READ(25,*)
175      READ(25,*) flu_beta         ! fraction of meltwater percolating
176      READ(25,*)
177      READ(25,*) e_thr_flu        ! permeability threshold for flushing
178      READ(25,*)
179      READ(25,*) frtr_si_phy      ! fractionation coeff in snow ice
180      READ(25,*)
181      READ(25,*) d_br_mol         ! molecular diffusivity of brine
182      READ(25,*)
183      READ(25,*) d_br_tur         ! turbulent diffusivity of brine
184      READ(25,*)
185      READ(25,*) ra_c             ! critical rayleigh number over which convection starts
186      READ(25,*)
187      READ(25,*) ra_smooth        ! coefficient to smooth the hyperbolic tangential for ra_c
188      READ(25,*)
189      READ(25,'(a2)') gravdr      ! type of gravity drainage
190      READ(25,*)
191      READ(25,*) delta_cw         ! Cox and weeks gravity drainage parameter
192      READ(25,*)
193      READ(25,*)
194      READ(25,*)
195      READ(25,*)
196      READ(25,*)
197      READ(25,*)
198      READ(25,*) emig
199      READ(25,*)
200      READ(25,*) fpar_fsw
201      READ(25,*)
202      READ(25,*) qpar_fsw
203      READ(25,*)
204      READ(25,*) c_rad_scheme
205      READ(25,*)
206      READ(25,*) c_rad_discr 
207      READ(25,*)
208      READ(25,*) rad_inot_s_dry   ! surface transmission parameter, dry snow
209      READ(25,*)
210      READ(25,*) rad_inot_s_wet   ! surface transmission parameter, wet snow
211      READ(25,*)
212      READ(25,*) rad_inot_i_dry   ! surface transmission parameter, dry ice
213      READ(25,*)
214      READ(25,*) rad_inot_i_wet   ! surface transmission parameter, wet ice
215      READ(25,*)
216      READ(25,*) h_not_s          ! SSL thickness, snow
217      READ(25,*)
218      READ(25,*) h_not_i          ! SSL thickness, ice
219      READ(25,*)
220      READ(25,*) rad_kappa_s_su_d ! surface extinction coefficient, dry snow
221      READ(25,*)
222      READ(25,*) rad_kappa_s_su_m ! surface extinction coefficient, melting snow
223      READ(25,*)
224      READ(25,*) rad_kappa_i_su_d ! surface extinction coefficient, cold ice
225      READ(25,*)
226      READ(25,*) rad_kappa_i_su_m ! surface extinction coefficient, melting ice
227      READ(25,*)
228      READ(25,*) rad_kappa_s_de_d ! depth extinction coefficient, dry snow
229      READ(25,*)
230      READ(25,*) rad_kappa_s_de_m ! depth extinction coefficient, wet snow
231      READ(25,*)
232      READ(25,*) rad_kappa_i_de_d ! attenuation coefficient, cold ice
233      READ(25,*)
234      READ(25,*) rad_kappa_i_de_m ! attenuation coefficient, melting ice
235      READ(25,*)
236
237      WRITE(numout,*) ' n_i        :', n_i
238      WRITE(numout,*) ' n_s        :', n_s
239      WRITE(numout,*) ' parsub     :', parsub
240      WRITE(numout,*) ' ln_evap    :', ln_evap
241      WRITE(numout,*) ' tabq_ano   :', tabq_ano
242      WRITE(numout,*) ' ln_grd     :', ln_grd
243      WRITE(numout,*) ' ln_flu     :', ln_flu
244      WRITE(numout,*) ' ln_flo     :', ln_flo
245      WRITE(numout,*) ' flu_beta   :', flu_beta
246      WRITE(numout,*) ' frtr_si_phy:', frtr_si_phy
247      WRITE(numout,*) ' d_br_mol   :', d_br_mol
248      WRITE(numout,*) ' d_br_tur   :', d_br_tur
249      WRITE(numout,*) ' ra_c       :', ra_c
250      WRITE(numout,*) ' ra_smooth  :', ra_smooth
251      WRITE(numout,*) ' gravdr     :', gravdr
252      WRITE(numout,*) ' delta_cw   :', delta_cw
253      WRITE(numout,*) ' emig        :', emig
254      WRITE(numout,*) ' fpar_fsw    :', fpar_fsw
255      WRITE(numout,*) ' qpar_fsw    :', qpar_fsw
256      WRITE(numout,*) ' c_rad_scheme:', c_rad_scheme
257      WRITE(numout,*) ' c_rad_discr: ', c_rad_discr
258      WRITE(numout,*) ' rad_inot_s_dry : ', rad_inot_s_dry
259      WRITE(numout,*) ' rad_inot_s_wet : ', rad_inot_s_wet
260      WRITE(numout,*) ' rad_inot_i_dry : ', rad_inot_i_dry
261      WRITE(numout,*) ' rad_inot_i_wet : ', rad_inot_i_wet
262      WRITE(numout,*) ' h_not_s    : ', h_not_s
263      WRITE(numout,*) ' h_not_i    : ', h_not_i
264      WRITE(numout,*) ' rad_kappa_s_su_d : ', rad_kappa_s_su_d
265      WRITE(numout,*) ' rad_kappa_s_su_m : ', rad_kappa_s_su_m
266      WRITE(numout,*) ' rad_kappa_i_su_d : ', rad_kappa_i_su_d
267      WRITE(numout,*) ' rad_kappa_i_su_m : ', rad_kappa_i_su_m
268      WRITE(numout,*) ' rad_kappa_s_de_d : ', rad_kappa_s_de_d
269      WRITE(numout,*) ' rad_kappa_s_de_m : ', rad_kappa_s_de_m
270      WRITE(numout,*) ' rad_kappa_i_de_d : ', rad_kappa_i_de_d
271      WRITE(numout,*) ' rad_kappa_i_de_m : ', rad_kappa_i_de_m
272      WRITE(numout,*)
273
274      CLOSE(25)
275
276!------------------------------------------------------------------------------
277      RETURN
278      END
Note: See TracBrowser for help on using the repository browser.