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/physics.f90

    r325 r327  
    55  PRIVATE 
    66 
    7   INTEGER, PARAMETER :: phys_none=0, phys_HS94=1, phys_DCMIP=2, phys_LB2012=3 
     7  INTEGER, PARAMETER :: phys_none=0, phys_HS94=1, phys_DCMIP=2, phys_lmdz_generic=3, phys_LB2012=4  
    88 
    99  INTEGER :: phys_type 
     
    2626    USE physics_dcmip_mod, ONLY : init_physics_dcmip=>init_physics 
    2727    USE etat0_venus_mod, ONLY : init_phys_venus=>init_physics 
     28    USE physics_lmdz_generic_mod, ONLY : init_physics_lmdz_generic=>init_physics 
    2829    IMPLICIT NONE 
    2930 
     
    4041       phys_type = phys_LB2012 
    4142       CALL init_phys_venus 
     43 
     44    CASE ('phys_lmdz_generic') 
     45       CALL init_physics_lmdz_generic 
     46       phys_type=phys_lmdz_generic 
    4247    CASE ('dcmip') 
    4348       CALL allocate_field(f_dulon,field_t,type_real,llm, name='dulon') 
     
    5055    CASE DEFAULT 
    5156       IF(is_mpi_root) PRINT*, 'init_physics : Bad selector for variable physics <',& 
    52             TRIM(physics_type), '> options are <none>, <held_suarez>, <Lebonnois2012>, <dcmip>' 
     57            TRIM(physics_type), '> options are <none>, <held_suarez>, <Lebonnois2012>, <dcmip>, <phys_lmdz_generic>' 
    5358       STOP 
    5459    END SELECT 
     
    5762  END SUBROUTINE init_physics 
    5863 
    59   SUBROUTINE physics(it,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
    60     USE icosa 
    61     USE physics_interface_mod 
     64  SUBROUTINE physics(it,f_phis, f_ps, f_theta_rhodz, f_ue, f_wflux, f_q) 
     65    USE icosa 
     66    USE physics_interface_mod 
     67    USE physics_lmdz_generic_mod, ONLY : physics_lmdz_generic => physics 
    6268    USE physics_dcmip_mod, ONLY : write_physics_dcmip => write_physics 
    6369    USE etat0_heldsz_mod 
     
    6975    TYPE(t_field),POINTER :: f_theta_rhodz(:) 
    7076    TYPE(t_field),POINTER :: f_ue(:) 
     77    TYPE(t_field),POINTER :: f_wflux(:) 
    7178    TYPE(t_field),POINTER :: f_q(:) 
    7279    REAL(rstd),POINTER :: phis(:) 
     
    8794       CASE(phys_HS94) 
    8895          CALL held_suarez(f_ps,f_theta_rhodz,f_ue)  
     96       CASE (phys_lmdz_generic) 
     97         CALL physics_lmdz_generic(it ,f_phis, f_ps, f_theta_rhodz, f_ue, f_wflux, f_q) 
    8998       CASE(phys_LB2012) 
    9099          CALL phys_venus(f_ps,f_theta_rhodz,f_ue)  
Note: See TracChangeset for help on using the changeset viewer.