source: branches/iLoveclim/SOURCES/Old-sources/climat-perturb-mois_mod.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: 6.0 KB
Line 
1!> \file climat-perturb-mois_mod.f90
2!! Module pour les variations temporelles mensuelle des variables climatiques
3!<
4
5!> \namespace climat_perturb_mois_mod
6!! Module pour les variations temporelles mensuelle des variables climatiques
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!<
12module  climat_perturb_mois_mod
13
14
15use module3d_phy
16implicit none
17
18integer nft             !< nombre de lignes a lire dans le fichier forcage climatique
19real,dimension(:),allocatable :: tdate          !< time for climate forcing
20real,dimension(:),allocatable :: tpert          !< temperature for climate forcing
21real,dimension(:),allocatable :: spert          !< sea surface perturbation
22
23real :: coefT                   !< pour modifier l'amplitude de la perturb. T
24real :: rappact                 !< pour le calcul du rapport 'accumulation
25integer :: retroac              !< 1-> full retroactions accum
26real :: rapbmshelf              !< pour calcul coefbmshelf
27real :: mincoefbmelt            !< butoirs mini
28real :: maxcoefbmelt            !< butoirs maxi de coefbmelt
29character(len=80) :: filforc    !< nom du fichier forcage
30
31! Pour l'instant tafor est global meme si inutile si on utilise
32! un forcage  (variation spatiales)
33
34contains
35
36!--------------------------------------------------------------------------------
37!> SUBROUTINE: input_clim
38!!  Routine qui permet d'initialiser les variables climatiques
39!>
40  subroutine input_clim !routine qui permet d'initialiser les variables climatiques
41
42    implicit none
43    character(len=8) :: control      !< label to check clim. forc. file (filin) is usable
44    character(len=80):: filin
45
46
47    ! Lecture du forcage
48    !-----------------------
49    ! Le fichier de forcage est lu dans le fichier entree parametres
50
51    filin=trim(dirforcage)//trim(filforc)
52
53    open(num_forc,file=filin,status='old')
54
55    read(num_forc,*) control,nft
56
57    ! Determination of file size (line nb), allocation of perturbation array
58
59    if (control.ne.'nb_lines') then
60       write(6,*) filin,'indiquer le nb de ligne en debut de fichier:'
61       write(6,*) 'le nb de lignes et le label de control nb_lines'
62       stop
63    endif
64
65    ! Dimensionnement des tableaux tdate, ....
66    if (.not.allocated(tdate)) then
67       allocate(tdate(nft),stat=err)
68       if (err/=0) then
69          print *,"erreur a l'allocation du tableau Tdate",err
70          stop 4
71       end if
72    end if
73
74
75    if (.not.allocated(spert)) then
76       allocate(spert(nft),stat=err)
77       if (err/=0) then
78          print *,"erreur a l'allocation du tableau Spert",err
79          stop 4
80       end if
81    end if
82
83    if (.not.allocated(tpert)) then
84       allocate(tpert(nft),stat=err)
85       if (err/=0) then
86          print *,"erreur a l'allocation du tableau Tpert",err
87          stop 4
88       end if
89    end if
90
91    do i=1,nft
92       read(num_forc,*) tdate(i),spert(i),tpert(i)
93    end do
94    close(num_forc)
95
96    tpert(:)=tpert(:)*coefT
97
98  end subroutine input_clim
99
100!--------------------------------------------------------------------------------
101!> SUBROUTINE: init_forclim
102!!  Routine qui permet d'initialiser les variables climatiques au cours du temps
103!>
104subroutine init_forclim
105
106
107namelist/clim_pert/coefT,rappact,retroac,rapbmshelf,mincoefbmelt,maxcoefbmelt,filforc
108
109rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
110read(num_param,clim_pert)
111
112! formats pour les ecritures dans 42
113428 format(A)
114
115write(num_rep_42,428)'!___________________________________________________________' 
116write(num_rep_42,428) '&clim_pert                      ! module climat_perturb_mod '
117write(num_rep_42,*)
118write(num_rep_42,*) 'coefT        = ', coefT 
119write(num_rep_42,*) 'rappact      = ', rappact 
120write(num_rep_42,*) 'rretroac     = ', retroac 
121write(num_rep_42,*) 'rapbmshelf   = ', rapbmshelf 
122write(num_rep_42,*) 'mincoefbmelt = ', mincoefbmelt
123write(num_rep_42,*) 'maxcoefbmelt = ', maxcoefbmelt
124write(num_rep_42,'(A,A)') ' filforc      = ', filforc
125write(num_rep_42,*)'/'                           
126write(num_rep_42,*)
127
128return
129end subroutine init_forclim
130
131!--------------------------------------------------------------------------------
132!> SUBROUTINE: forclim
133!!  Routine qui permet le calcule climatiques au cours du temps
134!!  @note Au temps considere (time) attribue les scalaires
135!!  @note   - tafor : forcage en temperature
136!!  @note   - sealevel : forcage niveau des mers
137!!  @note   - coefbmelt : forcage fusion basale ice shelves
138!>
139subroutine forclim               !  au temps considere (time) attribue les scalaires
140  !  tafor : forcage en temperature
141  !  sealevel : forcage niveau des mers
142  !  coefbmelt : forcage fusion basale ice shelves
143
144  use module3d_phy
145  implicit none
146
147  !       time en dehors des limites du fichier forcage
148  if(time.lt.tdate(1)) then
149     tafor=tpert(1)
150     sealevel=spert(1)
151     ift=1
152
153  else if (time.ge.tdate(nft)) then
154     tafor=tpert(nft)
155     sealevel=spert(nft)
156     ift=nft
157
158  else
159     do i=1,nft-1 
160        if((time.ge.tdate(i)).and.(time.lt.tdate(i+1))) then ! entre i et i+1 : cas general
161           tafor=tpert(i)+(tpert(i+1)-tpert(i))*       &
162                (time-tdate(i))/(tdate(i+1)-tdate(i))
163           sealevel=spert(i)+(spert(i+1)-spert(i))*    &
164                (time-tdate(i))/(tdate(i+1)-tdate(i))
165           ift=i
166           goto 100
167        endif
168     end do
169  endif
170100 continue
171
172
173  !  coefmshelf est un coefficient qui fait varier bmgrz et bmshelf
174  !  en fonction de tafor
175
176  !   coefbmshelf=(1.+tafor/10.)           ! coefbmshelf=0 pour tafor=-10deg
177
178  if ((tafor.le.0).and.(tafor.gt.-5.)) then
179     coefbmshelf=(1.+tafor/rapbmshelf)     ! coefbmshelf=0 pour tafor=-7 standard precedent
180
181  else if (tafor.le.-5) then               ! lineaire en 0 a -10 et la valeur a -5
182     coefbmshelf=(1.-5./rapbmshelf)/5.*(tafor+10)
183
184  else
185     coefbmshelf=(1.+5.*tafor/rapbmshelf)  ! 5 fois plus efficace vers le chaud
186  endif
187
188  coefbmshelf=max(coefbmshelf,mincoefbmelt) 
189  coefbmshelf=min(coefbmshelf,maxcoefbmelt)
190
191
192  call massb_perturb_mois
193
194end subroutine forclim
195
196end module  climat_perturb_mois_mod
197
Note: See TracBrowser for help on using the repository browser.