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

    r99 r149  
    88  SUBROUTINE init_physics 
    99  USE icosa 
    10   USE physics_dcmip_mod, init_physics_dcmip=>init_physics 
     10  USE physics_dcmip_mod,init_physics_dcmip=>init_physics 
     11  USE physics_dry_mod 
    1112  IMPLICIT NONE 
    1213     
     
    1819      CASE ('dcmip') 
    1920        CALL init_physics_dcmip 
     21 
     22      CASE ('lmd') 
     23        CALL init_physics_dry 
    2024       
    2125      CASE DEFAULT 
    22          PRINT*, 'Bad selector for variable physics <',physics_type, & 
     26         PRINT*, 'Bad selector for variable physics init <',physics_type, & 
    2327              '> options are <none>, <dcmip>,' 
    24          STOP 
     28 
    2529    END SELECT 
    2630     
    2731  END SUBROUTINE init_physics 
    2832 
    29   SUBROUTINE physics(it,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
     33  SUBROUTINE physics(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
    3034  USE icosa 
     35  USE physics_dry_mod 
    3136  USE physics_dcmip_mod, physics_dcmip=>physics 
     37  USE etat0_mod 
     38  USE etat0_heldsz_mod 
    3239  IMPLICIT NONE 
    3340    INTEGER, INTENT(IN)   :: it 
     41    REAL(rstd),INTENT(IN)::jD_cur,jH_cur 
    3442    TYPE(t_field),POINTER :: f_phis(:) 
    3543    TYPE(t_field),POINTER :: f_ps(:) 
     
    3745    TYPE(t_field),POINTER :: f_ue(:) 
    3846    TYPE(t_field),POINTER :: f_q(:) 
     47    LOGICAL:: firstcall,lastcall 
    3948     
    4049    SELECT CASE(TRIM(physics_type)) 
    4150      CASE ('none') 
     51 
     52        SELECT CASE(TRIM(etat0_type)) 
     53        CASE('heldsz')  
     54!       CALL transfert_request(f_ps,req_i1) 
     55!       CALL transfert_request(f_theta_rhodz,req_i1) 
     56!       CALL transfert_request(f_ue,req_e1_vect) 
     57!       CALL held_saurez(f_ps,f_theta_rhodz,f_ue)  
     58        CASE DEFAULT 
     59        PRINT*,"NO PHYSICAL PACAKAGE USED"  
     60        END SELECT 
    4261     
    4362      CASE ('dcmip') 
    4463        CALL physics_dcmip(it, f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
     64 
     65      CASE ('dry') 
     66        CALL physics_dry(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
    4567       
    4668      CASE DEFAULT 
    4769         PRINT*, 'Bad selector for variable physics <',physics_type, & 
    4870              '> options are <none>, <dcmip>,' 
    49          STOP 
     71  STOP 
    5072    END SELECT 
    5173     
Note: See TracChangeset for help on using the changeset viewer.