source: branches/iLoveclim/SOURCES/initial-0.3.f90 @ 83

Last change on this file since 83 was 77, checked in by dumas, 8 years ago

Merge branche iLOVECLIM sur rev 76

File size: 4.7 KB
Line 
1!> \file initial-0.3.f90
2!!Initialisation du modele
3!<
4
5!> SUBROUTINE initial
6!! Cette routine permet d'initialiser le modele.
7!! \author ...
8!! \date 19 Novembre 1999
9!! @note Elle appelle toutes les routines d'initialisation des differents packages.
10!! @note  C'est cette routine qui est appellee dans le main
11!! @note  Used modules:
12!! @note    - use module3D_phy
13!! @note    - use module_choix
14!! @note    - use icetempmod
15!! @note    - use diagno_mod
16!! @note    - use resolmeca_SIA_L1
17!! @note    - use sorties_ncdf_grisli
18!! @note    - use util_recovery
19!<
20
21
22subroutine initial
23
24  use module3D_phy
25  use module_choix
26  use icetempmod
27  use diagno_mod 
28  use resolmeca_SIA_L1
29  use flottab_mod
30  use sorties_ncdf_grisli
31  use util_recovery
32
33  !-------------------------------------------------------------------------------------
34  ! nouvelles entrees modulaires  janvier 2006
35  call initial_phy()        ! La physique
36  call initial2             ! Initialisation des tableaux
37  !
38  call  input_topo()        ! La geographie
39
40  !------------------------------------------------------
41  ! initialisation du climat  (reference et forcage)
42!cdc  call input_climat_ref()  ! Le climat de reference
43  call init_forclim        ! parametres du forcage
44  call input_clim          ! lecture fichiers de forcage
45  call init_ablation       ! parametres du calcul de l'ablation
46  !-------------------------------------------------------------------------------------
47
48  ! aurel neem -> pour initialisation traceurs
49  call init_tracer 
50
51  !initialisation des lacs proglaciaires
52  call input_lakes     
53
54
55  ! call  input_profile()     ! Les fichiers profils
56  !
57
58  if (icompteur.ne.0) then ! reprise  d un fichier cptr
59     call read_recovery(icompteur)
60!dcdmr --- GRISLI - LOVECLIM
61!     time = tbegin
62!dcdmr --- GRISLI - LOVECLIM
63     call sortie_ncdf_cat
64!  else if (icompteur.eq.2) then ! reprise d'un fichier cptr mais sans la topo
65!     call read_recovery_temp
66
67!  else if (icompteur.eq.3) then ! reprise d'un fichier cptr mais sans la topo ni l'eau
68!     call read_recovery_temp
69!     hwater(:,:)=0.
70  else
71     call read_no_recovery
72  endif
73
74  call sortie_ncdf_cat
75
76  ! calcul de Hmx et Hmy -> shift=-1, dim=1 -> H(i-1,j)
77
78  H(:,:)   = max(H(:,:),0.)
79  hmx(:,:) = 0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0.,dim=1))
80  hmy(:,:) = 0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0.,dim=2))
81  hmx(:,:) = max(hmx(:,:),0.)
82  hmy(:,:) = max(hmy(:,:),0.)
83
84
85  call init_eaubasale                  ! initialise le calcul des temperatures
86
87  if (geoplace(1:5).ne.'mism3') then
88     call init_icetemp(Num_rep_42)        ! initialise le calcul de temperature
89     call thermal_prop_icetemp            ! appel aux proprietes thermiques
90     call init_bmelt                      ! Appel aux tableaux d'initialisation des ice shelves
91
92  else ! initialisation dans le cas mismip
93     T(:,:,:)    = 0.
94     TPMP(:,:,:) = 0.
95     bmelt(:,:)  = 0.
96  end if
97
98  !-------------------------------------------------------------------------------------
99
100  !-------------------------------------------------------------------------------------
101  call init_outshort        ! initialisation sorties temporelles
102  call init_out_hz          ! initialisation des sorties
103  call init_out_ncdf        ! initialisation des sorties netcdf
104  call init_recovery        ! initialisation des sorties cptr ou nc
105
106  !-------------------------------------------------------------------------------------
107  !Appels a l'origine (2005) dans initial
108  !
109  call init_iso ! initialisation de l'isostasie cette routine est dans le module
110  !               isostasie_mod et dans noisostasie_mod
111
112
113
114  call init_deformation ! initialisation de la deformation. cette routine est
115  !                       dans le module deformation_mod
116
117  call init_resol_meca  ! type d'association SIA L1
118
119  call initial_heino   ! a mettre avant les init sliding et deformation
120
121
122  call init_diagno     ! initialisation de la resolution equation elliptique vitesses
123
124  call init_sliding    ! initialisation du glissement
125
126  call init_spinup     ! initialisation du spinup
127
128  call init_dragging   ! initialisation du frottement
129
130  call init_icethick   ! interverti avec init_dragging
131
132!  call init_dragging   ! initialisation du frottement
133
134  call initial_matrice !   cette routine est dans le module eq_elliptique_mod
135
136  call init_calving
137
138!
139!-------------------------------------------------------------------------------------
140! ecriture netcdf apres initialisation
141
142!!$  if (iter_beta.eq.0) then
143!!$
144!!$     if (itracebug.eq.1)  call tracebug(' Avant appel routine icethick3')
145!!$     call icethick3
146!!$     debug_3D(:,:,88) = S(:,:)
147!!$     if (itracebug.eq.1)  call tracebug(' Apres appel routine icethick3')
148!!$  end if
149  return
150
151end subroutine initial
152
Note: See TracBrowser for help on using the repository browser.