source: codes/icosagcm/devel/src/diagnostics/diagflux.F90 @ 732

Last change on this file since 732 was 732, checked in by dubos, 6 years ago

devel : more cleanup and reorganization in dynamics/

File size: 7.8 KB
RevLine 
[583]1MODULE diagflux_mod
2  USE icosa
[594]3  USE omp_para
[732]4  USE caldyn_vars_mod
[583]5  IMPLICIT NONE
6  SAVE
[594]7  PRIVATE
8
9  TYPE(t_field), POINTER, PUBLIC :: &
[593]10       f_masst(:), f_qmasst(:), & ! time-averaged mass, tracer mass,
11       f_massfluxt(:), f_qfluxt(:), & ! time-integrated mass flux and tracer flux
12       f_qfluxt_lon(:), f_qfluxt_lat(:), & ! scalar flux reconstructed at cell centers
[601]13       f_ulont(:), f_thetat(:), f_epot(:), f_ekin(:), f_enthalpy(:), & ! time-averaged potential E, kinetic E and enthalpy
14       f_ulonfluxt(:), f_thetafluxt(:), f_epotfluxt(:), f_ekinfluxt(:), f_enthalpyfluxt(:) ! time averaged 'fluxes' of epot, ekin and enthalpy
[583]15  LOGICAL :: diagflux_on
16  !$OMP THREADPRIVATE(diagflux_on)
17
[594]18  PUBLIC :: diagflux_on, init_diagflux, zero_qfluxt, qflux_centered_lonlat, flux_centered_lonlat, diagflux_energy
19
[583]20CONTAINS
21
22  SUBROUTINE init_diagflux
23    USE getin_mod
[593]24    INTEGER :: ll
[583]25    diagflux_on = .FALSE.
26    CALL getin("diagflux", diagflux_on)
[594]27    ll = MERGE(llm,1,diagflux_on)
[593]28    CALL allocate_field(f_masst,         field_t,type_real,ll,       name="masst")
[601]29    CALL allocate_field(f_ulont,         field_t,type_real,ll,       name="ulont")
30    CALL allocate_field(f_thetat,        field_t,type_real,ll,       name="thetat")
[593]31    CALL allocate_field(f_epot,          field_t,type_real,ll,       name="epot")
32    CALL allocate_field(f_ekin,          field_t,type_real,ll,       name="ekin")
33    CALL allocate_field(f_enthalpy,      field_t,type_real,ll,       name="enthalpy")
34    CALL allocate_field(f_qmasst,        field_t,type_real,ll,nqtot, name="qmasst")
35    CALL allocate_field(f_massfluxt,     field_u,type_real,ll,       name="massfluxt")
[601]36    CALL allocate_field(f_ulonfluxt,     field_u,type_real,ll,       name="ulonfluxt")
37    CALL allocate_field(f_thetafluxt,    field_u,type_real,ll,       name="thetafluxt")
[593]38    CALL allocate_field(f_epotfluxt,     field_u,type_real,ll,       name="epotfluxt")
39    CALL allocate_field(f_ekinfluxt,     field_u,type_real,ll,       name="ekinfluxt")
40    CALL allocate_field(f_enthalpyfluxt, field_u,type_real,ll,       name="enthalpyfluxt")
41    CALL allocate_field(f_qfluxt,        field_u,type_real,ll,nqtot, name="qfluxt")
42    CALL allocate_field(f_qfluxt_lon,    field_t,type_real,ll,nqtot, name="qfluxt_lon")
43    CALL allocate_field(f_qfluxt_lat,    field_t,type_real,ll,nqtot, name="qfluxt_lat")
44    IF(diagflux_on) CALL zero_qfluxt
[583]45  END SUBROUTINE init_diagflux
46
[594]47#define ZERO2(field) buf2=field(ind) ; buf2(:,ll_begin:ll_end)=0.
48#define ZERO3(field) buf3=field(ind) ; buf3(:,ll_begin:ll_end,:)=0.
49
[583]50  SUBROUTINE zero_qfluxt
51    INTEGER :: ind
[592]52    REAL(rstd), POINTER :: buf2(:,:),buf3(:,:,:)
[583]53    DO ind=1,ndomain
54       IF (.NOT. assigned_domain(ind)) CYCLE
55       CALL swap_dimensions(ind)
[594]56       ZERO2(f_masst)
[603]57       ZERO2(f_ulont)
58       ZERO2(f_thetat)
[594]59       ZERO2(f_epot)
60       ZERO2(f_ekin)
61       ZERO2(f_enthalpy)
62       ZERO3(f_qmasst)
63       ZERO2(f_massfluxt)
[603]64       ZERO2(f_ulonfluxt)
65       ZERO2(f_thetafluxt)
[594]66       ZERO2(f_epotfluxt)
67       ZERO2(f_ekinfluxt)
68       ZERO2(f_enthalpyfluxt)
69       ZERO3(f_qfluxt)
[583]70    END DO
71  END SUBROUTINE zero_qfluxt
[585]72
[594]73!------------------------------------ Reconstruct fluxes at cell centers ---------------------------------------
74
75  SUBROUTINE qflux_centered_lonlat(scale, f_flux, f_flux_lon, f_flux_lat)
[587]76    REAL(rstd), INTENT(IN) :: scale
[594]77    TYPE(t_field),POINTER :: f_flux(:), f_flux_lon(:), f_flux_lat(:)
78    REAL(rstd), POINTER :: flux(:,:,:), flux_lon(:,:,:), flux_lat(:,:,:)
[585]79    INTEGER :: ind, itrac
80    DO ind=1,ndomain
81       IF (.NOT. assigned_domain(ind)) CYCLE
82       CALL swap_dimensions(ind)
83       CALL swap_geometry(ind)
84       flux=f_flux(ind)
[587]85       flux_lon=f_flux_lon(ind)
86       flux_lat=f_flux_lat(ind)
[585]87       DO itrac=1,nqtot
[587]88          CALL compute_flux_centered_lonlat(scale, flux(:,:,itrac), flux_lon(:,:,itrac), flux_lat(:,:,itrac))
[585]89       END DO
90    END DO
[594]91  END SUBROUTINE qflux_centered_lonlat
92 
93  SUBROUTINE flux_centered_lonlat(scale, f_flux, f_flux_lon, f_flux_lat)
94    REAL(rstd), INTENT(IN) :: scale
95    TYPE(t_field),POINTER :: f_flux(:), f_flux_lon(:), f_flux_lat(:)
96    REAL(rstd), POINTER :: flux(:,:), flux_lon(:,:), flux_lat(:,:)
97    INTEGER :: ind
98    DO ind=1,ndomain
99       IF (.NOT. assigned_domain(ind)) CYCLE
100       CALL swap_dimensions(ind)
101       CALL swap_geometry(ind)
102       flux=f_flux(ind)
103       flux_lon=f_flux_lon(ind)
104       flux_lat=f_flux_lat(ind)
105       CALL compute_flux_centered_lonlat(scale, flux, flux_lon, flux_lat)
106    END DO
[585]107  END SUBROUTINE flux_centered_lonlat
[583]108 
[587]109  SUBROUTINE compute_flux_centered_lonlat(scale, flux, flux_lon, flux_lat)
110    USE wind_mod
111    REAL(rstd), INTENT(IN) :: scale
[585]112    REAL(rstd), INTENT(IN) :: flux(3*iim*jjm,llm)
113    REAL(rstd), INTENT(OUT) :: flux_lon(iim*jjm,llm), flux_lat(iim*jjm,llm)
114    REAL(rstd) :: flux_3d(iim*jjm,llm,3)
[587]115    CALL compute_flux_centered(scale, flux, flux_3d)
[585]116    CALL compute_wind_centered_lonlat_compound(flux_3d, flux_lon, flux_lat)
117  END SUBROUTINE compute_flux_centered_lonlat
118
[594]119!------------------------------------ Compute energy fluxes ---------------------------------------
120
[601]121  SUBROUTINE diagflux_energy(frac, f_phis,f_rhodz,f_theta_rhodz,f_u, f_geopot,f_theta,f_pk, f_hfluxt)
[594]122    REAL(rstd), INTENT(IN) :: frac
[601]123    TYPE(t_field),POINTER :: f_phis(:),f_rhodz(:),f_theta_rhodz(:),f_u(:), f_geopot(:), f_theta(:), f_pk(:), f_hfluxt(:)
[594]124    REAL(rstd), POINTER :: phis(:), rhodz(:,:), theta_rhodz(:,:,:), u(:,:), &
[601]125         geopot(:,:), theta(:,:,:), pk(:,:), hfluxt(:,:), &
126         ulont(:,:), thetat(:,:), epot(:,:), ekin(:,:), enthalpy(:,:), &
127         thetaflux(:,:), ulonflux(:,:), epotflux(:,:), ekinflux(:,:), enthalpyflux(:,:)
[594]128    INTEGER :: ind
129    DO ind=1,ndomain
130       IF (.NOT. assigned_domain(ind)) CYCLE
131       CALL swap_dimensions(ind)
132       CALL swap_geometry(ind)
133       hfluxt = f_hfluxt(ind)
134       phis = f_phis(ind)
135       rhodz = f_rhodz(ind)
136       theta_rhodz = f_theta_rhodz(ind)
137       u = f_u(ind)
138       geopot = f_geopot(ind)
[601]139       theta = f_theta(ind) ! buffer
140       pk = f_pk(ind) ! buffer
141       ulont = f_ulont(ind)
142       thetat = f_thetat(ind)
[594]143       epot = f_epot(ind)
144       ekin = f_ekin(ind)
145       enthalpy = f_enthalpy(ind)
[601]146       ulonflux = f_ulonfluxt(ind)
147       thetaflux = f_thetafluxt(ind)
[594]148       epotflux = f_epotfluxt(ind)
149       ekinflux = f_ekinfluxt(ind)
150       enthalpyflux = f_enthalpyfluxt(ind)
[601]151       CALL compute_diagflux_energy(frac,hfluxt, phis,rhodz,theta_rhodz,u, geopot,theta,pk, &
152            ulont, thetat, epot, ekin, enthalpy, &
153            ulonflux, thetaflux, epotflux, ekinflux, enthalpyflux)
[594]154    END DO
155  END SUBROUTINE diagflux_energy
156
[601]157  SUBROUTINE compute_diagflux_energy(frac, massflux, phis,rhodz,theta_rhodz,ue, geopot,theta,pk, &
158       ulon, thetat, epot, ekin, enthalpy, &
159       ulon_flux, thetat_flux, epot_flux, ekin_flux, enthalpy_flux)
[594]160    USE disvert_mod, ONLY : ptop
161    REAL(rstd), INTENT(IN) :: frac
[601]162    REAL(rstd), INTENT(IN) :: massflux(3*iim*jjm,llm), ue(3*iim*jjm,llm),&
[594]163                              phis(iim*jjm), rhodz(iim*jjm,llm), theta_rhodz(iim*jjm,llm,nqtot)
[601]164    REAL(rstd), INTENT(INOUT) :: geopot(iim*jjm,llm+1), theta(iim*jjm,llm), pk(iim*jjm,llm) ! theta,pk = buffers
165    REAL(rstd), INTENT(INOUT), DIMENSION(iim*jjm, llm)   ::  ulon, thetat, epot, ekin, enthalpy
166    REAL(rstd), INTENT(INOUT), DIMENSION(3*iim*jjm, llm) ::  ulon_flux, thetat_flux, epot_flux, ekin_flux, enthalpy_flux   
167    REAL(rstd) :: energy, p_ik, theta_ik, temp_ik, gv, Rd, cx,cy,cz, ux,uy,uz, ue_le,ulon_i
[594]168    INTEGER :: ij, l, ij_omp_begin_ext, ij_omp_end_ext
169    Rd = kappa*cpp
[595]170    ! even if loops are of the _ext variant, we still need halo exchanges before reconstructing fluxes at cell centers
171    ! => loop over interior region
[603]172    CALL distrib_level(ij_begin_ext, ij_end_ext, ij_omp_begin_ext,ij_omp_end_ext)
[612]173#include "../kernels_hex/energy_fluxes.k90"
[594]174  END SUBROUTINE compute_diagflux_energy
175
[583]176END MODULE diagflux_mod
Note: See TracBrowser for help on using the repository browser.