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

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

Grice2sea compilé et validé avec le module climat_Grice2sea_years_mod. climat_GrIce2sea_years_mod.f90 inclus massb_Ice2sea_RCM et massb_Ice2sea_fixe. pdd_declar_mod.f90 supprimé, les déclarations de variables concernant le pdd sont maintenant dans le module ablation_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  !-------------------------------------------------------------------------------------
50
51  ! aurel neem -> pour initialisation traceurs
52  call init_tracer 
53
54  !initialisation des lacs proglaciaires
55  call input_lakes     
56
57
58  ! call  input_profile()     ! Les fichiers profils
59  !
60
61  if (icompteur.ne.0) then ! reprise  d un fichier cptr
62     call read_recovery(icompteur)
63     time = tbegin
64     call sortie_ncdf_cat
65!  else if (icompteur.eq.2) then ! reprise d'un fichier cptr mais sans la topo
66!     call read_recovery_temp
67
68!  else if (icompteur.eq.3) then ! reprise d'un fichier cptr mais sans la topo ni l'eau
69!     call read_recovery_temp
70!     hwater(:,:)=0.
71  else
72     call read_no_recovery
73  endif
74
75call sortie_ncdf_cat
76
77  ! calcul de Hmx et Hmy -> shift=-1, dim=1 -> H(i-1,j)
78
79  H(:,:)   = max(H(:,:),0.)
80  hmx(:,:) = 0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0.,dim=1))
81  hmy(:,:) = 0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0.,dim=2))
82  hmx(:,:) = max(hmx(:,:),0.)
83  hmy(:,:) = max(hmy(:,:),0.)
84
85
86  call init_eaubasale                  ! initialise le calcul des temperatures
87
88  if (geoplace(1:5).ne.'mism3') then
89     call init_icetemp(Num_rep_42)        ! initialise le calcul de temperature
90     call thermal_prop_icetemp(T,TPMP,H,debug_3D)  ! appel aux proprietes thermiques
91     call init_bmelt                      ! Appel aux tableaux d'initialisation des ice shelves
92
93  else ! initialisation dans le cas mismip
94     T(:,:,:)    = 0.
95     TPMP(:,:,:) = 0.
96     bmelt(:,:)  = 0.
97  end if
98
99  !-------------------------------------------------------------------------------------
100
101  !-------------------------------------------------------------------------------------
102  call init_outshort        ! initialisation sorties temporelles
103  call init_out_hz          ! initialisation des sorties
104  call init_out_ncdf        ! initialisation des sorties netcdf
105  call init_recovery        ! initialisation des sorties cptr ou nc
106
107  !-------------------------------------------------------------------------------------
108  !Appels a l'origine (2005) dans initial
109  !
110  call init_iso ! initialisation de l'isostasie cette routine est dans le module
111  !               isostasie_mod et dans noisostasie_mod
112
113
114
115  call init_deformation ! initialisation de la deformation. cette routine est
116  !                       dans le module deformation_mod
117
118  call init_resol_meca  ! type d'association SIA L1
119
120  call initial_heino   ! a mettre avant les init sliding et deformation
121
122
123  call init_diagno     ! initialisation de la resolution equation elliptique vitesses
124
125  call init_sliding    ! initialisation du glissement
126
127  call init_spinup     ! initialisation du spinup
128
129  call init_dragging   ! initialisation du frottement
130
131  call init_icethick   ! interverti avec init_dragging
132
133!  call init_dragging   ! initialisation du frottement
134
135  call initial_matrice !   cette routine est dans le module eq_elliptique_mod
136
137  call init_calving
138
139  call allocate_types  ! cette routine alloue tous les types derive
140!
141!-------------------------------------------------------------------------------------
142! ecriture netcdf apres initialisation
143
144!!$  if (iter_beta.eq.0) then
145!!$
146!!$     if (itracebug.eq.1)  call tracebug(' Avant appel routine icethick3')
147!!$     call icethick3
148!!$     debug_3D(:,:,88) = S(:,:)
149!!$     if (itracebug.eq.1)  call tracebug(' Apres appel routine icethick3')
150!!$  end if
151  return
152
153end subroutine initial
154
Note: See TracBrowser for help on using the repository browser.