Ignore:
Timestamp:
04/03/13 12:05:12 (11 years ago)
Author:
sdubey
Message:
Added few new routines to read NC files and compute diagnostics to r145.
Few routines of dry physics including radiation module, surface process and convective adjustment in new routine phyparam.f90. dynetat to read start files for dynamics. check_conserve routine to compute conservation of quatities like mass, energy etc.etat0_heldsz.f90 for held-suarez test case initial conditions. new Key time_style=lmd or dcmip to use day_step, ndays like in LMDZ
File:
1 edited

Legend:

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

    r113 r149  
    11MODULE etat0_mod 
     2    CHARACTER(len=255),SAVE :: etat0_type 
    23 
    34CONTAINS 
     
    1213    USE etat0_dcmip4_mod, ONLY : etat0_dcmip4=>etat0   
    1314    USE etat0_dcmip5_mod, ONLY : etat0_dcmip5=>etat0   
     15    USE etat0_heldsz_mod, ONLY : etat0_heldsz=>etat0   
     16    USE dynetat0_gcm_mod, ONLY : dynetat0_start=>etat0  
     17    USE dynetat0_hz_mod,  ONLY : dynetat0_hz=>etat0  
     18 
    1419    IMPLICIT NONE 
    1520    TYPE(t_field),POINTER :: f_ps(:) 
     
    1924    TYPE(t_field),POINTER :: f_q(:) 
    2025     
    21     CHARACTER(len=255) :: etat0_type 
    2226    etat0_type='jablonowsky06' 
    2327    CALL getin("etat0",etat0_type) 
     
    2832    CASE ('academic') 
    2933       CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
     34    CASE ('heldsz') 
     35        print*,"heldsz test case" 
     36       CALL etat0_heldsz(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
    3037    CASE ('dcmip1') 
    3138       CALL etat0_dcmip1(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
     
    3845     CASE ('dcmip5') 
    3946       CALL etat0_dcmip5(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
     47     CASE ('readnf_start')  
     48          print*,"readnf_start used"     
     49       CALL dynetat0_start(f_ps,f_phis,f_theta_rhodz,f_u,f_q)  
     50        CASE ('readnf_hz')  
     51          print*,"readnf_hz used" 
     52       CALL dynetat0_hz(f_ps,f_phis,f_theta_rhodz,f_u,f_q)  
    4053   CASE DEFAULT 
    4154       PRINT*, 'Bad selector for variable etat0 <',etat0_type, & 
Note: See TracChangeset for help on using the changeset viewer.