source: branches/iLoveclim/SOURCES/GrIce2sea_files/massbal_GrIce2sea_doc.f90 @ 123

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

initial import GRISLI trunk

File size: 4.2 KB
Line 
1Resume climat GrIce2sea
2
3!============================================== climat_GrIce2sea_years_mod.f90
4module climat_Grice2sea_years_mod
5  use module3d_phy
6  use lect_climref_Ice2sea
7  use netcdf
8  use io_netcdf_grisli
9  implicit none
10
11real,dimension(:),allocatable        :: time_snap         !> date des snapshots  indice : nb de nb_snap)
12real,dimension(:,:,:),allocatable    :: smb_snap          !> bilan de masse des snapshots indices : nx,ny,nb_snap
13real                                 :: ecart_snap        !> ecart temporel entre les snapshots
14real                                 :: time_depart_snaps !> temps du debut premier snapshot
15integer                              :: nb_snap           !> nombre de snapshots
16
17! declaration pour le bilan de masse
18real,dimension(nx,ny)                :: bm_time           !> bilan de masse interpole entre 2 snapshots
19real,dimension(nx,ny)                :: grad_bm           !> gradient du bilan de masse
20
21
22
23contains
24!---------------------------------------------------------------------------------
25subroutine input_clim 
26
27  !lecture namelist
28  namelist/clim_snap/nb_snap,time_depart_snaps,ecart_snap,file_smb_snap
29
30  ! lecture du fichier smb
31  call Read_Ncdf_var('z',file_smb_snap,tab3D)     ! ce sont des anomalies 
32  smb_snap (i,j,k) = smb_snap(i,j,k) + bm(i,j)    ! ajoute les valeurs de reference
33
34  ! ecriture de verification
35  call write_ncdf_var(trim('smb'),dimtestname,trim(file_smb_snap),tab3D,'double')
36
37end subroutine input_clim
38!--------------------------------------------------------------------------------
39
40!--------------------------------------------------------------------------------
41subroutine init_forclim
42
43  !lecture namelist
44  namelist/lapse_rates/T_lapse_rate
45
46  call input_clim
47
48end subroutine init_forclim
49!--------------------------------------------------------------------------------
50
51!--------------------------------------------------------------------------------
52subroutine forclim   
53
54    call massb_Ice2sea_fixe    !---------------- A remplacer
55
56    call grad_smb              !-----------------------------> A faire
57    call massb_Ice2sea_RCM   
58   
59end subroutine forclim
60!--------------------------------------------------------------------------------
61end module  climat_Grice2sea_years_mod
62
63!=======================================================  lect_climat_years_Ice2sea_mod.f90
64
65module lect_clim_years_Ice2sea
66  use module3D_phy
67  use interface_input
68  use no_ablation
69
70
71!--------------------------------------------------------------------------------
72subroutine input_climat_ref()
73
74  !lecture namelist
75  namelist/clim_smb_T_gen/smb_file,coef_smb_unit,temp_annual_file
76
77  ! lecture fichiers climat actuel
78
79  call lect_input(3,'smb',1,bm,smb_file,trim(dirnameinp)//trim(runname)//'.nc')
80  bm(:,:)  = bm(:,:)*coef_smb_unit
81 
82  call lect_input(3,'Tann',1,Tann,temp_annual_file,trim(dirnameinp)//trim(runname)//'.nc')
83
84end subroutine input_climat_ref
85
86
87end module  lect_climref_Ice2sea
88
89!==============================================================   massb-GrIce2sea_fixe.f90
90
91subroutine massb_Ice2sea_fixe                ! calcule le mass balance
92
93use module3D_phy
94use climat_Grice2sea_mod
95
96Tann (:,:) = Ta0 (:,:) + T_lapse_rate * (S(:,:)-S0(:,:)) 
97Ts(:,:)    = Tann(:,:)
98
99! bm est inchange   
100end subroutine massb_Ice2sea_fixe
101
102!!==============================================================  massb-GrIce2sea_RCM.f90
103
104subroutine massb_Ice2sea_RCM                                    ! calcule le mass balance
105
106use module3D_phy
107use climat_Grice2sea_mod
108
109Tann (:,:) = Ta0 (:,:) + T_lapse_rate * (S(:,:)-S0(:,:)) 
110Ts(:,:)    = Tann(:,:)
111
112
113!
114! calcule bm_time par interpolation entre deux snapshots
115! avant prend la valeur de reference
116! apres prend la derniere valeur
117
118
119
120
121
122call  grad_smb              !-----------------------------> A faire
123
124! attribue bm
125bm(:,:) = bm_time(:,:) + grad_smb(:,:)
126
127end subroutine massb_Ice2sea_RCM 
128!---------------------------------------------------------------------------
129
130!---------------------------------------------------------------------------
131subroutine grad_smb 
132
133use module3D_phy
134use climat_Grice2sea_mod
135
136grad_smb (:,:) = 0.
137
138end subroutine grad_smb
139
140 
141!==============================================================================
Note: See TracBrowser for help on using the repository browser.