source: LMDZ6/trunk/libf/phylmdiso/fonte_neige_mod.F90 @ 3940

Last change on this file since 3940 was 3940, checked in by crisi, 3 years ago

replace files by symbloic liks from phylmdiso towards phylmd.
Many files at once

File size: 24.6 KB
Line 
1!
2! $Header$
3!
4MODULE fonte_neige_mod
5!
6! This module will treat the process of snow, melting, accumulating, calving, in
7! case of simplified soil model.
8!
9!****************************************************************************************
10  USE dimphy, ONLY : klon
11  USE indice_sol_mod
12
13  IMPLICIT NONE
14  SAVE
15
16! run_off_ter and run_off_lic are the runoff at the compressed grid knon for
17! land and land-ice respectively
18! Note: run_off_lic is used in mod_landice and therfore not private
19  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE    :: run_off_ter
20  !$OMP THREADPRIVATE(run_off_ter)
21  REAL, ALLOCATABLE, DIMENSION(:)             :: run_off_lic
22  !$OMP THREADPRIVATE(run_off_lic)
23
24! run_off_lic_0 is the runoff at land-ice a time-step earlier, on the global 1D array grid
25  REAL, ALLOCATABLE, DIMENSION(:), PRIVATE    :: run_off_lic_0
26  !$OMP THREADPRIVATE(run_off_lic_0)
27 
28  REAL, PRIVATE                               :: tau_calv 
29  !$OMP THREADPRIVATE(tau_calv)
30  REAL, ALLOCATABLE, DIMENSION(:,:)           :: ffonte_global
31  !$OMP THREADPRIVATE(ffonte_global)
32  REAL, ALLOCATABLE, DIMENSION(:,:)           :: fqfonte_global
33  !$OMP THREADPRIVATE(fqfonte_global)
34  REAL, ALLOCATABLE, DIMENSION(:,:)           :: fqcalving_global
35  !$OMP THREADPRIVATE(fqcalving_global)
36  REAL, ALLOCATABLE, DIMENSION(:)             :: runofflic_global
37  !$OMP THREADPRIVATE(runofflic_global)
38#ifdef ISO
39  REAL, ALLOCATABLE, DIMENSION(:,:), PRIVATE    :: xtrun_off_ter
40  !$OMP THREADPRIVATE(xtrun_off_ter)
41  REAL, ALLOCATABLE, DIMENSION(:,:)             :: xtrun_off_lic
42  !$OMP THREADPRIVATE(xtrun_off_lic)
43  REAL, ALLOCATABLE, DIMENSION(:,:), PRIVATE    :: xtrun_off_lic_0
44  !$OMP THREADPRIVATE(xtrun_off_lic_0)
45  REAL, ALLOCATABLE, DIMENSION(:,:,:), PRIVATE  :: fxtfonte_global
46  !$OMP THREADPRIVATE(fxtfonte_global)
47  REAL, ALLOCATABLE, DIMENSION(:,:,:), PRIVATE  :: fxtcalving_global
48  !$OMP THREADPRIVATE(fxtcalving_global)
49  REAL, ALLOCATABLE, DIMENSION(:,:), PRIVATE  :: xtrunofflic_global
50  !$OMP THREADPRIVATE(xtrunofflic_global)
51#endif
52
53CONTAINS
54!
55!****************************************************************************************
56!
57  SUBROUTINE fonte_neige_init(restart_runoff)
58
59! This subroutine allocates and initialize variables in the module.
60! The variable run_off_lic_0 is initialized to the field read from
61! restart file. The other variables are initialized to zero.
62!
63!****************************************************************************************
64! Input argument
65    REAL, DIMENSION(klon), INTENT(IN) :: restart_runoff
66
67! Local variables
68    INTEGER                           :: error
69    CHARACTER (len = 80)              :: abort_message
70    CHARACTER (len = 20)              :: modname = 'fonte_neige_init'
71
72
73!****************************************************************************************
74! Allocate run-off at landice and initilize with field read from restart
75!
76!****************************************************************************************
77
78    ALLOCATE(run_off_lic_0(klon), stat = error)
79    IF (error /= 0) THEN
80       abort_message='Pb allocation run_off_lic'
81       CALL abort_physic(modname,abort_message,1)
82    ENDIF
83    run_off_lic_0(:) = restart_runoff(:)
84
85!****************************************************************************************
86! Allocate other variables and initilize to zero
87!
88!****************************************************************************************
89    ALLOCATE(run_off_ter(klon), stat = error)
90    IF (error /= 0) THEN
91       abort_message='Pb allocation run_off_ter'
92       CALL abort_physic(modname,abort_message,1)
93    ENDIF
94    run_off_ter(:) = 0.
95   
96    ALLOCATE(run_off_lic(klon), stat = error)
97    IF (error /= 0) THEN
98       abort_message='Pb allocation run_off_lic'
99       CALL abort_physic(modname,abort_message,1)
100    ENDIF
101    run_off_lic(:) = 0.
102   
103    ALLOCATE(ffonte_global(klon,nbsrf))
104    IF (error /= 0) THEN
105       abort_message='Pb allocation ffonte_global'
106       CALL abort_physic(modname,abort_message,1)
107    ENDIF
108    ffonte_global(:,:) = 0.0
109
110    ALLOCATE(fqfonte_global(klon,nbsrf))
111    IF (error /= 0) THEN
112       abort_message='Pb allocation fqfonte_global'
113       CALL abort_physic(modname,abort_message,1)
114    ENDIF
115    fqfonte_global(:,:) = 0.0
116
117    ALLOCATE(fqcalving_global(klon,nbsrf))
118    IF (error /= 0) THEN
119       abort_message='Pb allocation fqcalving_global'
120       CALL abort_physic(modname,abort_message,1)
121    ENDIF
122    fqcalving_global(:,:) = 0.0
123
124    ALLOCATE(runofflic_global(klon))
125    IF (error /= 0) THEN
126       abort_message='Pb allocation runofflic_global'
127       CALL abort_physic(modname,abort_message,1)
128    ENDIF
129    runofflic_global(:) = 0.0
130
131!****************************************************************************************
132! Read tau_calv
133!
134!****************************************************************************************
135    CALL conf_interface(tau_calv)
136
137
138  END SUBROUTINE fonte_neige_init
139
140#ifdef ISO
141  SUBROUTINE fonte_neige_init_iso(xtrestart_runoff)
142
143! This subroutine allocates and initialize variables in the module.
144! The variable run_off_lic_0 is initialized to the field read from
145! restart file. The other variables are initialized to zero.
146
147    use infotrac_phy, ONLY: niso
148#ifdef ISOVERIF
149    USE isotopes_mod, ONLY: iso_eau,iso_HDO
150    USE isotopes_verif_mod
151#endif
152!
153!****************************************************************************************
154! Input argument
155    REAL, DIMENSION(niso,klon), INTENT(IN) :: xtrestart_runoff
156
157! Local variables
158    INTEGER                           :: error
159    CHARACTER (len = 80)              :: abort_message
160    CHARACTER (len = 20)              :: modname = 'fonte_neige_init'
161    integer i
162
163
164!****************************************************************************************
165! Allocate run-off at landice and initilize with field read from restart
166!
167!****************************************************************************************
168
169    ALLOCATE(xtrun_off_lic_0(niso,klon), stat = error)
170    IF (error /= 0) THEN
171       abort_message='Pb allocation run_off_lic'
172       CALL abort_gcm(modname,abort_message,1)
173    ENDIF   
174   
175    xtrun_off_lic_0(:,:) = xtrestart_runoff(:,:)       
176
177#ifdef ISOVERIF
178      if (iso_eau.gt.0) then   
179        call iso_verif_egalite_vect1D( &
180     &           xtrun_off_lic_0,run_off_lic_0,'fonte_neige 100', &
181     &           niso,klon)
182      endif !if (iso_eau.gt.0) then
183#endif       
184
185!****************************************************************************************
186! Allocate other variables and initilize to zero
187!
188!****************************************************************************************
189
190    ALLOCATE(xtrun_off_ter(niso,klon), stat = error)
191    IF (error /= 0) THEN
192       abort_message='Pb allocation xtrun_off_ter'
193       CALL abort_gcm(modname,abort_message,1)
194    ENDIF
195    xtrun_off_ter(:,:) = 0.
196   
197    ALLOCATE(xtrun_off_lic(niso,klon), stat = error)
198    IF (error /= 0) THEN
199       abort_message='Pb allocation xtrun_off_lic'
200       CALL abort_gcm(modname,abort_message,1)
201    ENDIF
202    xtrun_off_lic(:,:) = 0.
203
204    ALLOCATE(fxtfonte_global(niso,klon,nbsrf))
205    IF (error /= 0) THEN
206       abort_message='Pb allocation fxtfonte_global'
207       CALL abort_gcm(modname,abort_message,1)
208    ENDIF
209    fxtfonte_global(:,:,:) = 0.0
210
211    ALLOCATE(fxtcalving_global(niso,klon,nbsrf))
212    IF (error /= 0) THEN
213       abort_message='Pb allocation fxtcalving_global'
214       CALL abort_gcm(modname,abort_message,1)
215    ENDIF
216    fxtcalving_global(:,:,:) = 0.0
217
218    ALLOCATE(xtrunofflic_global(niso,klon))
219    IF (error /= 0) THEN
220       abort_message='Pb allocation xtrunofflic_global'
221       CALL abort_gcm(modname,abort_message,1)
222    ENDIF
223    xtrunofflic_global(:,:) = 0.0
224
225  END SUBROUTINE fonte_neige_init_iso
226#endif
227!
228!
229!****************************************************************************************
230!
231  SUBROUTINE fonte_neige( knon, nisurf, knindex, dtime, &
232       tsurf, precip_rain, precip_snow, &
233       snow, qsol, tsurf_new, evap &
234#ifdef ISO   
235     & ,fq_fonte_diag,fqfonte_diag,snow_evap_diag,fqcalving_diag   &
236     & ,max_eau_sol_diag,runoff_diag,run_off_lic_diag,coeff_rel_diag   &
237#endif
238     &   )
239
240  USE indice_sol_mod
241#ifdef ISO
242    use infotrac_phy, ONLY: niso
243    !use isotopes_mod, ONLY: ridicule_snow,iso_eau,iso_HDO
244#ifdef ISOVERIF
245    use isotopes_verif_mod
246#endif
247#endif
248       
249! Routine de traitement de la fonte de la neige dans le cas du traitement
250! de sol simplifie!
251! LF 03/2001
252! input:
253!   knon         nombre de points a traiter
254!   nisurf       surface a traiter
255!   knindex      index des mailles valables pour surface a traiter
256!   dtime       
257!   tsurf        temperature de surface
258!   precip_rain  precipitations liquides
259!   precip_snow  precipitations solides
260!
261! input/output:
262!   snow         champs hauteur de neige
263!   qsol         hauteur d'eau contenu dans le sol
264!   tsurf_new    temperature au sol
265!   evap
266!
267  INCLUDE "YOETHF.h"
268  INCLUDE "YOMCST.h"
269  INCLUDE "FCTTRE.h"
270  INCLUDE "clesphys.h"
271
272! Input variables
273!****************************************************************************************
274    INTEGER, INTENT(IN)                  :: knon
275    INTEGER, INTENT(IN)                  :: nisurf
276    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
277    REAL   , INTENT(IN)                  :: dtime
278    REAL, DIMENSION(klon), INTENT(IN)    :: tsurf
279    REAL, DIMENSION(klon), INTENT(IN)    :: precip_rain
280    REAL, DIMENSION(klon), INTENT(IN)    :: precip_snow
281   
282! Input/Output variables
283!****************************************************************************************
284
285    REAL, DIMENSION(klon), INTENT(INOUT) :: snow
286    REAL, DIMENSION(klon), INTENT(INOUT) :: qsol
287    REAL, DIMENSION(klon), INTENT(INOUT) :: tsurf_new
288    REAL, DIMENSION(klon), INTENT(INOUT) :: evap
289
290
291#ifdef ISO   
292        ! sortie de quelques diagnostiques
293        real, dimension(klon),intent(out) :: fq_fonte_diag
294        real, dimension(klon),intent(out) :: fqfonte_diag
295        real, dimension(klon), intent(out) ::  snow_evap_diag
296        real, dimension(klon), intent(out) ::  fqcalving_diag 
297        real, intent(out) :: max_eau_sol_diag 
298        real, dimension(klon), intent(out) ::  runoff_diag   
299        real, dimension(klon), intent(OUT):: run_off_lic_diag 
300        real, intent(OUT):: coeff_rel_diag
301#endif
302! Local variables
303!****************************************************************************************
304
305    INTEGER               :: i, j
306    REAL                  :: fq_fonte
307    REAL                  :: coeff_rel
308    REAL, PARAMETER       :: snow_max=3000.
309    REAL, PARAMETER       :: max_eau_sol = 150.0
310!! PB temporaire en attendant mieux pour le modele de neige
311! REAL, parameter :: chasno = RLMLT/(2.3867E+06*0.15)
312    REAL, PARAMETER       :: chasno = 3.334E+05/(2.3867E+06*0.15)
313!IM cf JLD/ GKtest
314    REAL, PARAMETER       :: chaice = 3.334E+05/(2.3867E+06*0.15)
315! fin GKtest
316    REAL, DIMENSION(klon) :: ffonte
317    REAL, DIMENSION(klon) :: fqcalving, fqfonte
318    REAL, DIMENSION(klon) :: d_ts
319    REAL, DIMENSION(klon) :: bil_eau_s, snow_evap
320
321    LOGICAL               :: neige_fond
322
323#ifdef ISO
324        max_eau_sol_diag=max_eau_sol
325#endif
326
327!****************************************************************************************
328! Start calculation
329! - Initialization
330!
331!****************************************************************************************
332    coeff_rel = dtime/(tau_calv * rday)
333   
334    bil_eau_s(:) = 0.
335
336!****************************************************************************************
337! - Increment snow due to precipitation and evaporation
338! - Calculate the water balance due to precipitation and evaporation (bil_eau_s)
339!
340!****************************************************************************************
341    WHERE (precip_snow > 0.)
342       snow = snow + (precip_snow * dtime)
343    END WHERE
344
345    snow_evap = 0.
346 
347#ifdef ISOVERIF
348        write(*,*) 'klon,snow_evap(413)=',klon,snow_evap(413)
349#endif
350
351    IF (.NOT. ok_lic_cond) THEN
352!---only positive evaporation has an impact on snow
353!---note that this could create a bit of water
354!---this was the default until CMIP6
355      WHERE (evap > 0. )
356         snow_evap = MIN (snow / dtime, evap)    !---one cannot evaporate more than the amount of snow
357         snow = snow - snow_evap * dtime         !---snow that remains on the ground
358         snow = MAX(0.0, snow)                   !---just in case
359      END WHERE
360#ifdef ISOVERIF
361        write(*,*) 'fonte_neige 342: snow_evap(413)=',snow_evap(413)
362#endif
363
364    ELSE
365!--now considers both positive and negative evaporation in the budget of snow
366      snow_evap = MIN (snow / dtime, evap)    !---one cannot evaporate more than the amount of snow
367      snow = snow - snow_evap * dtime         !---snow that remains or deposits on the ground
368      snow = MAX(0.0, snow)                   !---just in case
369#ifdef ISOVERIF
370        write(*,*) 'fonte_neige 351: snow_evap(413)=',snow_evap(413)
371        write(*,*) 'evap(413)=',evap(413)
372        write(*,*) 'snow(413),dtime=',snow(413),dtime
373#endif
374
375   ENDIF
376   
377
378    bil_eau_s(:) = (precip_rain(:) * dtime) - (evap(:) - snow_evap(:)) * dtime
379#ifdef ISO
380        snow_evap_diag(:)=snow_evap(:)
381        coeff_rel_diag=coeff_rel
382#ifdef ISOVERIF
383        write(*,*) 'fonte neige 350: snow_evap_diag(1)=',snow_evap_diag(1)
384        write(*,*) 'klon,snow_evap_diag(413)=',klon,snow_evap_diag(413)
385        write(*,*) 'snow_evap(413)=',snow_evap(413)
386#endif
387#endif
388
389
390!****************************************************************************************
391! - Calculate melting snow
392! - Calculate calving and decrement snow, if there are to much snow
393! - Update temperature at surface
394!
395!****************************************************************************************
396
397    ffonte(:) = 0.0
398    fqcalving(:) = 0.0
399    fqfonte(:) = 0.0
400
401    DO i = 1, knon
402       ! Y'a-t-il fonte de neige?
403       neige_fond = (snow(i)>epsfra .OR. nisurf==is_sic .OR. nisurf==is_lic) .AND. tsurf_new(i)>=RTT
404       IF (neige_fond) THEN
405          fq_fonte     = MIN( MAX((tsurf_new(i)-RTT )/chasno,0.0),snow(i))
406          ffonte(i)    = fq_fonte * RLMLT/dtime
407          fqfonte(i)   = fq_fonte/dtime
408          snow(i)      = MAX(0., snow(i) - fq_fonte)
409          bil_eau_s(i) = bil_eau_s(i) + fq_fonte
410          tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno 
411#ifdef ISO
412        fq_fonte_diag(i)=fq_fonte
413#endif
414
415!IM cf JLD OK     
416!IM cf JLD/ GKtest fonte aussi pour la glace
417          IF (nisurf == is_sic .OR. nisurf == is_lic ) THEN
418             fq_fonte = MAX((tsurf_new(i)-RTT )/chaice,0.0)
419             ffonte(i) = ffonte(i) + fq_fonte * RLMLT/dtime
420             IF ( ok_lic_melt ) THEN
421                fqfonte(i) = fqfonte(i) + fq_fonte/dtime
422                bil_eau_s(i) = bil_eau_s(i) + fq_fonte
423             ENDIF
424             tsurf_new(i) = RTT
425          ENDIF
426          d_ts(i) = tsurf_new(i) - tsurf(i)
427       ENDIF
428
429       ! s'il y a une hauteur trop importante de neige, elle est ecretee
430       fqcalving(i) = MAX(0., snow(i) - snow_max)/dtime
431       snow(i)=MIN(snow(i),snow_max)
432    ENDDO
433#ifdef ISO
434    DO i = 1, knon
435       fqcalving_diag(i)=fqcalving(i)
436       fqfonte_diag(i)=fqfonte(i)
437    enddo !DO i = 1, knon
438#endif
439
440    IF (nisurf == is_ter) THEN
441       DO i = 1, knon
442          qsol(i) = qsol(i) + bil_eau_s(i)
443          run_off_ter(i) = run_off_ter(i) + MAX(qsol(i) - max_eau_sol, 0.0)
444#ifdef ISO
445        runoff_diag(i)=MAX(qsol(i) - max_eau_sol, 0.0)
446#endif
447          qsol(i) = MIN(qsol(i), max_eau_sol)
448       ENDDO
449    ELSE IF (nisurf == is_lic) THEN
450       DO i = 1, knon
451          j = knindex(i)
452          !--temporal filtering
453          run_off_lic(i)   = coeff_rel*fqcalving(i) + (1.-coeff_rel)*run_off_lic_0(j)
454          run_off_lic_0(j) = run_off_lic(i)
455          !--add melting snow and liquid precip to runoff of ice cap
456          run_off_lic(i)   = run_off_lic(i) + fqfonte(i) + precip_rain(i)
457       ENDDO
458    ENDIF
459
460#ifdef ISO
461    DO i = 1, klon   
462        run_off_lic_diag(i)=run_off_lic(i)
463    enddo ! DO i = 1, knon   
464#endif
465   
466!****************************************************************************************
467! Save ffonte, fqfonte and fqcalving in global arrays for each
468! sub-surface separately
469!
470!****************************************************************************************
471    DO i = 1, knon
472       ffonte_global(knindex(i),nisurf)    = ffonte(i)
473       fqfonte_global(knindex(i),nisurf)   = fqfonte(i)
474       fqcalving_global(knindex(i),nisurf) = fqcalving(i)
475    ENDDO
476
477    IF (nisurf == is_lic) THEN
478    DO i = 1, knon
479       runofflic_global(knindex(i)) = run_off_lic(i)
480    ENDDO
481    ENDIF
482
483  END SUBROUTINE fonte_neige
484!
485!****************************************************************************************
486!
487  SUBROUTINE fonte_neige_final(restart_runoff &
488#ifdef ISO     
489     &     ,xtrestart_runoff &
490#endif   
491     &   )
492!
493! This subroutine returns run_off_lic_0 for later writing to restart file.
494!
495#ifdef ISO
496    use infotrac_phy, ONLY: niso
497#ifdef ISOVERIF
498    use isotopes_mod, ONLY: iso_eau
499    use isotopes_verif_mod
500#endif
501#endif
502!****************************************************************************************
503    REAL, DIMENSION(klon), INTENT(OUT) :: restart_runoff
504#ifdef ISO     
505    REAL, DIMENSION(niso,klon), INTENT(OUT) :: xtrestart_runoff
506#ifdef ISOVERIF
507    integer i
508#endif 
509#endif
510
511!****************************************************************************************
512! Set the output variables
513    restart_runoff(:) = run_off_lic_0(:)
514#ifdef ISO
515    xtrestart_runoff(:,:) = xtrun_off_lic_0(:,:)
516#ifdef ISOVERIF
517      if (iso_eau.gt.0) then   
518        do i=1,klon
519          if (iso_verif_egalite_nostop(run_off_lic_0(i), &
520     &         xtrun_off_lic_0(iso_eau,i),'fonte_neige 413') &
521     &         .eq.1) then
522              write(*,*) 'i=',i
523              stop
524          endif
525        enddo !do i=1,klon
526      endif !if (iso_eau.gt.0) then
527#endif   
528#endif
529
530! Deallocation of all varaibles in the module
531!   DEALLOCATE(run_off_lic_0, run_off_ter, run_off_lic, ffonte_global, &
532!        fqfonte_global, fqcalving_global)
533
534    IF (ALLOCATED(run_off_lic_0)) DEALLOCATE(run_off_lic_0)
535    IF (ALLOCATED(run_off_ter)) DEALLOCATE(run_off_ter)
536    IF (ALLOCATED(run_off_lic)) DEALLOCATE(run_off_lic)
537    IF (ALLOCATED(ffonte_global)) DEALLOCATE(ffonte_global)
538    IF (ALLOCATED(fqfonte_global)) DEALLOCATE(fqfonte_global)
539    IF (ALLOCATED(fqcalving_global)) DEALLOCATE(fqcalving_global)
540    IF (ALLOCATED(runofflic_global)) DEALLOCATE(runofflic_global)
541#ifdef ISO
542    IF (ALLOCATED(xtrun_off_lic_0)) DEALLOCATE(xtrun_off_lic_0)
543    IF (ALLOCATED(xtrun_off_ter)) DEALLOCATE(xtrun_off_ter)
544    IF (ALLOCATED(xtrun_off_lic)) DEALLOCATE(xtrun_off_lic)
545    IF (ALLOCATED(fxtfonte_global)) DEALLOCATE(fxtfonte_global)
546    IF (ALLOCATED(fxtcalving_global)) DEALLOCATE(fxtcalving_global)
547    IF (ALLOCATED(xtrunofflic_global)) DEALLOCATE(xtrunofflic_global)
548#endif
549
550  END SUBROUTINE fonte_neige_final
551!
552!****************************************************************************************
553!
554  SUBROUTINE fonte_neige_get_vars(pctsrf, fqcalving_out, &
555       fqfonte_out, ffonte_out, run_off_lic_out &
556#ifdef ISO     
557     &  ,fxtcalving_out, fxtfonte_out,xtrun_off_lic_out &
558#endif     
559     &  )
560
561
562! Cumulate ffonte, fqfonte and fqcalving respectively for
563! all type of surfaces according to their fraction.
564!
565! This routine is called from physiq.F before histwrite.
566!****************************************************************************************
567
568  USE indice_sol_mod
569#ifdef ISO
570    use infotrac_phy, ONLY: niso
571#endif
572
573    REAL, DIMENSION(klon,nbsrf), INTENT(IN) :: pctsrf
574
575    REAL, DIMENSION(klon), INTENT(OUT)      :: fqcalving_out
576    REAL, DIMENSION(klon), INTENT(OUT)      :: fqfonte_out
577    REAL, DIMENSION(klon), INTENT(OUT)      :: ffonte_out
578    REAL, DIMENSION(klon), INTENT(OUT)      :: run_off_lic_out
579
580
581#ifdef ISO
582    REAL, DIMENSION(niso,klon), INTENT(OUT)      :: fxtcalving_out
583    REAL, DIMENSION(niso,klon), INTENT(OUT)      :: fxtfonte_out
584    REAL, DIMENSION(niso,klon), INTENT(OUT)      :: xtrun_off_lic_out
585    integer i,ixt
586#endif
587    INTEGER   :: nisurf
588!****************************************************************************************
589
590    ffonte_out(:)    = 0.0
591    fqfonte_out(:)   = 0.0
592    fqcalving_out(:) = 0.0
593#ifdef ISO       
594    fxtfonte_out(:,:)   = 0.0
595    fxtcalving_out(:,:) = 0.0
596#endif
597
598    DO nisurf = 1, nbsrf
599       ffonte_out(:) = ffonte_out(:) + ffonte_global(:,nisurf)*pctsrf(:,nisurf)
600       fqfonte_out(:) = fqfonte_out(:) + fqfonte_global(:,nisurf)*pctsrf(:,nisurf)
601       fqcalving_out(:) = fqcalving_out(:) + fqcalving_global(:,nisurf)*pctsrf(:,nisurf)
602    ENDDO
603
604    run_off_lic_out(:)=runofflic_global(:)
605
606
607#ifdef ISO
608       DO nisurf = 1, nbsrf
609        do i=1,klon
610         do ixt=1,niso
611          fxtfonte_out(ixt,i) = fxtfonte_out(ixt,i) + fxtfonte_global(ixt,i,nisurf)*pctsrf(i,nisurf)
612          fxtcalving_out(ixt,i) = fxtcalving_out(ixt,i) + fxtcalving_global(ixt,i,nisurf)*pctsrf(i,nisurf)
613         enddo !do ixt=1,niso
614        enddo !do i=1,klon
615       enddo !DO nisurf = 1, nbsrf
616       xtrun_off_lic_out(:,:)=xtrunofflic_global(:,:)
617#endif
618
619  END SUBROUTINE fonte_neige_get_vars
620!
621!****************************************************************************************
622!
623!#ifdef ISO
624!  subroutine fonte_neige_export_xtrun_off_lic_0(knon,xtrun_off_lic_0_diag)
625!    use infotrac_phy, ONLY: niso
626!
627!    ! inputs
628!    INTEGER, INTENT(IN)                      :: knon
629!    real, INTENT(IN), DIMENSION(niso,klon)   :: xtrun_off_lic_0_diag
630!
631!    xtrun_off_lic_0(:,:)=xtrun_off_lic_0_diag(:,:)
632!
633!  end subroutine fonte_neige_export_xtrun_off_lic_0
634!#endif
635
636#ifdef ISO
637        subroutine gestion_neige_besoin_varglob_fonte_neige(klon,knon, &
638     &           xtprecip_snow,xtprecip_rain, &
639     &           fxtfonte_neige,fxtcalving, &
640     &           knindex,nisurf,run_off_lic_diag,coeff_rel_diag)
641
642        ! dans cette routine, on a besoin des variables globales de
643        ! fonte_neige_mod. Il faut donc la mettre dans fonte_neige_mod
644        ! le reste de gestion_neige est dans isotopes_routines_mod car sinon pb
645        ! de dépendance circulaire.
646
647    USE infotrac_phy, ONLY: ntraciso,niso
648    USE isotopes_mod, ONLY: iso_eau   
649  USE indice_sol_mod   
650#ifdef ISOVERIF
651    USE isotopes_verif_mod
652#endif
653        implicit none
654
655         ! inputs
656        integer klon,knon
657        real xtprecip_snow(ntraciso,klon),xtprecip_rain(ntraciso,klon)
658    INTEGER, INTENT(IN)                  :: nisurf
659    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
660    real, DIMENSION(klon), INTENT(IN) :: run_off_lic_diag 
661     real, INTENT(IN) ::   coeff_rel_diag 
662        real, DIMENSION(niso,klon), INTENT(IN) :: fxtfonte_neige,fxtcalving
663
664        ! locals
665        integer i,ixt,j
666       
667#ifdef ISOVERIF
668        IF (nisurf == is_lic) THEN
669          if (iso_eau.gt.0) then 
670           DO i = 1, knon
671             j = knindex(i)
672               call iso_verif_egalite(xtrun_off_lic_0(iso_eau,j), &
673     &                  run_off_lic_0(j),'gestion_neige_besoin_varglob_fonte_neige 625')
674           enddo
675          endif
676        endif
677#endif
678
679! calcul de run_off_lic
680
681      IF (nisurf == is_lic) THEN
682!         coeff_rel = dtime/(tau_calv * rday)
683#ifdef ISOVERIF
684        j=61
685        write(*,*) 'fonte_neige 636:'
686        write(*,*) 'run_off_lic_0(j)=',run_off_lic_0(j)
687        write(*,*) 'xtrun_off_lic_0(:,j)=',xtrun_off_lic_0(:,j)
688#endif
689         DO i = 1, knon
690          j = knindex(i)
691          do ixt=1,niso
692          xtrun_off_lic(ixt,i)   = (coeff_rel_diag *  fxtcalving(ixt,i)) + &
693               (1. - coeff_rel_diag) * xtrun_off_lic_0(ixt,j)
694          xtrun_off_lic_0(ixt,j) = xtrun_off_lic(ixt,i)
695          xtrun_off_lic(ixt,i)   = xtrun_off_lic(ixt,i) + fxtfonte_neige(ixt,i) + xtprecip_rain(ixt,i)
696          enddo !do ixt=1,niso
697#ifdef ISOVERIF
698          if (iso_eau.gt.0) then             
699                 if (iso_verif_egalite_choix_nostop(xtrun_off_lic(iso_eau,i), &
700     &                  run_off_lic_diag(i),'gestion_neige_besoin_varglob_fonte_neige 1201a', &
701     &                  errmax,errmaxrel).eq.1) then
702                        write(*,*) 'i,j=',i,j   
703                        write(*,*) 'coeff_rel_diag=',coeff_rel_diag
704                        stop
705                 endif
706          endif
707#endif
708         END DO
709      endif !IF (nisurf == is_lic) THEN 
710
711! Save ffonte, fqfonte and fqcalving in global arrays for each
712! sub-surface separately
713    DO i = 1, knon
714     do ixt=1,niso
715       fxtfonte_global(ixt,knindex(i),nisurf)   = fxtfonte_neige(ixt,i)
716       fxtcalving_global(ixt,knindex(i),nisurf) = fxtcalving(ixt,i)
717     enddo !do ixt=1,niso
718    ENDDO   
719
720    IF (nisurf == is_lic) THEN
721    DO i = 1, knon   
722     do ixt=1,niso   
723       xtrunofflic_global(ixt,knindex(i)) = xtrun_off_lic(ixt,i)
724     enddo ! do ixt=1,niso   
725    ENDDO
726    ENDIF
727       
728        end subroutine gestion_neige_besoin_varglob_fonte_neige
729#endif
730
731
732END MODULE fonte_neige_mod
Note: See TracBrowser for help on using the repository browser.