source: codes/icosagcm/devel/src/diagnostics/diagflux.f90 @ 583

Last change on this file since 583 was 583, checked in by dubos, 7 years ago

devel : accumulate tracer fluxes over time for diagnostics

File size: 1.1 KB
Line 
1MODULE diagflux_mod
2  USE icosa
3  IMPLICIT NONE
4  SAVE
5 
6  TYPE(t_field),POINTER :: f_qfluxt(:), f_qfluxt_i(:) ! time-integrated flux of scalars and its reconstruction at cell centers
7 
8  LOGICAL :: diagflux_on
9  !$OMP THREADPRIVATE(diagflux_on)
10
11CONTAINS
12
13  SUBROUTINE init_diagflux
14    USE getin_mod
15    diagflux_on = .FALSE.
16    CALL getin("diagflux", diagflux_on)
17    IF(diagflux_on) THEN
18       CALL allocate_field(f_qfluxt,  field_u,type_real,llm,nqtot, name="qfluxt")
19       CALL allocate_field(f_qfluxt_i,  field_t,type_real,llm,nqtot, name="qfluxt_i")
20       CALL zero_qfluxt
21    ELSE
22       CALL allocate_field(f_qfluxt,  field_u,type_real,llm,0, name="qfluxt")
23       CALL allocate_field(f_qfluxt_i,  field_t,type_real,llm,0, name="qfluxt_i")
24    END IF
25  END SUBROUTINE init_diagflux
26
27  SUBROUTINE zero_qfluxt
28    USE mpipara
29    USE omp_para
30    INTEGER :: ind
31    REAL(rstd), POINTER :: qfluxt(:,:,:)
32    DO ind=1,ndomain
33       IF (.NOT. assigned_domain(ind)) CYCLE
34       CALL swap_dimensions(ind)
35       qfluxt=f_qfluxt(ind)
36       qfluxt(:,ll_begin:ll_end,:)=0.
37    END DO
38  END SUBROUTINE zero_qfluxt
39 
40END MODULE diagflux_mod
Note: See TracBrowser for help on using the repository browser.