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

Last change on this file since 98 was 98, checked in by ymipsl, 12 years ago

Put time variable : dt, itaumax, write_period, itau_out in the time module

YM

File size: 1.2 KB
Line 
1MODULE physics_mod
2
3  CHARACTER(LEN=255) :: physics_type="none"
4
5
6CONTAINS
7
8  SUBROUTINE init_physics
9  USE icosa
10  USE physics_dcmip_mod, init_physics_dcmip=>init_physics
11  IMPLICIT NONE
12   
13    CALL getin("physics",physics_type)
14   
15    SELECT CASE(TRIM(physics_type))
16      CASE ('none')
17   
18      CASE ('dcmip')
19        CALL init_physics_dcmip
20     
21      CASE DEFAULT
22         PRINT*, 'Bad selector for variable physics <',physics_type, &
23              '> options are <none>, <dcmip>,'
24         STOP
25    END SELECT
26   
27  END SUBROUTINE init_physics
28
29  SUBROUTINE physics(f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
30  USE icosa
31  USE physics_dcmip_mod, physics_dcmip=>physics
32  IMPLICIT NONE
33    TYPE(t_field),POINTER :: f_phis(:)
34    TYPE(t_field),POINTER :: f_ps(:)
35    TYPE(t_field),POINTER :: f_theta_rhodz(:)
36    TYPE(t_field),POINTER :: f_ue(:)
37    TYPE(t_field),POINTER :: f_q(:)
38   
39    SELECT CASE(TRIM(physics_type))
40      CASE ('none')
41   
42      CASE ('dcmip')
43        CALL physics_dcmip(f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
44     
45      CASE DEFAULT
46         PRINT*, 'Bad selector for variable physics <',physics_type, &
47              '> options are <none>, <dcmip>,'
48         STOP
49    END SELECT
50   
51  END SUBROUTINE physics
52
53END MODULE physics_mod
Note: See TracBrowser for help on using the repository browser.