source: codes/icosagcm/trunk/src/physics.f90 @ 156

Last change on this file since 156 was 149, checked in by sdubey, 11 years ago
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 size: 1.9 KB
RevLine 
[81]1MODULE physics_mod
2
3  CHARACTER(LEN=255) :: physics_type="none"
4
5
6CONTAINS
7
[98]8  SUBROUTINE init_physics
[81]9  USE icosa
[149]10  USE physics_dcmip_mod,init_physics_dcmip=>init_physics
11  USE physics_dry_mod
[81]12  IMPLICIT NONE
13   
14    CALL getin("physics",physics_type)
15   
16    SELECT CASE(TRIM(physics_type))
17      CASE ('none')
18   
19      CASE ('dcmip')
[98]20        CALL init_physics_dcmip
[149]21
22      CASE ('lmd')
23        CALL init_physics_dry
[81]24     
25      CASE DEFAULT
[149]26         PRINT*, 'Bad selector for variable physics init <',physics_type, &
[81]27              '> options are <none>, <dcmip>,'
[149]28
[81]29    END SELECT
30   
31  END SUBROUTINE init_physics
32
[149]33  SUBROUTINE physics(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
[81]34  USE icosa
[149]35  USE physics_dry_mod
[81]36  USE physics_dcmip_mod, physics_dcmip=>physics
[149]37  USE etat0_mod
38  USE etat0_heldsz_mod
[81]39  IMPLICIT NONE
[99]40    INTEGER, INTENT(IN)   :: it
[149]41    REAL(rstd),INTENT(IN)::jD_cur,jH_cur
[81]42    TYPE(t_field),POINTER :: f_phis(:)
43    TYPE(t_field),POINTER :: f_ps(:)
44    TYPE(t_field),POINTER :: f_theta_rhodz(:)
45    TYPE(t_field),POINTER :: f_ue(:)
46    TYPE(t_field),POINTER :: f_q(:)
[149]47    LOGICAL:: firstcall,lastcall
[81]48   
49    SELECT CASE(TRIM(physics_type))
50      CASE ('none')
[149]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
[81]61   
62      CASE ('dcmip')
[99]63        CALL physics_dcmip(it, f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
[149]64
65      CASE ('dry')
66        CALL physics_dry(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
[81]67     
68      CASE DEFAULT
69         PRINT*, 'Bad selector for variable physics <',physics_type, &
70              '> options are <none>, <dcmip>,'
[149]71  STOP
[81]72    END SELECT
73   
74  END SUBROUTINE physics
75
76END MODULE physics_mod
Note: See TracBrowser for help on using the repository browser.