source: trunk/SOURCES/Old-sources/climat-forcage_mod-0.4.f90 @ 334

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

Move unused sources files in Old-sources directory

File size: 11.3 KB
Line 
1!> \file climat-forcage_mod-0.4.f90
2!!Module pour le calcule du forcage climatique
3!<
4
5!> \namespace climat_forcage_mod
6!! Module pour le calcule du forcage climatique
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12module  climat_forcage_mod
13
14! declaration variables
15
16use module3d_phy
17
18implicit none
19character(len=80) :: filin
20integer :: nft             !<   nft est le nombre de lignes a lire dans le fichier
21                           !< contenant le forcage climatique
22real,dimension(:),allocatable :: tdate          !< time for climate forcing
23real,dimension(:),allocatable :: alphat
24real,dimension(:),allocatable :: alphap
25real,dimension(:),allocatable :: spert
26
27
28real :: mincoefbmelt            !< butoirs mini
29real :: maxcoefbmelt            !< butoirs maxi de coefbmshelf
30character(len=25) :: forcage_file1 !< fichier de forcage 1 (climat)
31character(len=25) :: forcage_file2 !< fichier de forcage 2
32
33
34integer,parameter :: ntr=2 !< nb of snapshot files now explicitely specified
35character(len=80) :: filtr(ntr)
36
37real ttr(ntr)!< la date des tranches (snapshots)  (len=ntr)
38real delta(nx,ny,ntr),deltj(nx,ny,ntr),rapact(nx,ny,ntr)
39real  deltatime(nx,ny),deltjtime(nx,ny),rapactime(nx,ny)
40
41contains
42
43!------------------------------------------------------------------------------------------
44
45!> SUBROUTINE: input_clim
46!! Routine qui permet d'initialiser les variables climatiques
47!>
48
49  subroutine input_clim          !routine qui permet d'initialiser les variables climatiques
50
51    implicit none
52    character(len=8) :: control     !label to check clim. forc. file (filin) is usable
53    integer l                       !in snapshot files:the first column is the mask, read but not used
54
55    deltatime(:,:)=0.
56    deltjtime(:,:)=0.
57    rapactime(:,:)=1.
58
59    if (geoplace.eq.'heminor') then
60
61       !     atmospheric temperature gradient
62       tempgrad=0.008
63       tempgrjul=0.0065
64
65
66       !pour le nord cette partie est copiee de inputfile-hemicycle.f (3juin04)
67       ! fichiers snapshots pour forcage
68       !----------------------------------
69       filtr(1)=trim(dirnameinp)//'Snapshots-GCM/forclgm-lmd5prese.g50'
70       filtr(2)=trim(dirnameinp)//'Snapshots-GCM/forclgm-lmd5futur.g50'
71
72       ! fichiers donnant l'evolution temporelle
73
74       ! this file contains tdate(i),alphat(i),alphap(i),spert(i),i=1,nft     
75       ! -------------------hemicycle ------------
76       ! lecture du fichier scalaire (sea level)
77       !        filin=trim(dirnameinp)//'heminor-forclgm.dat'
78       filin=trim(dirnameinp)//'signal-cycle-hemin.dat'
79
80    elseif (geoplace.eq.'hemin40') then
81
82       !     atmospheric temperature gradient
83       tempgrad=0.0065   ! 0.0085
84       tempgrjul=0.0065
85
86       ! fichiers snapshots pour forcage
87       !----------------------------------
88       !          filtr(1)=trim(dirnameinp)//'Snapshots-GCM/forcage_hemin40-21k.g40' ! glaciaire std
89       !           filtr(1)=trim(dirnameinp)//'Snapshots-GCM/file_regions_.g40' ! glaciaire regions vincent
90       !           filtr(2)=trim(dirnameinp)//'Snapshots-GCM/file_regions_2.g40' ! pour glaciaire permanent
91       !          filtr(2)=trim(dirnameinp)//'Snapshots-GCM/forclgm-reg_oc2-00k.g40'
92       !          filtr(2)=trim(dirnameinp)//'Snapshots-GCM/no_forcage_hn40-0k.g40' ! climat act a 0ky
93       !           filtr(2)=trim(dirnameinp)//'Snapshots-GCM/file_regions_2act.g40' ! pour climat act permanent
94
95       !cdc forcage modele IPSL LSCE Cycle
96       !            filtr(1)=TRIM(DIRNAMEINP)//'Snapshots-GCM/forcage_IPSL-21k.g40'
97       !            filtr(2)=TRIM(DIRNAMEINP)//'Snapshots-GCM/no_forcage_hn40-0k.g40' !climat act a 0ka
98       filtr(1)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file1)
99       filtr(2)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file2)
100       print*,'fichier de forcage 1',TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file1)
101       print*,'fichier de forcage 2',TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file2)
102
103       ! fichiers donnant l'evolution temporelle
104       ! -----------------------------------------
105       filin=trim(dirforcage)//'signal-cycle-hemin.dat'
106
107    else if ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
108
109
110       !     atmospheric temperature gradient
111       tempgrad=0.0065   ! 0.0085
112       tempgrjul=0.0065
113
114       !cdc forcage modele IPSL LSCE Cycle
115       !            filtr(1)=TRIM(DIRNAMEINP)//'Snapshots-GCM/forcage_IPSL-21k.g40'
116       !            filtr(2)=TRIM(DIRNAMEINP)//'Snapshots-GCM/no_forcage_hn40-0k.g40' !climat act a 0ka
117       filtr(1)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file1)
118       filtr(2)=TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file2)
119       print*,'fichier de forcage 1',TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file1)
120       print*,'fichier de forcage 2',TRIM(DIRNAMEINP)//'Snapshots-GCM/'//TRIM(forcage_file2)
121
122       ! fichiers donnant l'evolution temporelle
123       ! ---------------------------- ------------
124       filin=trim(dirforcage)//'signal-cycle-hemin.dat' !forcage vostok en rapport : a creer
125
126    endif !fin du test sur geoplace
127
128    ! lecture des fichiers snapsots pour n'importe quel  geoplace
129    ! -------------------------------------------------------------
130    write(6,*) 'fichiers snapshots'
131    do k=1,ntr
132       write(6,*) filtr(k)
133       open(num_forc,file=filtr(k))
134       read(num_forc,*) ttr(k)
135       read(num_forc,*)
136       read(num_forc,*)
137       do j=1,ny
138          do i=1,nx
139             read(num_forc,*) l,rapact(i,j,k),delta(i,j,k),deltj(i,j,k)
140          end do
141       end do
142       close(num_forc)
143    end do
144    ttr(1)=-500000. !ttr est la date des tranches 3d-1.h
145    ttr(2)=0
146
147    ! lecture des fichiers d'evolution pour tout geoplace
148    ! ----------------------------------------------------
149    open(num_forc,file=filin,status='old')
150    !        print*,nft
151    read(num_forc,*) control,nft
152    print*,'control',control,nft
153    ! determination of file size (line nb), allocation of perturbation array
154
155    if (control.ne.'nb_lines') then
156       write(6,*) filin,'indiquer le nb de ligne en debut de fichier:'
157       write(6,*) 'le nb de lignes et le label de control nb_lines'
158       stop
159    endif
160
161    if (.not.allocated(tdate)) THEN
162       allocate(tdate(nft),stat=err)
163       if (err/=0) then
164          print *,"erreur à l'allocation du tableau tdate",err
165          stop 4
166       end if
167    end if
168
169    if (.not.allocated(alphat)) THEN
170       allocate(alphat(nft),stat=err)
171       if (err/=0) then
172          print *,"erreur à l'allocation du tableau tpert",err
173          stop 4
174       end if
175    end if
176
177    if (.not.allocated(alphap)) THEN
178       allocate(alphap(nft),stat=err)
179       if (err/=0) then
180          print *,"erreur à l'allocation du tableau tpert",err
181          stop 4
182       end if
183    end if
184
185    if (.not.allocated(spert)) THEN
186       allocate(spert(nft),stat=err)
187       if (err/=0) then
188          print *,"erreur à l'allocation du tableau spert",err
189          stop 4
190       end if
191    end if
192
193    do i=1,nft
194       read(num_forc,*) tdate(i),alphat(i),alphap(i),spert(i)
195       !          print*,tdate(i),alphat(i),alphap(i),spert(i)
196    end do
197
198    close(num_forc)
199
200
201  end subroutine input_clim
202
203
204!--------------------------------------------------------------------------------
205!> SUBROUTINE: init_forclim
206!! Initialisation des parametres du forcage climatique au cours du temps
207!>
208
209subroutine init_forclim
210
211
212namelist/clim_forcage/forcage_file1,forcage_file2,mincoefbmelt,maxcoefbmelt
213
214rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
215read(num_param,clim_forcage)
216
217
218! formats pour les ecritures dans 42
219428 format(A)
220
221write(num_rep_42,428)'!___________________________________________________________' 
222write(num_rep_42,428) '&clim_forcage                                ! nom du bloc '
223write(num_rep_42,*)
224write(num_rep_42,*) 'forcage_file1 = ', forcage_file1
225write(num_rep_42,*) 'forcage_file2 = ', forcage_file2
226write(num_rep_42,*) 'mincoefbmelt = ', mincoefbmelt
227write(num_rep_42,*) 'maxcoefbmelt = ', maxcoefbmelt
228write(num_rep_42,*)'/'                           
229write(num_rep_42,*)
230return
231end subroutine init_forclim
232
233
234!---------------------------------------------------------------------
235!> SUBROUTINE: forclim
236!! Routine pour le calcul du forcage climatique au cours du temps
237!>
238
239subroutine forclim
240
241implicit none
242real :: coeft,coefp,coeftime       !coeftime is not used
243integer :: l                       !dumm index for loops on snapsots files  l=itr,ntr-1
244integer itr                        !nb of the current snapshot file (change with time)
245
246
247if(time.le.tdate(1)) then   ! time avant le debut du fichier forcage
248   sealevel=spert(1)
249   coeft=alphat(1)
250   coefp=alphap(1)
251   ift=1
252
253else if (time.ge.tdate(nft)) then     ! time apres la fin du fichier forcage
254   sealevel=spert(nft)
255   coeft=alphat(nft)
256   coefp=alphap(nft)
257   ift=nft
258
259else                         ! time en general
260   
261   ift = 1     
262   do i=ift,nft-1  ! interpolation entre i et i+1
263
264      if((time.ge.tdate(i)).and.(time.lt.tdate(i+1))) then  ! cas general
265          sealevel=spert(i)+(spert(i+1)-spert(i))*    &
266                 (time-tdate(i))/(tdate(i+1)-tdate(i))
267
268          coeft=alphat(i)+(alphat(i+1)-alphat(i))*      &
269                 (time-tdate(i))/(tdate(i+1)-tdate(i))
270
271          coefp=alphap(i)+(alphap(i+1)-alphap(i))*      &
272                 (time-tdate(i))/(tdate(i+1)-tdate(i))
273     
274!        print*,'sea,coeft,coefp', sealevel,coeft,coefp
275          ift=i
276          goto 100
277         endif
278
279      end do
280endif
281100   continue
282
283!          print*,'coefft p',coeft,coefp
284!=forcage du climat
285
286if(time.le.ttr(1)) then   ! time en dehors des limites du fichier forcage
287   do j=1,ny
288      do i=1,nx
289         deltatime(i,j)=delta(i,j,1)
290         deltjtime(i,j)=deltj(i,j,1)
291         rapactime(i,j)=rapact(i,j,1)
292      end do
293   end do
294   itr=1
295
296else if (time.ge.ttr(ntr)) then        ! mis a 0
297   do j=1,ny
298      do i=1,nx
299         deltatime(i,j)=delta(i,j,ntr)
300         deltjtime(i,j)=deltj(i,j,ntr)
301         rapactime(i,j)=rapact(i,j,ntr)
302      end do
303   end do
304   itr=ntr
305
306else               !  interpolation entre l et l+1 : cas general
307   itr=max(itr,1)
308
309   do l=itr,ntr-1    ! interpolation entre i et i+1
310     
311      if((time.ge.ttr(l)).and.(time.lt.ttr(l+1))) then  ! test tranche
312         
313         coeftime= (time-ttr(l))/(ttr(l+1)-ttr(l))
314         do j=1,ny
315            do i=1,nx
316               deltatime(i,j)=delta(i,j,l)+             &
317                    (delta(i,j,l+1)-delta(i,j,l))*coeft
318
319               deltjtime(i,j)=deltj(i,j,l)+             &
320                    (deltj(i,j,l+1)-deltj(i,j,l))*coeft
321
322               rapactime(i,j)=rapact(i,j,l)+            &
323                    (rapact(i,j,l+1)-rapact(i,j,l))*coefp
324            end do
325         end do
326         itr=l
327         goto 200
328
329      endif        ! fin du test sur la tranche
330   end do
331endif   ! fin du test avant,apres,milieu
332
333200   continue
334
335deltatime(:,:)=0.
336deltjtime(:,:)=0.
337rapactime(:,:)=1.
338
339coefbmshelf=1. ! modif pour test de sensibilite (tof 20 avril 01)
340coefbmshelf=max(coefbmshelf,mincoefbmelt)
341coefbmshelf=min(coefbmshelf,maxcoefbmelt)
342
343if (geoplace(1:5).eq.'hemin') then
344   call accum7()
345
346else if ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
347   call massb_anteis_forcage()
348
349else
350   print*,"partie en travaux climat forcage autre que sur heminord"
351   print*,"geoplace ",geoplace
352endif
353
354
355seasea=sealevel        ! pour des sorties
356
357end subroutine forclim
358
359end module  climat_forcage_mod
Note: See TracBrowser for help on using the repository browser.