source: trunk/SOURCES/initial-0.3.f90 @ 10

Last change on this file since 10 was 9, checked in by dumas, 9 years ago

Mise en place de Hemin-40 avec nouveaux module climat : climat_forcage_mois_mod.f90, ablation_mod.f90, pdd_declar_mod.f90. Suppression de l'appel à lect-clim-act-hemin40_mod.f90

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