source: trunk/SOURCES/climat-profil_mod-0.4.f90 @ 23

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

initial import GRISLI trunk

File size: 12.9 KB
Line 
1!> \file climat-profil_mod-0.4.f90
2!! module pour creer une calotte a partir d'un masque (mk0)
3!<
4
5!> \namespace CLIMAT_PROFIL_MOD
6!! Module pour creer une calotte a partir d'un masque (mk0)
7!! \author Vincent Peyaud
8!! \date  fevrier 2006
9!! @note Ex profil calotte saalian pour Gerard
10!! @note Used module
11!! @note   - use module3D_phy
12!! @note   - use printtable
13!<
14MODULE  CLIMAT_PROFIL_MOD
15!Vincent Peyaud fevrier 2006
16!module pour creer une calotte a partir d'un masque (mk0)
17!Ex profil calotte saalian pour Gerard
18!!!!!!!!!!!!!!!!!!!!=1=decalaration variables================!!!!!!!!!!!!!!!!!!!!
19
20       use module3D_phy
21       use printtable
22implicit none
23CHARACTER(LEN=80) :: filin
24INTEGER NFT!   NFT est le nombre de lignes a lire dans le fichier
25           ! contenant le forcage climatique
26REAL,dimension(:),allocatable :: TDATE          ! time for climate forcing
27REAL,dimension(:),allocatable :: alphaT
28REAL,dimension(:),allocatable :: alphaP
29REAL,dimension(:),allocatable :: SPERT
30INTEGER,parameter :: NTR=1 ! nb of snapshot files
31!ntr is now explicitely specified in the climat module
32CHARACTER(LEN=80) masque_ice
33!CHARACTER(LEN=80),dimension(ntr)::  filtr   !snapshot file name (len=ntr)
34REAL ttr(2)! la date des tranches (snapshots)  (len=ntr)
35REAL delTa(nx,ny,ntr),delTj(nx,ny,ntr),rapact(nx,ny,ntr)
36REAL  delTatime(nx,ny),delTjtime(nx,ny),rapactime(nx,ny)
37
38CONTAINS
39!!!!!!!!!!!!!!!!!!!!=2=lecure des input=s====================!!!!!!!!!!!!!!!!!!!!
40!> SUBROUTINE: input_clim
41!! Routine qui permet d'initialiser les variables climatiques
42!>
43subroutine INPUT_CLIM !routine qui permet d'initialiser les variables climatiques
44       USE module3D_phy
45
46  implicit none
47CHARACTER(LEN=8) :: control!label to check clim. forc. file (filin) is usable
48INTEGER L !In snapshot files:the first column is the mask, read but not used
49INTEGER iii,jjj 
50if (geoplace.eq.'euras40') then
51        TEMPGRAD=0.008
52        TEMPGRJUL=0.0065
53        masque_ice=TRIM(DIRNAMEINP)//'masque_saalian_eurasie40.dat'
54        filin=TRIM(DIRNAMEINP)//'signal-cycle-hemin.dat'
55        elseif (geoplace.eq.'heminor') then
56!     atmospheric temperature gradient
57        TEMPGRAD=0.008
58        TEMPGRJUL=0.0065
59!Pou le nord cette pariti est copiée de inputfile-hemicycle.f (3juin04)
60! 1_fichiers snapshots pour forcage
61!----------------------------------
62!          filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/forcLGM-lmd5prese.g50'
63!          filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/forcLGM-lmd5futur.g50'
64! 2_fichiers donnant l'evolution temporelle
65! -------------------HEMICYCLE ------------
66! lecture du fichier scalaire (sea level)
67!        filin=TRIM(DIRNAMEINP)//'heminor-forcLGM.dat'
68         filin=TRIM(DIRNAMEINP)//'signal-cycle-hemin.dat'
69!!!this file contains TDATE(I),alphaT(I),alphaP(i),SPERT(I),I=1,nft         
70elseif (geoplace.eq.'hemin40') then
71!     atmospheric temperature gradient
72        TEMPGRAD=0.008
73        TEMPGRJUL=0.0065
74        masque_ice=TRIM(DIRNAMEINP)//'masque_saalian_hemin40.dat'
75! 1_fichiers snapshots pour forcage
76!----------------------------------
77!          filtr(1)=TRIM(DIRNAMEINP)//'FORCAGES/file_regions_2.g40'
78!          filtr(2)=TRIM(DIRNAMEINP)//'FORCAGES/file_regions_2act.g40'
79! 2_fichiers donnant l'evolution temporelle
80! -----------------------------------------
81        filin=TRIM(DIRNAMEINP)//'signal-cycle-hemin.dat'
82elseif ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
83!     atmospheric temperature gradient
84        TEMPGRAD=0.0085
85        TEMPGRJUL=0.0085
86! 1_fichiers snapshots pour forcage
87!----------------------------------
88!           filtr(1)='../INPUT-DATA/FORCAGES/forcage-ant-20k.g40'
89!           filtr(2)='../INPUT-DATA/FORCAGES/forcage-ant-00k.g40'
90! 2_fichiers donnant l'evolution temporelle
91! ---------------------------- ------------
92         filin=TRIM(DIRNAMEINP)//'forcmodif4cycles.dat' !forcage vostok en rapport : a creer
93
94endif !Fin du test sur geolpace
95
96! 3_lecure des fichiers snapsots pour tout geoplace
97! -------------------------------------------------
98write(6,*) 'fichiers masque'
99!        do k=1,ntr
100         write(6,*) masque_ice
101         open(num_forc,file=masque_ice)
102         read(num_forc,*) 
103         read(num_forc,*)
104         read(num_forc,*)
105           do j=1,ny
106            do i=1,nx
107              read(num_forc,*) iii,jjj,mk0(i,j)
108!             read(num_forc,*) mk0(i,j)
109            end do
110           end do
111         close(num_forc)
112!         end DO
113      do j=3,ny-2
114         do i=3,nx-2
115            mk0(i,j)=1
116            if ((i.lt.25).and.(j.gt.35)) mk0(i,j)=0
117         end do
118      end do
119                                                         
120        ttr(1)=-500000. !ttr est la date des tranches 3D-1.h
121        ttr(2)=0
122! 4_lecure des fichiers d'evolution pour tout geoplace
123! ----------------------------------------------------
124         open(num_forc,file=filin,status='old')
125!        print*,nft
126         read(num_forc,*) control,nft
127        print*,'control',control,nft
128! Determination of file size (line nb), allocation of perturbation array
129if (control.ne.'nb_lines') then
130         write(6,*) filin,'indiquer le nb de ligne en debut de fichier:'
131         write(6,*) 'le nb de lignes et le label de control nb_lines'
132         stop
133endif
134    if (.not.allocated(TDATE)) THEN
135       allocate(TDATE(nft),stat=err)
136         if (err/=0) then
137           print *,"Erreur à l'allocation du tableau TDATE",err
138           stop 4
139         end if
140    end if
141    if (.not.allocated(alphaT)) THEN
142       allocate(alphaT(nft),stat=err)
143         if (err/=0) then
144           print *,"Erreur à l'allocation du tableau TPERT",err
145           stop 4
146         end if
147    end if
148    if (.not.allocated(alphaP)) THEN
149       allocate(alphaP(nft),stat=err)
150         if (err/=0) then
151           print *,"Erreur à l'allocation du tableau TPERT",err
152           stop 4
153         end if
154    end if
155    if (.not.allocated(SPERT)) THEN
156       allocate(SPERT(nft),stat=err)
157         if (err/=0) then
158           print *,"Erreur à l'allocation du tableau SPERT",err
159           stop 4
160         end if
161    end if
162       
163         do I=1,NFT
164           read(num_forc,*) TDATE(I),alphaT(I),alphaP(i),SPERT(I)
165!          print*,TDATE(I),alphaT(I),alphaP(i),SPERT(I)
166         end do
167!          do j=1,ny
168!           do i=1,nx
169!             h(i,j)=250.*mk0(i,j)
170!             end do
171!          end do
172print*, 'module profil  climatique'
173!nom_table='mk0'
174!call printtable_i(mk0,nom_table)
175! A CREER ou organiser a partir des codes dans ! 2_fichiers donnant l'evolution temporelle
176
177END subroutine INPUT_CLIM
178
179!!!!!!!!!!!!!!!!!!!!=3=forcage climatique====================!!!!!!!!!!!!!!!!!!!!
180!> SUBROUTINE: forclim
181!! Routine qui permet le calcule climatiques au cours du temps
182!>
183subroutine FORCLIM
184       USE module3D_phy
185  implicit none
186  real COEFT,COEFP,coeftime!coeftime is not used
187  INTEGER L !dumm index for loops on snapsots files  l=ITR,NTR-1
188  INTEGER ITR !nb of the current snapshot file (change with time)
189!       TIME en dehors des limites du fichier forcage
190!       if(TIME.le.TDATE(1)) then
191!         TAFOR=TPERT(1)
192!         SEALEVEL=SPERT(1)
193!         COEFT=alphaT(1)
194!         COEFP=alphaP(1)
195!         IFT=1
196!       else if (TIME.ge.TDATE(NFT)) then
197!         TAFOR=TPERT(NFT)
198!         SEALEVEL=SPERT(NFT)
199!         COEFT=alphaT(NFT)
200!         COEFP=alphaP(NFT)
201!         IFT=NFT
202!       ELSE
203
204!A modifier
205!        IFT = 1      ! modifie par SC le 24/11/99
206!       do I=IFT,NFT-1
207!       print*,'ds boucle1 sur snapshots',ift,TDATE(I),TDATE(I+1),time
208!         if((TIME.ge.TDATE(I)).and.(TIME.lt.TDATE(I+1))) then
209!        interpolation entre I et I+1 : cas general
210!           TAFOR=TPERT(I)+(TPERT(I+1)-TPERT(I))*
211!    &            (TIME-TDATE(I))/(TDATE(I+1)-TDATE(I))
212!         SEALEVEL=SPERT(I)+(SPERT(I+1)-SPERT(I))*    &
213!                (TIME-TDATE(I))/(TDATE(I+1)-TDATE(I))
214
215!         COEFT=alphaT(I)+(alphaT(I+1)-alphaT(I))*      &
216!                (TIME-TDATE(I))/(TDATE(I+1)-TDATE(I))
217
218!         COEFP=alphaP(I)+(alphaP(I+1)-alphaP(I))*      &
219!                (TIME-TDATE(I))/(TDATE(I+1)-TDATE(I))
220!        SEALEVEL=-50.         
221!       print*,'SEA,COEFT,COEFP', SEALEVEL,COEFT,COEFP
222!           IFT=I
223!           goto 100
224!         endif
225
226!       end do
227!     endif
228!100   continue
229
230!          print*,'coeffT P',COEFT,COEFP
231!=forcage du climat
232!       TIME en dehors des limites du fichier forcage
233!        if(TIME.le.Ttr(1)) then   ! mis a -500 000 ans
234!          do j=1,ny
235!            do i=1,nx
236!              delTatime(i,j)=delTa(i,j,1)
237!              delTjtime(i,j)=delTj(i,j,1)
238!              rapactime(i,j)=rapact(i,j,1)
239!            end do
240!           end do
241!              ITR=1
242
243!        else if (TIME.ge.ttr(Ntr)) then        ! mis a 0
244!          do j=1,ny
245!            do i=1,nx
246!             delTatime(i,j)=delTa(i,j,ntr)
247!             delTjtime(i,j)=delTj(i,j,ntr)
248!             rapactime(i,j)=rapact(i,j,ntr)
249!            end do
250!           end do
251!           ITR=NTR
252
253!        else               !  interpolation entre l et l+1 : cas general
254!        itr=max(itr,1)
255!       WRITE(6,*)'itr = !',itr
256
257
258!parametres du fit
259
260!        do l=ITR,NTR-1
261!        print*,'ds boucle2 sur snapshots',l,ttr(l)
262!           if((TIME.ge.ttr(l)).and.(TIME.lt.ttr(l+1))) then  ! test tranche
263!
264!           coeftime= (TIME-TTR(l))/(TTR(l+1)-TTR(l))
265!           do j=1,ny
266!            do i=1,nx
267!            delTatime(i,j)=delTa(i,j,l)+             &
268!               (delTa(i,j,l+1)-delTa(i,j,l))*coefT
269
270!            delTjtime(i,j)=delTj(i,j,l)+             &
271!               (delTj(i,j,l+1)-delTj(i,j,l))*coefT
272
273!            rapactime(i,j)=rapact(i,j,l)+            &
274!               (rapact(i,j,l+1)-rapact(i,j,l))*coefP
275!             end do
276!           end do
277!           ITR=l
278!            goto 200
279!
280!            endif        ! fin du test sur la tranche
281!         end do
282!       endif   ! fin du test avant,apres,milieu
283!
284200   continue
285!     sortie pour verifier les valeurs
286!      print*,time ,coefT,coefP,sealevel
287!0print*,'dans le forclim climat coefbmshelf nest pas defini'
288!! coefmshelf est un coefficient qui fait vairier bmgrz et bmshelf
289!! en fonction de TAFOR (deplace depuis icetemp 16juin2004(au LSCE))
290!! coefbmshelf=(1.+TAFOR/10.)    ! coefbmshelf=0 pour TAFOR=-10deg
291!           do j=60,120!1,ny
292!            do i=50,100 !1,nx
293!                 if ((flot(i,j).and.time.lt.130000).and.  &
294!                     .not.(i.gt.75.and.j.lt.75)) then
295!                   delTjtime(i,j)=delTjtime(i,j)-4.
296!                   delTatime(i,j)=delTatime(i,j)-4.
297!                endif
298!             end do
299!           end do
300
301!   delTatime=-5.
302!   delTjtime=-5.
303    rapactime=1.2
304    do j=1,ny 
305    do i=1,nx   
306    if (j.le.20) delTatime(i,j)=-14.
307    if (j.le.20) delTjtime(i,j)=-14.
308    if (j.gt.128) delTatime(i,j)=-7.
309    if (j.gt.128) delTjtime(i,j)=-7.
310    enddo
311    enddo 
312!   do j=1,ny 
313!   do i=1,nx   
314    do j=20,128!20,ny 
315!   delTatime(i,j)=-14+7.*(  (j-20) )/115.
316!   delTjtime(i,j)=-14+7.*(  (j-20) )/115.
317    do i=1,nx!25,nx!20,nx   
318!  delTatime(i,j)=-18+7.*(((i*i-120*120)+(j*j-21*21))**0.5)/170.
319!  delTatime(i,j)=-18+7.*((i*i)**0.5+(j*j)**0.5)/170.
320!  delTatime(i,j)=-18+8.*( ( (i-25)*(i-25) )**0.5+ ( (j*j)-200 )**0.5)/170.
321   delTatime(i,j)=-17+9.*(  (j-20) )/115.
322   delTjtime(i,j)=-17+9.*(  (j-20) )/115.
323    enddo
324    enddo 
325    do j=1,ny 
326    do i=1,nx   
327!     if ((S0(i,j).eq.0.).and.(S(i,j).gt.sealevel)) then
328!           if (j.lt.55.and.i.gt.35) then
329!           else       
330!           delTjtime(i,j)=delTjtime(i,j)+5
331!           endif
332!     endif
333!  if (ice(i,j)==1) delTjtime(i,j)=delTjtime(i,j)-3.
334    enddo
335    enddo 
336
337    sealevel=-55.
338!    TAFOR=delTatime(90,100)
339! coefbmshelf=(1.+TAFOR/7.)    ! coefbmshelf=0 pour TAFOR=-7deg standard
340!   coefbmshelf(:,:)=(1.+delTatime(:,:)/7.) 
341 coefbmshelf=1. ! modif pour test de sensibilite (tof 20 avril 01)
342   coefbmshelf=max(coefbmshelf,0.)
343   coefbmshelf=min(coefbmshelf,2.)
344print*,'= t,sea,tafor',time,sealevel,tafor
345print*,'coefbmshelf',coefbmshelf
346
347if ((geoplace(1:5).eq.'hemin').or.(geoplace(1:5).eq.'euras')) then
348call ACCUM7() ! ds le main
349call ablation()
350
351!open(unit=15,file='forcage_eur.dat')
352!do j=1,ny
353!do i=1,nx
354!write(15,*) delTjtime(i,j),delTjtime(i,j),rapactime(i,j)
355!enddo
356!enddo
357!close(15)
358
359elseif ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
360! call n'est plus dans le main
361call MASSB_ANTEIS_FORCAGE()
362call ABLATION()
363else
364 print*,"partie en travaux climat forcage auter que sur heminord"
365 print*,"geoplace ",geoplace
366endif
367
368!
369!!          Tjuly(i,j)=min(Tjuly(i,j),-3.0)
370!!          TANN(I,J)=min(TANN(I,J),Tjuly(i,j))
371!nom_table='surf'
372!call printtable_r(S0,nom_table)
373!nom_table='ta0'
374!call printtable_r(ta0,nom_table)
375!nom_table='tann'
376!call printtable_r(tann,nom_table)
377!nom_table='tj0'
378!call printtable_r(tj0,nom_table)
379!nom_table='tjja'
380!call printtable_r(tjuly,nom_table)
381!nom_table='dta_'
382!call printtable_r(delTatime,nom_table)
383!nom_table='pre0'
384!call printtable_r(precip0,nom_table)
385!nom_table='prec'
386!call printtable_r(precip,nom_table)
387!nom_table='surf'
388! call printtable_r(s,nom_table)
389
390END subroutine FORCLIM
391
392END MODULE  CLIMAT_PROFIL_MOD
Note: See TracBrowser for help on using the repository browser.