Ignore:
Timestamp:
07/09/14 00:58:30 (10 years ago)
Author:
dubos
Message:

Upgraded JW06 and DCMIP5 to new etat0 interface (tested)

File:
1 edited

Legend:

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

    r201 r203  
    1515    USE mpipara, ONLY : is_mpi_root 
    1616    USE disvert_mod 
     17    ! New interface 
     18    USE etat0_dcmip5_mod, ONLY : getin_etat0_dcmip5=>getin_etat0 
     19    ! Old interface 
    1720    USE etat0_williamson_mod, ONLY : etat0_williamson_new 
    18     USE etat0_jablonowsky06_mod, ONLY : etat0_jablonowsky06=>etat0 
    1921    USE etat0_academic_mod, ONLY : etat0_academic=>etat0   
    2022    USE etat0_dcmip1_mod, ONLY : etat0_dcmip1=>etat0 
     
    2224    USE etat0_dcmip3_mod, ONLY : etat0_dcmip3=>etat0   
    2325    USE etat0_dcmip4_mod, ONLY : etat0_dcmip4=>etat0   
    24     USE etat0_dcmip5_mod, ONLY : etat0_dcmip5=>etat0   
    2526    USE etat0_heldsz_mod, ONLY : etat0_heldsz=>etat0   
    2627    USE dynetat0_gcm_mod, ONLY : dynetat0_start=>etat0  
     
    5152     
    5253    SELECT CASE (TRIM(etat0_type)) 
     54       !------------------- New interface --------------------- 
    5355    CASE ('isothermal') 
    5456       CALL getin_etat0_isothermal 
    5557       CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) 
     58    CASE ('jablonowsky06') 
     59       CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) 
     60     CASE ('dcmip5') 
     61        CALL getin_etat0_dcmip5 
     62        CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) 
     63         
     64        !------------------- Old interface -------------------- 
    5665    CASE ('williamson91.6') 
    5766       init_mass=.FALSE. 
    5867       CALL etat0_williamson_new(f_phis,f_mass,f_theta_rhodz,f_u, f_q) 
    59     CASE ('jablonowsky06') 
    60 !       CALL etat0_jablonowsky06(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
    61        CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) 
    6268    CASE ('academic') 
    6369       CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
     
    7985        END IF 
    8086       CALL etat0_dcmip4(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
    81      CASE ('dcmip5') 
    82        CALL etat0_dcmip5(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
    8387     CASE ('readnf_start')  
    8488          print*,"readnf_start used"     
     
    135139      q=f_q(ind) 
    136140      CALL compute_etat0_collocated(ps,mass, phis, theta_rhodz, u, q) 
    137  
    138141    ENDDO 
    139142  END SUBROUTINE etat0_collocated 
     
    143146    USE theta2theta_rhodz_mod 
    144147    USE wind_mod 
    145     USE etat0_jablonowsky06_mod, ONLY : compute_jablonowsky06 => compute_etat0_new 
     148    USE etat0_jablonowsky06_mod, ONLY : compute_jablonowsky06 => compute_etat0 
     149    USE etat0_dcmip5_mod, ONLY : compute_dcmip5 => compute_etat0 
    146150    IMPLICIT NONE 
    147151    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm) 
     
    189193       CALL compute_jablonowsky06(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i) 
    190194       CALL compute_jablonowsky06(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e) 
     195    CASE('dcmip5') 
     196       CALL compute_dcmip5(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q) 
     197       CALL compute_dcmip5(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    191198    END SELECT 
    192199 
Note: See TracChangeset for help on using the changeset viewer.