source: branches/iLoveclim/SOURCES/initial-phy-2.f90 @ 123

Last change on this file since 123 was 123, checked in by aquiquet, 7 years ago

Merged branch iLOVECLIM to trunk at rev 121

File size: 8.2 KB
Line 
1!> \file initial-phy-2.f90
2!! Initialisation des parametres physique du modele
3!<
4
5!> SUBROUTINE: initial_phy
6!! Subroutine qui initialise les parametres physique du modele
7!! \author ...
8!! \date ...
9!! @note Used modules:
10!! @note    - module3D_phy
11!!
12!<
13subroutine initial_phy
14
15  !     **************************************************
16  !     **         initialisation                        *
17  !     *                                                *
18  !     **************************************************
19
20  use module3D_phy
21  use param_phy_mod
22
23  implicit none
24
25  character(len=80) :: filin
26  character(len=80) :: comment_run
27
28  namelist/runpar/runname,icompteur,iout,reprcptr,itracebug,num_tracebug,comment_run
29  namelist/grdline/igrdline,Schoof
30  namelist/timesteps/dtmin,dtmax,dtt,testdiag,tbegin,tend
31
32
33  ! ouverture du fichier parametre ..._param_list.dat
34  !--------------------------------------------------------------
35  ! dirsource='SOURCES'
36!dcdmr --- GRISLI - LOVECLIM
37!  dirsource='../../SOURCES'
38  dirsource='inputdata/grisli'
39  ! filin='../'//trim(dirsource)//'/Fichiers-parametres/'//trim(geoplace)//'_param_list.dat'
40!  filin=trim(geoplace)//'_param_list.dat'
41  filin='./'//trim(dirsource)//'/'//trim(geoplace)//'_param_list.dat'
42!dcdmr --- GRISLI - LOVECLIM
43  open(num_param,file=filin) 
44
45
46  ! lecture des parametres du run                          block runpar
47  !--------------------------------------------------------------------
48
49  rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
50  read(num_param,runpar)
51
52
53  ! ouverture du fichier num_rep_42
54  !-------------------------------------
55428 format(A)             ! formats pour les ecritures dans 42
56!dcdmr --- GRISLI - LOVECLIM
57!  filin='param'//runname
58  filin='restartdata/param'//runname
59!dcdmr --- GRISLI - LOVECLIM
60  open(num_rep_42,file=filin)
61
62  ! reecriture des parametres entres dans le fichier 42
63  !------------------------------------------------------
64  write(num_rep_42,*)'!  Parametres du run :',runname, '    ',geoplace
65  write(num_rep_42,*)'!  sources dans  ',trim(dirsource)
66  write(num_rep_42,*)
67  write(num_rep_42,428)'!___________________________________________________________' 
68  write(num_rep_42,428) '&runpar                  ! nom du bloc  parametres du run'
69  write(num_rep_42,*)
70  write(num_rep_42,*) 'runname      =  "',runname,'"'
71  write(num_rep_42,*) 'icompteur    = ', icompteur                             
72  write(num_rep_42,*) 'iout    = ', iout 
73  write(num_rep_42,*) 'reprcptr     = "',trim(reprcptr),'"'
74  write(num_rep_42,*) 'num_tracebug  = ', num_tracebug
75  write(num_rep_42,*) 'comment_run   ="',trim(comment_run),'"'
76  write(num_rep_42,*)'/'                           
77  write(num_rep_42,428) '! runname    : nom de l experience (8 caracteres)  '
78  write(num_rep_42,428) '! icompteur  : reprise dans un fichier  0 -> non, 1 -> oui, 2 -> T et Hw'
79  write(num_rep_42,428) '! icompteur  : 3-> T seulement'
80  write(num_rep_42,428) '! iout   : 1-> sortie cptr pour reprise,2 -> sortie nc pour reprise '
81  write(num_rep_42,428) '! reprcptr   : nom du fichier'
82  write(num_rep_42,428) '! itracebug: 1-> ecriture de traces au debut des routines'
83  write(num_rep_42,428) '! num_tracebug   numero d unite ecriture traces'
84  write(num_rep_42,428) '! comment_run: commentaire court sur le run'
85
86  write(num_rep_42,*)
87
88
89
90  !     switch reprise compteur ou non: 1 => compteur, 0 => pas compteur
91  !     icompteur=2 reprise de tout sauf de la topo
92  !     icompteur=1 reprise de tout
93
94  !      reprcptr=TRIM('../CPTR-Heino/Heino096+k150.CPTR')
95
96
97
98
99  write(6,*)'_________________________________________________'
100  write(6,*)'runname=',runname
101  !      write(6,*) dirnameout
102  !      write(6,*) TRIM(DIRNAMEOUT)//'short'//runname//'.ritz'
103
104
105  ! ouverture du fichier short
106  !------------------------------
107
108  ! filin='time-series/short'//runname//'.ritz'
109  filin='short'//runname//'.ritz'
110  filin=TRIM(DIRNAMEOUT)//TRIM(filin)
111
112  open(num_ritz,file=filin)
113
114
115
116  ! lecture des parametres du run                          block grdline
117  !--------------------------------------------------------------------
118
119
120  rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
121  read(num_param,grdline)
122
123
124  write(num_rep_42,428)'!___________________________________________________________' 
125  write(num_rep_42,428) '&grdline                 ! bloc grounding line'
126  write(num_rep_42,*)
127  write(num_rep_42,*) 'igrdline     = ',igrdline
128  write(num_rep_42,*) 'Schoof       = ',Schoof
129  write(num_rep_42,*)'/'                           
130  write(num_rep_42,428)'! igrdline :  1 ligne d echouage fixée, sinon 0'
131  write(num_rep_42,428)'! Schoof   :  0 pas de Schoof, 1 flux de Schoof'
132  write(num_rep_42,*)
133
134
135  !     grounding line fixee
136  !--------------------------
137  !     Pour faire des expériences avec l'épaisseur des ice-shelves fixée
138  !     igrdline=1 !fixé, sinon (libre) igrdline=0
139  !     igrdline=0
140
141
142
143  ! lecture des parametres du run                          block timesteps
144  !-----------------------------------------------------------------------
145  rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
146  read(num_param,timesteps)
147
148  write(*,*) "Le temps dans initial-phy-2.F90", time, tbegin
149
150! dmr&aurel ##  namelist/timesteps/dtmin,dtmax,dtt,testdiag,tbegin,tend
151  write(num_rep_42,428)'!___________________________________________________________' 
152  write(num_rep_42,428) '&timesteps                 ! bloc time steps'
153  write(num_rep_42,*)
154  write(num_rep_42,*) 'tend      = ',tend
155  write(num_rep_42,*) 'tbegin    = ',tbegin
156  write(num_rep_42,*) 'dtmin     = ',dtmin
157  write(num_rep_42,*) 'dtmax     = ',dtmax
158  write(num_rep_42,*) 'dtt       = ',dtt
159  write(num_rep_42,*) 'testdiag  = ',testdiag
160
161
162  write(num_rep_42,*)'/'                           
163  write(num_rep_42,428)'! tous les temps en annees. tbegin et tend : debut et fin du run '
164  write(num_rep_42,428)'! pour equation masse, pas de temps mini -> dtmin, maxi -> dtmax'     
165  write(num_rep_42,428)'! dtt : pas de temps long'
166  write(num_rep_42,428)'! testdiag, pour gérer le pas de temps dynamique dt'
167  write(num_rep_42,428)'! ordres de grandeur (a moduler selon dx) : '
168  write(num_rep_42,428)'! 40 km dtmin=2.e-2, dtmax=1., dtt=5., tesdiag=0.02'
169
170  write(num_rep_42,*)
171
172
173  !      si shelf rapide
174  !        testdiag=0.016
175
176  !---------------------------------------------------------------------
177  dt=dtmin           ! sera réattribue a chaque pas de temps
178  ntmax=90000000     ! nombre de tours maxi dans la boucle temps
179  dttest=dtmin       ! sert dans plein de tests
180  time=tbegin 
181  nt=-1
182
183
184
185  ! ----------------parametres dont le traitement en namelist est remis a plus tard
186
187
188  ! Tous les parametres liés à l'ablation devraient être dans un module ablation
189  ! A changer plus tard
190
191  !     temperature forcing : annual, july.
192  TAFOR=0.
193  TJFOR=0.0
194  SEALEVEL=0.0
195
196  SECYEAR=365.*24.*3600.
197  secyear= 31556926 ! s /an   pour Heino
198
199!!$!     *** ABLATION
200!!$!     integrating step for positive degree days (degrees)
201!!$      DTP=2.0
202!!$!     number of months in 1 year, st. dev. for temp *)
203!!$      NYEAR=12
204!!$      SIGMA=5.0
205!!$!     proportion of melted water that can refreeze *)
206!!$      CSI=0.6
207!!$!     melting factors for snow and ice
208!!$      Csnow=0.003
209!!$      Cice=0.008
210!!$!     ct for PDD calculation
211!!$      S22=0.5/SIGMA/SIGMA
212!!$      PY=2*PI/NYEAR
213!!$      PDDCT=DTP/SIGMA/sqrt(2.*PI)/NYEAR*365.
214
215
216! calcul de certain parametres de param_phy car ro et g ne sont plus parameter
217
218rog      = ro*g                !<  ro*g   (glace)
219rowg     = row*g               !<  row*g  (ocean)
220romg     = rom*g               !<  rom*g  (asthenosphere)
221rofreshg = rofresh*g           !<  rofresh*g
222d00      = ro**3*g**3          !<  ro**3*g**3
223dice     = ro/row              !<  ro/row
224
225coef_Sflot = (Row-Ro)/Row      !<   S = coef_Sflot * H + sealevel pour les shelves
226coef_Bflot = -Ro/Row           !<   B = coef_Bflot * H + sealevel pour les shelves
227
228  !---------------------
229
230
231  !     *** TEMPERATURE IN ICE AND MANTLE
232  !     Total number of vertical grid points, grid step in mantle
233  NZZ=NZ+NZM
234
235  !     specific latent heat of fusion of ice J/Kg
236  CL=3.35E5
237
238  !     DA mantle diffusion
239  DA=4.E7
240  !     switch
241  NICE=1
242  isynchro=0
243
244
245end subroutine initial_phy
Note: See TracBrowser for help on using the repository browser.