source: branches/iLoveclim/SOURCES/climat-perturb_mod-0.4.f90 @ 77

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

Merge branche iLOVECLIM sur rev 76

File size: 8.9 KB
Line 
1!> \file climat-perturb_mod-0.4.f90
2!! Module pour les variations temporelles des variables climatiques
3!<
4
5!> \namespace  climat_perturb_mod
6!!Module pour les variations temporelles des variables climatiques
7!! \author C. Dumas
8!! \date 12/2015
9!! @note Used modules:
10!! @note   - use module3D_phy
11!<
12module  climat_perturb_mod
13
14
15use module3d_phy,only:nx,ny,S,S0,Tann,Tjuly,precip,acc,Ylat,num_forc,num_param,num_rep_42,dirforcage,dirnameinp,tafor,time,sealevel,coefbmshelf
16
17implicit none
18
19integer nft             !< nombre de lignes a lire dans le fichier forcage climatique
20real,dimension(:),allocatable :: tdate          !< time for climate forcing
21real,dimension(:),allocatable :: tpert          !< temperature for climate forcing
22real,dimension(:),allocatable :: spert          !< sea surface perturbation
23
24real,dimension(nx,ny) :: ta0          !< initial air temperature at sea level annual
25
26real :: coefT                   !< pour modifier l'amplitude de la perturb. T
27real :: rappact                 !< pour le calcul du rapport 'accumulation
28integer :: retroac              !< 1-> full retroactions accum
29real :: rapbmshelf              !< pour calcul coefbmshelf
30real :: mincoefbmelt            !< butoirs mini
31real :: maxcoefbmelt            !< butoirs maxi de coefbmelt
32character(len=80) :: filforc    !< nom du fichier forcage
33
34! Pour l'instant tafor est global meme si inutile si on utilise
35! un forcage  (variation spatiales)
36
37contains
38
39!--------------------------------------------------------------------------------
40!> SUBROUTINE: input_clim 
41!! Routine qui permet d'initialiser les variations temporelles des variables climatiques
42!>
43  subroutine input_clim !routine qui permet d'initialiser les variations temporelles des variables climatiques
44
45    implicit none
46    character(len=8) :: control      !label to check clim. forc. file (filin) is usable
47    character(len=80):: filin
48    integer ::  err                       !< pour l'allocation des tableaux
49    integer :: i
50
51    ! Lecture du forcage
52    !-----------------------
53    ! Le fichier de forcage est lu dans le fichier entree parametres
54
55    filin=trim(dirforcage)//trim(filforc)
56
57    open(num_forc,file=filin,status='old')
58
59    read(num_forc,*) control,nft
60
61    ! Determination of file size (line nb), allocation of perturbation array
62
63    if (control.ne.'nb_lines') then
64       write(6,*) filin,'indiquer le nb de ligne en debut de fichier:'
65       write(6,*) 'le nb de lignes et le label de control nb_lines'
66       stop
67    endif
68
69    ! Dimensionnement des tableaux tdate, ....
70
71    if (.not.allocated(tdate)) then
72       allocate(tdate(nft),stat=err)
73       if (err/=0) then
74          print *,"erreur a l'allocation du tableau Tdate",err
75          stop 4
76       end if
77    end if
78
79    if (.not.allocated(spert)) then
80       allocate(spert(nft),stat=err)
81       if (err/=0) then
82          print *,"erreur a l'allocation du tableau Spert",err
83          stop 4
84       end if
85    end if
86
87
88    if (.not.allocated(tpert)) then
89       allocate(tpert(nft),stat=err)
90       if (err/=0) then
91          print *,"erreur a l'allocation du tableau Tpert",err
92          stop 4
93       end if
94    end if
95
96    do i=1,nft
97       read(num_forc,*) tdate(i),spert(i),tpert(i)
98    end do
99    close(num_forc)
100
101    tpert(:)=tpert(:)*coefT
102
103
104  end subroutine input_clim
105
106!--------------------------------------------------------------------------------
107!> SUBROUTINE: init_forclim
108!! Routine qui permet d'initialiser les variables climatiques au cours du temps
109!>
110subroutine init_forclim
111
112
113  character(len=80):: filin
114  integer :: i,j
115  integer :: ivo,jvo
116
117namelist/clim_pert/coefT,rappact,retroac,rapbmshelf,mincoefbmelt,maxcoefbmelt,filforc
118
119rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
120read(num_param,clim_pert)
121
122! formats pour les ecritures dans 42
123428 format(A)
124
125write(num_rep_42,428)'!___________________________________________________________' 
126write(num_rep_42,428) '&clim_pert                      ! module climat_perturb_mod '
127write(num_rep_42,*)
128write(num_rep_42,*) 'coefT        = ', coefT 
129write(num_rep_42,*) 'rappact      = ', rappact 
130write(num_rep_42,*) 'rretroac     = ', retroac 
131write(num_rep_42,*) 'rapbmshelf   = ', rapbmshelf 
132write(num_rep_42,*) 'mincoefbmelt = ', mincoefbmelt
133write(num_rep_42,*) 'maxcoefbmelt = ', maxcoefbmelt
134write(num_rep_42,'(A,A)') ' filforc      = ', filforc
135write(num_rep_42,*)'/'                           
136write(num_rep_42,*)
137
138
139
140!!!!!!!! ATTENTION AJOUTE POUR TEST MAIS A REMETTRE AU PROPRE PLUS TARD C. DUMAS !!!!!!!!!!
141!!!!!!!! ancien input_climat_ref de lect_clim_act_anteis
142!     accumulation de Philippe
143      filin='accumHUY40km.dat'
144      call lect_eis(nx,ny,precip,filin,DIRNAMEINP)
145!====================================== La reponse est 42 ===========
146      write(num_rep_42,*) 'fichier accum : ', filin 
147
148!     cas particulier de Vostok
149      ivo=101
150      jvo=62
151      do j=jvo-1,jvo+1
152        do i=ivo-1,ivo+1
153            precip(i,j)=0.02         ! valeur plus faible a Vostok.
154        end do
155      end do
156      acc(:,:)=precip(:,:)
157
158!    temperature en surface :
159!    parametrisation de Fortuin pour la temperature annuelle.
160      do j=1,ny
161        do i=1,nx
162
163            if (s0(i,j).le.200.) then   ! shelfs
164               tann(i,j)=49.642-0.943*abs(ylat(i,j))
165            else if ((s0(i,j).gt.200.).and.(s0(i,j).lt.1500.)) then ! pente
166               tann(i,j)=36.689-0.005102*s0(i,j)-0.725*abs(ylat(i,j))
167            else if (s0(i,j).ge.1500.) then        ! plateau
168               tann(i,j)=7.405-0.014285*s0(i,j)-0.180*abs(ylat(i,j))
169            endif
170
171            ta0(i,j)=tann(i,j)
172!           pour la temperature d'ete, idem parametrisation huybrechts
173            tjuly(i,j)=tann(i,j)-17.65+0.00222*s0(i,j)&
174                         +0.40802*abs(ylat(i,j))
175        end do
176      end do
177!!!!!!!! FIN MODIF  TEMPORAIRE !!!!!!!!!!
178
179
180return
181end subroutine init_forclim
182
183!--------------------------------------------------------------------------------
184!> SUBROUTINE: forclim
185!! 
186!!  Routine qui permet le calcule climatiques au cours du temps
187!!  @note Au temps considere (time) attribue les scalaires
188!!  @note   - tafor : forcage en temperature
189!!  @note   - sealevel : forcage niveau des mers
190!!  @note   - coefbmelt : forcage fusion basale ice shelves
191!>
192subroutine forclim               !  au temps considere (time) attribue les scalaires
193  !  tafor : forcage en temperature
194  !  sealevel : forcage niveau des mers
195  !  coefbmelt : forcage fusion basale ice shelves
196
197!  use module3d_phy
198  implicit none
199  integer :: i,ift
200
201  !       time en dehors des limites du fichier forcage
202  if(time.lt.tdate(1)) then
203     tafor=tpert(1)
204     sealevel=spert(1)
205     ift=1
206
207  else if (time.ge.tdate(nft)) then
208     tafor=tpert(nft)
209     sealevel=spert(nft)
210     ift=nft
211
212  else
213     do i=1,nft-1 
214        if((time.ge.tdate(i)).and.(time.lt.tdate(i+1))) then ! entre i et i+1 : cas general
215           tafor=tpert(i)+(tpert(i+1)-tpert(i))*       &
216                (time-tdate(i))/(tdate(i+1)-tdate(i))
217           sealevel=spert(i)+(spert(i+1)-spert(i))*    &
218                (time-tdate(i))/(tdate(i+1)-tdate(i))
219           ift=i
220           goto 100
221        endif
222     end do
223  endif
224100 continue
225
226
227  !  coefmshelf est un coefficient qui fait varier bmgrz et bmshelf
228  !  en fonction de tafor
229
230  !   coefbmshelf=(1.+tafor/10.)           ! coefbmshelf=0 pour tafor=-10deg
231
232  if ((tafor.le.0).and.(tafor.gt.-5.)) then
233     coefbmshelf=(1.+tafor/rapbmshelf)     ! coefbmshelf=0 pour tafor=-7 standard precedent
234
235  else if (tafor.le.-5) then               ! lineaire en 0 a -10 et la valeur a -5
236     coefbmshelf=(1.-5./rapbmshelf)/5.*(tafor+10)
237
238  else
239     coefbmshelf=(1.+5.*tafor/rapbmshelf)  ! 5 fois plus efficace vers le chaud
240  endif
241
242  coefbmshelf=max(coefbmshelf,mincoefbmelt) 
243  coefbmshelf=min(coefbmshelf,maxcoefbmelt)
244
245        call massb_perturb_Tparam 
246  !  massb_perturb_Tparam remplace desormais massb_anteis_perturb
247  !  le code est le meme pour l'Antarctique (simplement passe en format libre)
248  !  dans le fichier massb-ant_perturb_Tparam.f90
249
250
251end subroutine forclim
252
253subroutine massb_perturb_Tparam               ! calcule le mass balance en mode perturbation
254                                              ! avec la temperature parametree
255                                              ! version pour l'antarctique
256                                              ! simple copie nettoyee de massb_anteis_perturb
257  implicit none
258
259  integer :: i,j
260
261!     surface temperature et accumulation
262
263  do j=1,ny
264     do i=1,nx
265
266        if(retroac.eq.1) then
267
268           tann(i,j)=ta0(i,j)-0.00914*(s(i,j)-s0(i,j))+tafor
269           tjuly(i,j)=tann(i,j)-17.65+0.00222*s(i,j)  &
270                +0.40802*abs(ylat(i,j))
271         
272           acc(i,j)=precip(i,j)*exp(rappact*(tann(i,j)-ta0(i,j)))
273
274        else if(retroac.eq.0) then
275
276           tann(i,j)=ta0(i,j)
277           tjuly(i,j)=tann(i,j)
278           acc(i,j)=precip(i,j)*exp(rappact*(tann(i,j)-ta0(i,j)))
279        endif
280     end do
281  end do
282
283end subroutine massb_perturb_Tparam
284
285
286end module  climat_perturb_mod
Note: See TracBrowser for help on using the repository browser.