source: branches/GRISLIv3/SOURCES/initial-0.3.f90 @ 399

Last change on this file since 399 was 399, checked in by dumas, 14 months ago

use only in subroutine initial

File size: 5.1 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, only:time,H,hmx,hmy,T,tpmp,bmelt,geoplace,icompteur,num_rep_42
25  use runparam, only: tbegin
26  use module_choix, only:input_topo,init_forclim,input_clim,init_ablation,init_tracer,&
27       input_rsl,init_eaubasale,init_bmelt,init_outshort,init_iso,init_deformation,initial_heino,&
28       init_furst_schoof,init_sliding,init_spinup,init_dragging,init_icethick,initial_matrice,&
29       init_calving
30  use icetempmod, only:init_icetemp
31  use diagno_mod, only:init_diagno
32  use resolmeca_SIA_L1, only:init_resol_meca
33  use flottab_mod, only:
34  use sorties_ncdf_grisli, only:sortie_ncdf_cat,init_out_ncdf
35  use util_recovery, only:init_recovery
36  use bilan_flux_mod, only:init_bilan_flux
37
38  !-------------------------------------------------------------------------------------
39  ! nouvelles entrees modulaires  janvier 2006
40  call initial_phy          ! La physique
41  call initial2             ! Initialisation des tableaux
42  !
43  call  input_topo          ! La geographie
44
45  !------------------------------------------------------
46  ! initialisation du climat  (reference et forcage)
47!cdc  call input_climat_ref    ! Le climat de reference
48  call init_forclim        ! parametres du forcage
49  call input_clim          ! lecture fichiers de forcage
50  call init_ablation       ! parametres du calcul de l'ablation
51  !-------------------------------------------------------------------------------------
52
53  ! aurel neem -> pour initialisation traceurs
54  call init_tracer 
55
56  !initialisation du niveau marin local
57  call input_rsl
58
59
60  ! call  input_profile()     ! Les fichiers profils
61  !
62
63  if (icompteur.ne.0) then ! reprise  d un fichier cptr
64     call read_recovery(icompteur)
65     time = tbegin
66     call sortie_ncdf_cat
67!  else if (icompteur.eq.2) then ! reprise d'un fichier cptr mais sans la topo
68!     call read_recovery_temp
69
70!  else if (icompteur.eq.3) then ! reprise d'un fichier cptr mais sans la topo ni l'eau
71!     call read_recovery_temp
72!     hwater(:,:)=0.
73  else
74     call read_no_recovery
75  endif
76
77  call sortie_ncdf_cat
78
79  ! calcul de Hmx et Hmy -> shift=-1, dim=1 -> H(i-1,j)
80
81  H(:,:)   = max(H(:,:),0.)
82  hmx(:,:) = 0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0d0,dim=1))
83  hmy(:,:) = 0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0d0,dim=2))
84  hmx(:,:) = max(hmx(:,:),0.)
85  hmy(:,:) = max(hmy(:,:),0.)
86
87
88  call init_eaubasale                  ! initialise le calcul des temperatures
89
90  if (geoplace(1:5).ne.'mism3') then
91     call init_icetemp(num_rep_42)        ! initialise le calcul de temperature
92     call thermal_prop_icetemp            ! appel aux proprietes thermiques
93     call init_bmelt                      ! Appel aux tableaux d'initialisation des ice shelves
94
95  else ! initialisation dans le cas mismip
96     T(:,:,:)    = 0.
97     TPMP(:,:,:) = 0.
98     bmelt(:,:)  = 0.
99  end if
100
101  !-------------------------------------------------------------------------------------
102
103  !-------------------------------------------------------------------------------------
104  call init_outshort        ! initialisation sorties temporelles
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  call init_furst_schoof ! initialisation furst schoof gr line
124
125  call init_diagno     ! initialisation de la resolution equation elliptique vitesses
126
127  call init_sliding    ! initialisation du glissement
128
129  call init_spinup     ! initialisation du spinup
130
131  call init_dragging   ! initialisation du frottement
132
133  call init_icethick   ! interverti avec init_dragging
134
135  call initial_matrice !   cette routine est dans le module eq_elliptique_mod
136
137  call init_calving
138
139  call init_bilan_flux
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.