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

Last change on this file since 4033 was 4033, checked in by crisi, 2 years ago

nettoyage de sorties ecran

File size: 23.9 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
348    IF (.NOT. ok_lic_cond) THEN
349!---only positive evaporation has an impact on snow
350!---note that this could create a bit of water
351!---this was the default until CMIP6
352      WHERE (evap > 0. )
353         snow_evap = MIN (snow / dtime, evap)    !---one cannot evaporate more than the amount of snow
354         snow = snow - snow_evap * dtime         !---snow that remains on the ground
355         snow = MAX(0.0, snow)                   !---just in case
356      END WHERE
357
358    ELSE
359!--now considers both positive and negative evaporation in the budget of snow
360      snow_evap = MIN (snow / dtime, evap)    !---one cannot evaporate more than the amount of snow
361      snow = snow - snow_evap * dtime         !---snow that remains or deposits on the ground
362      snow = MAX(0.0, snow)                   !---just in case
363
364   ENDIF
365   
366
367    bil_eau_s(:) = (precip_rain(:) * dtime) - (evap(:) - snow_evap(:)) * dtime
368#ifdef ISO
369        snow_evap_diag(:)=snow_evap(:)
370        coeff_rel_diag=coeff_rel
371#endif
372
373
374!****************************************************************************************
375! - Calculate melting snow
376! - Calculate calving and decrement snow, if there are to much snow
377! - Update temperature at surface
378!
379!****************************************************************************************
380
381    ffonte(:) = 0.0
382    fqcalving(:) = 0.0
383    fqfonte(:) = 0.0
384
385    DO i = 1, knon
386       ! Y'a-t-il fonte de neige?
387       neige_fond = (snow(i)>epsfra .OR. nisurf==is_sic .OR. nisurf==is_lic) .AND. tsurf_new(i)>=RTT
388       IF (neige_fond) THEN
389          fq_fonte     = MIN( MAX((tsurf_new(i)-RTT )/chasno,0.0),snow(i))
390          ffonte(i)    = fq_fonte * RLMLT/dtime
391          fqfonte(i)   = fq_fonte/dtime
392          snow(i)      = MAX(0., snow(i) - fq_fonte)
393          bil_eau_s(i) = bil_eau_s(i) + fq_fonte
394          tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno 
395#ifdef ISO
396        fq_fonte_diag(i)=fq_fonte
397#endif
398
399!IM cf JLD OK     
400!IM cf JLD/ GKtest fonte aussi pour la glace
401          IF (nisurf == is_sic .OR. nisurf == is_lic ) THEN
402             fq_fonte = MAX((tsurf_new(i)-RTT )/chaice,0.0)
403             ffonte(i) = ffonte(i) + fq_fonte * RLMLT/dtime
404             IF ( ok_lic_melt ) THEN
405                fqfonte(i) = fqfonte(i) + fq_fonte/dtime
406                bil_eau_s(i) = bil_eau_s(i) + fq_fonte
407             ENDIF
408             tsurf_new(i) = RTT
409          ENDIF
410          d_ts(i) = tsurf_new(i) - tsurf(i)
411       ENDIF
412
413       ! s'il y a une hauteur trop importante de neige, elle est ecretee
414       fqcalving(i) = MAX(0., snow(i) - snow_max)/dtime
415       snow(i)=MIN(snow(i),snow_max)
416    ENDDO
417#ifdef ISO
418    DO i = 1, knon
419       fqcalving_diag(i)=fqcalving(i)
420       fqfonte_diag(i)=fqfonte(i)
421    enddo !DO i = 1, knon
422#endif
423
424    IF (nisurf == is_ter) THEN
425       DO i = 1, knon
426          qsol(i) = qsol(i) + bil_eau_s(i)
427          run_off_ter(i) = run_off_ter(i) + MAX(qsol(i) - max_eau_sol, 0.0)
428#ifdef ISO
429        runoff_diag(i)=MAX(qsol(i) - max_eau_sol, 0.0)
430#endif
431          qsol(i) = MIN(qsol(i), max_eau_sol)
432       ENDDO
433    ELSE IF (nisurf == is_lic) THEN
434       DO i = 1, knon
435          j = knindex(i)
436          !--temporal filtering
437          run_off_lic(i)   = coeff_rel*fqcalving(i) + (1.-coeff_rel)*run_off_lic_0(j)
438          run_off_lic_0(j) = run_off_lic(i)
439          !--add melting snow and liquid precip to runoff of ice cap
440          run_off_lic(i)   = run_off_lic(i) + fqfonte(i) + precip_rain(i)
441       ENDDO
442    ENDIF
443
444#ifdef ISO
445    DO i = 1, klon   
446        run_off_lic_diag(i)=run_off_lic(i)
447    enddo ! DO i = 1, knon   
448#endif
449   
450!****************************************************************************************
451! Save ffonte, fqfonte and fqcalving in global arrays for each
452! sub-surface separately
453!
454!****************************************************************************************
455    DO i = 1, knon
456       ffonte_global(knindex(i),nisurf)    = ffonte(i)
457       fqfonte_global(knindex(i),nisurf)   = fqfonte(i)
458       fqcalving_global(knindex(i),nisurf) = fqcalving(i)
459    ENDDO
460
461    IF (nisurf == is_lic) THEN
462    DO i = 1, knon
463       runofflic_global(knindex(i)) = run_off_lic(i)
464    ENDDO
465    ENDIF
466
467  END SUBROUTINE fonte_neige
468!
469!****************************************************************************************
470!
471  SUBROUTINE fonte_neige_final(restart_runoff &
472#ifdef ISO     
473     &     ,xtrestart_runoff &
474#endif   
475     &   )
476!
477! This subroutine returns run_off_lic_0 for later writing to restart file.
478!
479#ifdef ISO
480    use infotrac_phy, ONLY: niso
481#ifdef ISOVERIF
482    use isotopes_mod, ONLY: iso_eau
483    use isotopes_verif_mod
484#endif
485#endif
486!****************************************************************************************
487    REAL, DIMENSION(klon), INTENT(OUT) :: restart_runoff
488#ifdef ISO     
489    REAL, DIMENSION(niso,klon), INTENT(OUT) :: xtrestart_runoff
490#ifdef ISOVERIF
491    integer i
492#endif 
493#endif
494
495!****************************************************************************************
496! Set the output variables
497    restart_runoff(:) = run_off_lic_0(:)
498#ifdef ISO
499    xtrestart_runoff(:,:) = xtrun_off_lic_0(:,:)
500#ifdef ISOVERIF
501      if (iso_eau.gt.0) then   
502        do i=1,klon
503          if (iso_verif_egalite_nostop(run_off_lic_0(i), &
504     &         xtrun_off_lic_0(iso_eau,i),'fonte_neige 413') &
505     &         .eq.1) then
506              write(*,*) 'i=',i
507              stop
508          endif
509        enddo !do i=1,klon
510      endif !if (iso_eau.gt.0) then
511#endif   
512#endif
513
514! Deallocation of all varaibles in the module
515!   DEALLOCATE(run_off_lic_0, run_off_ter, run_off_lic, ffonte_global, &
516!        fqfonte_global, fqcalving_global)
517
518    IF (ALLOCATED(run_off_lic_0)) DEALLOCATE(run_off_lic_0)
519    IF (ALLOCATED(run_off_ter)) DEALLOCATE(run_off_ter)
520    IF (ALLOCATED(run_off_lic)) DEALLOCATE(run_off_lic)
521    IF (ALLOCATED(ffonte_global)) DEALLOCATE(ffonte_global)
522    IF (ALLOCATED(fqfonte_global)) DEALLOCATE(fqfonte_global)
523    IF (ALLOCATED(fqcalving_global)) DEALLOCATE(fqcalving_global)
524    IF (ALLOCATED(runofflic_global)) DEALLOCATE(runofflic_global)
525#ifdef ISO
526    IF (ALLOCATED(xtrun_off_lic_0)) DEALLOCATE(xtrun_off_lic_0)
527    IF (ALLOCATED(xtrun_off_ter)) DEALLOCATE(xtrun_off_ter)
528    IF (ALLOCATED(xtrun_off_lic)) DEALLOCATE(xtrun_off_lic)
529    IF (ALLOCATED(fxtfonte_global)) DEALLOCATE(fxtfonte_global)
530    IF (ALLOCATED(fxtcalving_global)) DEALLOCATE(fxtcalving_global)
531    IF (ALLOCATED(xtrunofflic_global)) DEALLOCATE(xtrunofflic_global)
532#endif
533
534  END SUBROUTINE fonte_neige_final
535!
536!****************************************************************************************
537!
538  SUBROUTINE fonte_neige_get_vars(pctsrf, fqcalving_out, &
539       fqfonte_out, ffonte_out, run_off_lic_out &
540#ifdef ISO     
541     &  ,fxtcalving_out, fxtfonte_out,xtrun_off_lic_out &
542#endif     
543     &  )
544
545
546! Cumulate ffonte, fqfonte and fqcalving respectively for
547! all type of surfaces according to their fraction.
548!
549! This routine is called from physiq.F before histwrite.
550!****************************************************************************************
551
552  USE indice_sol_mod
553#ifdef ISO
554    use infotrac_phy, ONLY: niso
555#endif
556
557    REAL, DIMENSION(klon,nbsrf), INTENT(IN) :: pctsrf
558
559    REAL, DIMENSION(klon), INTENT(OUT)      :: fqcalving_out
560    REAL, DIMENSION(klon), INTENT(OUT)      :: fqfonte_out
561    REAL, DIMENSION(klon), INTENT(OUT)      :: ffonte_out
562    REAL, DIMENSION(klon), INTENT(OUT)      :: run_off_lic_out
563
564
565#ifdef ISO
566    REAL, DIMENSION(niso,klon), INTENT(OUT)      :: fxtcalving_out
567    REAL, DIMENSION(niso,klon), INTENT(OUT)      :: fxtfonte_out
568    REAL, DIMENSION(niso,klon), INTENT(OUT)      :: xtrun_off_lic_out
569    integer i,ixt
570#endif
571    INTEGER   :: nisurf
572!****************************************************************************************
573
574    ffonte_out(:)    = 0.0
575    fqfonte_out(:)   = 0.0
576    fqcalving_out(:) = 0.0
577#ifdef ISO       
578    fxtfonte_out(:,:)   = 0.0
579    fxtcalving_out(:,:) = 0.0
580#endif
581
582    DO nisurf = 1, nbsrf
583       ffonte_out(:) = ffonte_out(:) + ffonte_global(:,nisurf)*pctsrf(:,nisurf)
584       fqfonte_out(:) = fqfonte_out(:) + fqfonte_global(:,nisurf)*pctsrf(:,nisurf)
585       fqcalving_out(:) = fqcalving_out(:) + fqcalving_global(:,nisurf)*pctsrf(:,nisurf)
586    ENDDO
587
588    run_off_lic_out(:)=runofflic_global(:)
589
590
591#ifdef ISO
592       DO nisurf = 1, nbsrf
593        do i=1,klon
594         do ixt=1,niso
595          fxtfonte_out(ixt,i) = fxtfonte_out(ixt,i) + fxtfonte_global(ixt,i,nisurf)*pctsrf(i,nisurf)
596          fxtcalving_out(ixt,i) = fxtcalving_out(ixt,i) + fxtcalving_global(ixt,i,nisurf)*pctsrf(i,nisurf)
597         enddo !do ixt=1,niso
598        enddo !do i=1,klon
599       enddo !DO nisurf = 1, nbsrf
600       xtrun_off_lic_out(:,:)=xtrunofflic_global(:,:)
601#endif
602
603  END SUBROUTINE fonte_neige_get_vars
604!
605!****************************************************************************************
606!
607!#ifdef ISO
608!  subroutine fonte_neige_export_xtrun_off_lic_0(knon,xtrun_off_lic_0_diag)
609!    use infotrac_phy, ONLY: niso
610!
611!    ! inputs
612!    INTEGER, INTENT(IN)                      :: knon
613!    real, INTENT(IN), DIMENSION(niso,klon)   :: xtrun_off_lic_0_diag
614!
615!    xtrun_off_lic_0(:,:)=xtrun_off_lic_0_diag(:,:)
616!
617!  end subroutine fonte_neige_export_xtrun_off_lic_0
618!#endif
619
620#ifdef ISO
621        subroutine gestion_neige_besoin_varglob_fonte_neige(klon,knon, &
622     &           xtprecip_snow,xtprecip_rain, &
623     &           fxtfonte_neige,fxtcalving, &
624     &           knindex,nisurf,run_off_lic_diag,coeff_rel_diag)
625
626        ! dans cette routine, on a besoin des variables globales de
627        ! fonte_neige_mod. Il faut donc la mettre dans fonte_neige_mod
628        ! le reste de gestion_neige est dans isotopes_routines_mod car sinon pb
629        ! de dépendance circulaire.
630
631    USE infotrac_phy, ONLY: ntraciso,niso
632    USE isotopes_mod, ONLY: iso_eau   
633  USE indice_sol_mod   
634#ifdef ISOVERIF
635    USE isotopes_verif_mod
636#endif
637        implicit none
638
639         ! inputs
640        integer klon,knon
641        real xtprecip_snow(ntraciso,klon),xtprecip_rain(ntraciso,klon)
642    INTEGER, INTENT(IN)                  :: nisurf
643    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex
644    real, DIMENSION(klon), INTENT(IN) :: run_off_lic_diag 
645     real, INTENT(IN) ::   coeff_rel_diag 
646        real, DIMENSION(niso,klon), INTENT(IN) :: fxtfonte_neige,fxtcalving
647
648        ! locals
649        integer i,ixt,j
650       
651#ifdef ISOVERIF
652        IF (nisurf == is_lic) THEN
653          if (iso_eau.gt.0) then 
654           DO i = 1, knon
655             j = knindex(i)
656               call iso_verif_egalite(xtrun_off_lic_0(iso_eau,j), &
657     &                  run_off_lic_0(j),'gestion_neige_besoin_varglob_fonte_neige 625')
658           enddo
659          endif
660        endif
661#endif
662
663! calcul de run_off_lic
664
665      IF (nisurf == is_lic) THEN
666!         coeff_rel = dtime/(tau_calv * rday)
667
668         DO i = 1, knon
669          j = knindex(i)
670          do ixt=1,niso
671          xtrun_off_lic(ixt,i)   = (coeff_rel_diag *  fxtcalving(ixt,i)) + &
672               (1. - coeff_rel_diag) * xtrun_off_lic_0(ixt,j)
673          xtrun_off_lic_0(ixt,j) = xtrun_off_lic(ixt,i)
674          xtrun_off_lic(ixt,i)   = xtrun_off_lic(ixt,i) + fxtfonte_neige(ixt,i) + xtprecip_rain(ixt,i)
675          enddo !do ixt=1,niso
676#ifdef ISOVERIF
677          if (iso_eau.gt.0) then             
678                 if (iso_verif_egalite_choix_nostop(xtrun_off_lic(iso_eau,i), &
679     &                  run_off_lic_diag(i),'gestion_neige_besoin_varglob_fonte_neige 1201a', &
680     &                  errmax,errmaxrel).eq.1) then
681                        write(*,*) 'i,j=',i,j   
682                        write(*,*) 'coeff_rel_diag=',coeff_rel_diag
683                        stop
684                 endif
685          endif
686#endif
687         END DO
688      endif !IF (nisurf == is_lic) THEN 
689
690! Save ffonte, fqfonte and fqcalving in global arrays for each
691! sub-surface separately
692    DO i = 1, knon
693     do ixt=1,niso
694       fxtfonte_global(ixt,knindex(i),nisurf)   = fxtfonte_neige(ixt,i)
695       fxtcalving_global(ixt,knindex(i),nisurf) = fxtcalving(ixt,i)
696     enddo !do ixt=1,niso
697    ENDDO   
698
699    IF (nisurf == is_lic) THEN
700    DO i = 1, knon   
701     do ixt=1,niso   
702       xtrunofflic_global(ixt,knindex(i)) = xtrun_off_lic(ixt,i)
703     enddo ! do ixt=1,niso   
704    ENDDO
705    ENDIF
706       
707        end subroutine gestion_neige_besoin_varglob_fonte_neige
708#endif
709
710
711END MODULE fonte_neige_mod
Note: See TracBrowser for help on using the repository browser.