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

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

devel : multiplicative factor in flux/wind reconstructions

File size: 2.5 KB
Line 
1MODULE diagflux_mod
2  USE icosa
3  IMPLICIT NONE
4  SAVE
5 
6  TYPE(t_field),POINTER :: f_qfluxt(:), f_qfluxt_lon(:), f_qfluxt_lat(:) ! time-integrated flux of scalars and its reconstruction at cell centers
7  LOGICAL :: diagflux_on
8  !$OMP THREADPRIVATE(diagflux_on)
9
10CONTAINS
11
12  SUBROUTINE init_diagflux
13    USE getin_mod
14    diagflux_on = .FALSE.
15    CALL getin("diagflux", diagflux_on)
16    IF(diagflux_on) THEN
17       CALL allocate_field(f_qfluxt,  field_u,type_real,llm,nqtot, name="qfluxt")
18       CALL allocate_field(f_qfluxt_lon,  field_t,type_real,llm,nqtot, name="qfluxt_lon")
19       CALL allocate_field(f_qfluxt_lat,  field_t,type_real,llm,nqtot, name="qfluxt_lat")
20       CALL zero_qfluxt
21    ELSE
22       STOP ! FIXME
23       CALL allocate_field(f_qfluxt,  field_u,type_real,llm,0, name="qfluxt")
24       CALL allocate_field(f_qfluxt_lon,  field_t,type_real,llm,0, name="qfluxt_lon")
25       CALL allocate_field(f_qfluxt_lat,  field_t,type_real,llm,0, name="qfluxt_lat")
26    END IF
27  END SUBROUTINE init_diagflux
28
29  SUBROUTINE zero_qfluxt
30    USE mpipara
31    USE omp_para
32    INTEGER :: ind
33    REAL(rstd), POINTER :: qfluxt(:,:,:)
34    DO ind=1,ndomain
35       IF (.NOT. assigned_domain(ind)) CYCLE
36       CALL swap_dimensions(ind)
37       qfluxt=f_qfluxt(ind)
38       qfluxt(:,ll_begin:ll_end,:)=0.
39    END DO
40  END SUBROUTINE zero_qfluxt
41
42  SUBROUTINE flux_centered_lonlat(scale, f_flux, f_flux_lon, f_flux_lat)
43    REAL(rstd), INTENT(IN) :: scale
44    TYPE(t_field),POINTER :: f_flux(:), f_flux_lon(:), f_flux_lat(:)
45    REAL(rstd), POINTER :: flux(:,:,:), flux_lon(:,:,:), flux_lat(:,:,:)
46    INTEGER :: ind, itrac
47    DO ind=1,ndomain
48       IF (.NOT. assigned_domain(ind)) CYCLE
49       CALL swap_dimensions(ind)
50       CALL swap_geometry(ind)
51       flux=f_flux(ind)
52       flux_lon=f_flux_lon(ind)
53       flux_lat=f_flux_lat(ind)
54       DO itrac=1,nqtot
55          CALL compute_flux_centered_lonlat(scale, flux(:,:,itrac), flux_lon(:,:,itrac), flux_lat(:,:,itrac))
56       END DO
57    END DO
58  END SUBROUTINE flux_centered_lonlat
59 
60  SUBROUTINE compute_flux_centered_lonlat(scale, flux, flux_lon, flux_lat)
61    USE wind_mod
62    REAL(rstd), INTENT(IN) :: scale
63    REAL(rstd), INTENT(IN) :: flux(3*iim*jjm,llm)
64    REAL(rstd), INTENT(OUT) :: flux_lon(iim*jjm,llm), flux_lat(iim*jjm,llm)
65    REAL(rstd) :: flux_3d(iim*jjm,llm,3)
66    CALL compute_flux_centered(scale, flux, flux_3d)
67    CALL compute_wind_centered_lonlat_compound(flux_3d, flux_lon, flux_lat)
68  END SUBROUTINE compute_flux_centered_lonlat
69
70END MODULE diagflux_mod
Note: See TracBrowser for help on using the repository browser.