Ignore:
Timestamp:
02/09/15 20:18:34 (9 years ago)
Author:
ymipsl
Message:

Merge recent developments from saturn branch onto trunk.

  • lmdz generic physics interface
  • performance improvment on mix mpi/openmp
  • asynchrone and overlaping communication
  • best domain distribution between process and threads
  • ....

This version is compatible with the actual saturn version and the both branches are considered merged on dynamico component.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/etat0.f90

    r325 r327  
    1818    USE etat0_dcmip5_mod, ONLY : getin_etat0_dcmip5=>getin_etat0 
    1919    USE etat0_williamson_mod, ONLY : getin_etat0_williamson=>getin_etat0 
     20    USE etat0_temperature_mod, ONLY: getin_etat0_temperature=>getin_etat0 
    2021    ! Old interface 
    2122    USE etat0_academic_mod, ONLY : etat0_academic=>etat0   
     
    5556    CASE ('isothermal') 
    5657       CALL getin_etat0_isothermal 
     58       CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) 
     59    CASE ('temperature_profile') 
     60       CALL getin_etat0_temperature 
    5761       CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) 
    5862    CASE ('jablonowsky06') 
     
    161165    USE etat0_dcmip5_mod, ONLY : compute_dcmip5 => compute_etat0 
    162166    USE etat0_williamson_mod, ONLY : compute_w91_6 => compute_etat0 
     167    USE etat0_temperature_mod, ONLY: compute_etat0_temperature => compute_etat0 
    163168    IMPLICIT NONE 
    164169    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm) 
     
    186191       CALL compute_etat0_isothermal(iim*jjm, phis, ps, temp_i, ulon_i, ulat_i, q) 
    187192       CALL compute_etat0_isothermal(3*iim*jjm, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
     193    CASE ('temperature_profile') 
     194       CALL compute_etat0_temperature(iim*jjm, phis, ps, temp_i, ulon_i, ulat_i, q) 
     195       CALL compute_etat0_temperature(3*iim*jjm, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    188196    CASE('jablonowsky06') 
    189197       CALL compute_jablonowsky06(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i) 
Note: See TracChangeset for help on using the changeset viewer.