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

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

devel : reconstruct fluxes at cell centers

File size: 2.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
40  SUBROUTINE flux_centered_lonlat(f_flux, f_flux_lon, f_flux_lat)
41    TYPE(t_field),POINTER :: f_flux(:), f_flux_lon(:), f_flux_lat(:)
42    REAL(rstd), POINTER :: flux(:,:,:), flux_lon(:,:,:), flux_lat(:,:,:)
43    INTEGER :: ind, itrac
44    DO ind=1,ndomain
45       IF (.NOT. assigned_domain(ind)) CYCLE
46       CALL swap_dimensions(ind)
47       CALL swap_geometry(ind)
48       flux=f_flux(ind)
49       DO itrac=1,nqtot
50          CALL compute_flux_centered_lonlat(flux(:,:,itrac), flux_lon(:,:,itrac), flux_lat(:,:,itrac))
51       END DO
52    END DO
53  END SUBROUTINE flux_centered_lonlat
54 
55  SUBROUTINE compute_flux_centered_lonlat(flux, flux_lon, flux_lat)
56    REAL(rstd), INTENT(IN) :: flux(3*iim*jjm,llm)
57    REAL(rstd), INTENT(OUT) :: flux_lon(iim*jjm,llm), flux_lat(iim*jjm,llm)
58    REAL(rstd) :: flux_3d(iim*jjm,llm,3)
59    CALL compute_flux_centered(flux, flux_3d)
60    CALL compute_wind_centered_lonlat_compound(flux_3d, flux_lon, flux_lat)
61  END SUBROUTINE compute_flux_centered_lonlat
62
63END MODULE diagflux_mod
Note: See TracBrowser for help on using the repository browser.