source: trunk/SOURCES/Heino_files/climat-heino_mod.f90 @ 159

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

initial import GRISLI trunk

File size: 3.0 KB
Line 
1!> \file climat-heino_mod.f90
2!!Module pour la lecture du climat des experience Heino
3!<
4
5!> \namespace climat_heino
6!! Module pour la lecture du climat
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12
13
14module  climat_heino               ! pour le climat des experiences Heino
15
16
17use module3d_phy
18implicit none
19
20real, dimension(nx,ny) :: dist_heino     !< distance au centre
21real,dimension(nx,ny) ::  xcc , ycc      !< coordeonnes en m
22real :: bilmin                           !< bilan min
23real :: bilmax                           !< bilan max
24real :: coefbil
25real :: Rcal                             !< rayon de la calotte
26real :: Tsmin                            !< Temperature min
27real :: St                               !< gradient horizontal de temperature
28real :: time_change                      !< temps apres lequel on met un changement
29real :: deltaTann                        !< changement de temeprature
30real :: ratiobil                         !< changement de bilan (facteur)
31
32
33contains
34!______________________________________________________________________________
35
36!>SUBROUTINE: input_clim
37!!Initialise la distance au centre
38!<
39
40  subroutine input_clim                  ! initialise la distance au centre
41
42    real :: xcentre=2000.
43    real :: ycentre=2000.
44    real :: coefbil
45
46    if (itracebug.eq.1)  call tracebug(' Heino: entree dans routine input_clim')
47
48
49    do j=1,ny
50       do i=1,nx
51          xcc(i,j)=(i-1)*dx
52          ycc(i,j)=(j-1)*dx
53       end do
54    end do
55
56    xcc(:,:)=xcc(:,:)/1000.
57    ycc(:,:)=ycc(:,:)/1000.
58
59
60    dist_heino(:,:)=(xcc(:,:)-xcentre)**2+(ycc(:,:)-ycentre)**2
61    dist_heino(:,:)=dist_heino(:,:)**0.5
62    Rcal=2000.    ! en km mais la distance l'est aussi
63    write(num_rep_42,*)
64    write(num_rep_42,*)'bilan Heino------------------------------------'
65    write(num_rep_42,*)'initialisation distance au centre en km'
66
67    bilmin=0.15   ! en m/an
68    bilmax=0.3    ! en m/an
69
70    coefbil=(bilmax-bilmin)/Rcal
71
72    bm(:,:)=bilmin+coefbil*dist_heino(:,:)
73
74    where (mk0.eq.0) bm(:,:)=0.               ! 0 dans l'ocean
75
76    write(num_rep_42,*) 'bilmin,bilmax (m/an)',bilmin,bilmax
77
78    Tsmin=-40.0    ! run standard
79    !Tsmin=-50.0    ! run T1
80    St=2.5e-9
81
82    write(num_rep_42,*)'Temperature, Tsmin (deg C), gradient (deg/km-3)',Tsmin,St
83
84    Tann(:,:)=Tsmin+St*dist_heino(:,:)**3
85
86    where (mk0.eq.0) Tann(:,:)=0.
87    Ts(:,:)=Tann(:,:)
88
89    time_change=1.e6
90    deltaTann=0.
91    ratiobil=1.
92
93    write(num_rep_42,*)'Ces valeurs sont gardee jusqu a',time_change,'ans'
94    write(num_rep_42,*)'apres : T=T+',deltaTann,'        bilan=bilan*',ratiobil
95
96    Acc(:,:)=bm(:,:)
97
98    return
99  end subroutine input_clim
100
101!__________________________________________________________________________
102
103!>SUBROUTINE: forclim
104!! Clacule du climat au cours du temps
105!<
106subroutine forclim
107if (itracebug.eq.1)  call tracebug(' Heino: entree dans routine forclim')
108
109if (time.gt.time_change) then
110   Tann(:,:)=Tann(:,:)+deltaTann
111   Ts(:,:)=Tann(:,:)
112   bm(:,:)=bm(:,:)*ratiobil
113endif
114
115
116end subroutine forclim
117
118end module climat_heino
Note: See TracBrowser for help on using the repository browser.