Ignore:
Timestamp:
10/23/17 18:25:46 (7 years ago)
Author:
dubos
Message:

devel : compute horizontal fluxes of ulon and theta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/diagnostics/diagflux.F90

    r595 r601  
    1010       f_massfluxt(:), f_qfluxt(:), & ! time-integrated mass flux and tracer flux 
    1111       f_qfluxt_lon(:), f_qfluxt_lat(:), & ! scalar flux reconstructed at cell centers 
    12        f_epot(:), f_ekin(:), f_enthalpy(:), & ! time-averaged potential E, kinetic E and enthalpy 
    13        f_epotfluxt(:), f_ekinfluxt(:), f_enthalpyfluxt(:) ! time averaged 'fluxes' of epot, ekin and enthalpy 
     12       f_ulont(:), f_thetat(:), f_epot(:), f_ekin(:), f_enthalpy(:), & ! time-averaged potential E, kinetic E and enthalpy 
     13       f_ulonfluxt(:), f_thetafluxt(:), f_epotfluxt(:), f_ekinfluxt(:), f_enthalpyfluxt(:) ! time averaged 'fluxes' of epot, ekin and enthalpy 
    1414  LOGICAL :: diagflux_on 
    1515  !$OMP THREADPRIVATE(diagflux_on) 
     
    2626    ll = MERGE(llm,1,diagflux_on) 
    2727    CALL allocate_field(f_masst,         field_t,type_real,ll,       name="masst") 
     28    CALL allocate_field(f_ulont,         field_t,type_real,ll,       name="ulont") 
     29    CALL allocate_field(f_thetat,        field_t,type_real,ll,       name="thetat") 
    2830    CALL allocate_field(f_epot,          field_t,type_real,ll,       name="epot") 
    2931    CALL allocate_field(f_ekin,          field_t,type_real,ll,       name="ekin") 
     
    3133    CALL allocate_field(f_qmasst,        field_t,type_real,ll,nqtot, name="qmasst") 
    3234    CALL allocate_field(f_massfluxt,     field_u,type_real,ll,       name="massfluxt") 
     35    CALL allocate_field(f_ulonfluxt,     field_u,type_real,ll,       name="ulonfluxt") 
     36    CALL allocate_field(f_thetafluxt,    field_u,type_real,ll,       name="thetafluxt") 
    3337    CALL allocate_field(f_epotfluxt,     field_u,type_real,ll,       name="epotfluxt") 
    3438    CALL allocate_field(f_ekinfluxt,     field_u,type_real,ll,       name="ekinfluxt") 
     
    110114!------------------------------------ Compute energy fluxes --------------------------------------- 
    111115 
    112   SUBROUTINE diagflux_energy(frac, f_phis,f_rhodz,f_theta_rhodz,f_u, f_geopot,f_theta, f_hfluxt) 
     116  SUBROUTINE diagflux_energy(frac, f_phis,f_rhodz,f_theta_rhodz,f_u, f_geopot,f_theta,f_pk, f_hfluxt) 
    113117    REAL(rstd), INTENT(IN) :: frac 
    114     TYPE(t_field),POINTER :: f_phis(:),f_rhodz(:),f_theta_rhodz(:),f_u(:), f_geopot(:), f_theta(:), f_hfluxt(:) 
     118    TYPE(t_field),POINTER :: f_phis(:),f_rhodz(:),f_theta_rhodz(:),f_u(:), f_geopot(:), f_theta(:), f_pk(:), f_hfluxt(:) 
    115119    REAL(rstd), POINTER :: phis(:), rhodz(:,:), theta_rhodz(:,:,:), u(:,:), & 
    116          geopot(:,:), pk(:,:,:), hfluxt(:,:), & 
    117          epot(:,:), ekin(:,:), enthalpy(:,:), & 
    118          epotflux(:,:), ekinflux(:,:), enthalpyflux(:,:) 
     120         geopot(:,:), theta(:,:,:), pk(:,:), hfluxt(:,:), & 
     121         ulont(:,:), thetat(:,:), epot(:,:), ekin(:,:), enthalpy(:,:), & 
     122         thetaflux(:,:), ulonflux(:,:), epotflux(:,:), ekinflux(:,:), enthalpyflux(:,:) 
    119123    INTEGER :: ind 
    120124    DO ind=1,ndomain 
     
    128132       u = f_u(ind) 
    129133       geopot = f_geopot(ind) 
    130        pk = f_theta(ind) ! buffer 
     134       theta = f_theta(ind) ! buffer 
     135       pk = f_pk(ind) ! buffer 
     136       ulont = f_ulont(ind) 
     137       thetat = f_thetat(ind) 
    131138       epot = f_epot(ind) 
    132139       ekin = f_ekin(ind) 
    133140       enthalpy = f_enthalpy(ind) 
     141       ulonflux = f_ulonfluxt(ind) 
     142       thetaflux = f_thetafluxt(ind) 
    134143       epotflux = f_epotfluxt(ind) 
    135144       ekinflux = f_ekinfluxt(ind) 
    136145       enthalpyflux = f_enthalpyfluxt(ind) 
    137        CALL compute_diagflux_energy(frac,hfluxt, phis,rhodz,theta_rhodz,u, geopot,pk, epot,ekin,enthalpy, epotflux, ekinflux, enthalpyflux) 
     146       CALL compute_diagflux_energy(frac,hfluxt, phis,rhodz,theta_rhodz,u, geopot,theta,pk, & 
     147            ulont, thetat, epot, ekin, enthalpy, & 
     148            ulonflux, thetaflux, epotflux, ekinflux, enthalpyflux) 
    138149    END DO 
    139150  END SUBROUTINE diagflux_energy 
    140151 
    141   SUBROUTINE compute_diagflux_energy(frac, massflux, phis,rhodz,theta_rhodz,u, geopot,pk, epot,ekin,enthalpy, epot_flux, ekin_flux, enthalpy_flux) 
     152  SUBROUTINE compute_diagflux_energy(frac, massflux, phis,rhodz,theta_rhodz,ue, geopot,theta,pk, & 
     153       ulon, thetat, epot, ekin, enthalpy, & 
     154       ulon_flux, thetat_flux, epot_flux, ekin_flux, enthalpy_flux) 
    142155    USE disvert_mod, ONLY : ptop 
    143156    REAL(rstd), INTENT(IN) :: frac 
    144     REAL(rstd), INTENT(IN) :: massflux(3*iim*jjm,llm), u(3*iim*jjm,llm),& 
     157    REAL(rstd), INTENT(IN) :: massflux(3*iim*jjm,llm), ue(3*iim*jjm,llm),& 
    145158                              phis(iim*jjm), rhodz(iim*jjm,llm), theta_rhodz(iim*jjm,llm,nqtot) 
    146     REAL(rstd), INTENT(INOUT) :: geopot(iim*jjm,llm+1), pk(iim*jjm,llm) ! pk = buffer 
    147     REAL(rstd), INTENT(INOUT), DIMENSION(iim*jjm, llm)   ::  epot, ekin, enthalpy 
    148     REAL(rstd), INTENT(INOUT), DIMENSION(3*iim*jjm, llm) ::  epot_flux, ekin_flux, enthalpy_flux     
    149     REAL(rstd) :: energy, p_ik, theta_ik, temp_ik, gv, Rd  
     159    REAL(rstd), INTENT(INOUT) :: geopot(iim*jjm,llm+1), theta(iim*jjm,llm), pk(iim*jjm,llm) ! theta,pk = buffers 
     160    REAL(rstd), INTENT(INOUT), DIMENSION(iim*jjm, llm)   ::  ulon, thetat, epot, ekin, enthalpy 
     161    REAL(rstd), INTENT(INOUT), DIMENSION(3*iim*jjm, llm) ::  ulon_flux, thetat_flux, epot_flux, ekin_flux, enthalpy_flux     
     162    REAL(rstd) :: energy, p_ik, theta_ik, temp_ik, gv, Rd, cx,cy,cz, ux,uy,uz, ue_le,ulon_i 
    150163    INTEGER :: ij, l, ij_omp_begin_ext, ij_omp_end_ext 
    151164    Rd = kappa*cpp 
Note: See TracChangeset for help on using the changeset viewer.