Ignore:
Timestamp:
10/24/17 01:22:08 (7 years ago)
Author:
dubos
Message:

devel : output theta and momentum fluxes

Location:
codes/icosagcm/devel/src/diagnostics
Files:
2 edited

Legend:

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

    r601 r603  
    5454       CALL swap_dimensions(ind) 
    5555       ZERO2(f_masst) 
     56       ZERO2(f_ulont) 
     57       ZERO2(f_thetat) 
    5658       ZERO2(f_epot) 
    5759       ZERO2(f_ekin) 
     
    5961       ZERO3(f_qmasst) 
    6062       ZERO2(f_massfluxt) 
     63       ZERO2(f_ulonfluxt) 
     64       ZERO2(f_thetafluxt) 
    6165       ZERO2(f_epotfluxt) 
    6266       ZERO2(f_ekinfluxt) 
     
    165169    ! even if loops are of the _ext variant, we still need halo exchanges before reconstructing fluxes at cell centers 
    166170    ! => loop over interior region 
    167     CALL distrib_level(ij_end-ij_begin+1,ij_omp_begin_ext,ij_omp_end_ext) 
    168     ij_omp_begin_ext = ij_omp_begin_ext+ij_begin-1 
    169     ij_omp_end_ext = ij_omp_end_ext+ij_begin-1 
     171    CALL distrib_level(ij_begin_ext, ij_end_ext, ij_omp_begin_ext,ij_omp_end_ext) 
    170172#include "../kernels/energy_fluxes.k90" 
    171173  END SUBROUTINE compute_diagflux_energy 
  • codes/icosagcm/devel/src/diagnostics/observable.f90

    r600 r603  
    11MODULE observable_mod 
    22  USE icosa 
     3  USE diagflux_mod 
     4  USE output_field_mod 
    35  IMPLICIT NONE 
    46  PRIVATE 
     
    3537    USE disvert_mod 
    3638    USE wind_mod 
    37     USE output_field_mod 
    3839    USE omp_para 
    3940    USE time_mod 
     
    4445    USE theta2theta_rhodz_mod 
    4546    USE omega_mod 
    46     USE diagflux_mod 
    4747    LOGICAL, INTENT(IN) :: init 
    4848    INTEGER :: l 
     
    163163          CALL output_field("massflux_lat",f_buf_ulat) 
    164164 
    165           CALL transfert_request(f_epotfluxt,req_e1_vect)  
    166           CALL flux_centered_lonlat(1./(itau_out*dt) , f_epotfluxt, f_buf_ulon, f_buf_ulat) 
    167           CALL output_field("epot_t", f_epot) 
    168           CALL output_field("epotflux_lon",f_buf_ulon) 
    169           CALL output_field("epotflux_lat",f_buf_ulat) 
    170  
    171           CALL transfert_request(f_ekinfluxt,req_e1_vect)  
    172           CALL flux_centered_lonlat(1./(itau_out*dt) , f_ekinfluxt, f_buf_ulon, f_buf_ulat) 
    173           CALL output_field("ekin_t", f_ekin) 
    174           CALL output_field("ekinflux_lon",f_buf_ulon) 
    175           CALL output_field("ekinflux_lat",f_buf_ulat) 
    176  
    177           CALL transfert_request(f_enthalpyfluxt,req_e1_vect)  
    178           CALL flux_centered_lonlat(1./(itau_out*dt) , f_enthalpyfluxt, f_buf_ulon, f_buf_ulat) 
    179           CALL output_field("enthalpy_t", f_enthalpy) 
    180           CALL output_field("enthalpyflux_lon",f_buf_ulon) 
    181           CALL output_field("enthalpyflux_lat",f_buf_ulat) 
     165          CALL output_energyflux(f_ulont, f_ulonfluxt, "ulon_t", "ulonflux_lon", "ulonflux_lat") 
     166          CALL output_energyflux(f_thetat, f_thetafluxt, "theta_t", "thetaflux_lon", "thetaflux_lat") 
     167          CALL output_energyflux(f_epot, f_epotfluxt, "epot_t", "epotflux_lon", "epotflux_lat") 
     168          CALL output_energyflux(f_ekin, f_ekinfluxt, "ekin_t", "ekinflux_lon", "ekinflux_lat") 
     169          CALL output_energyflux(f_enthalpy, f_enthalpyfluxt, "enthalpy_t", "enthalpyflux_lon", "enthalpyflux_lat") 
    182170 
    183171          CALL qflux_centered_lonlat(1./(itau_out*dt) , f_qfluxt, f_qfluxt_lon, f_qfluxt_lat) 
     
    189177    END IF 
    190178  END SUBROUTINE write_output_fields_basic 
     179 
     180  SUBROUTINE output_energyflux(f_energy, f_flux, name_energy, name_fluxlon, name_fluxlat) 
     181    TYPE(t_field), POINTER :: f_energy(:), f_flux(:) 
     182    CHARACTER(*), INTENT(IN) :: name_energy, name_fluxlon, name_fluxlat 
     183    CALL transfert_request(f_flux,req_e1_vect) 
     184    CALL flux_centered_lonlat(1./(itau_out*dt) , f_flux, f_buf_ulon, f_buf_ulat) 
     185    CALL output_field(name_energy,  f_energy) 
     186    CALL output_field(name_fluxlon, f_buf_ulon) 
     187    CALL output_field(name_fluxlat, f_buf_ulat) 
     188  END SUBROUTINE output_energyflux 
    191189   
    192190 !------------------- Conversion from prognostic to observable variables ------------------ 
Note: See TracChangeset for help on using the changeset viewer.