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

Last change on this file since 171 was 170, checked in by dubos, 11 years ago

Activated call to physics - Held & Suarez test case seems to work now

File size: 2.0 KB
RevLine 
[81]1MODULE physics_mod
2
[170]3  CHARACTER(LEN=255) :: physics_type="automatic"
[81]4
5
6CONTAINS
7
[98]8  SUBROUTINE init_physics
[170]9    USE icosa
10    USE physics_dcmip_mod,init_physics_dcmip=>init_physics
11    USE physics_dry_mod
12    IMPLICIT NONE
13
[81]14    CALL getin("physics",physics_type)
[170]15
[81]16    SELECT CASE(TRIM(physics_type))
[170]17    CASE ('automatic')
[149]18
[170]19    CASE ('dcmip')
20       CALL init_physics_dcmip
[149]21
[170]22    CASE ('dry')
23       CALL init_physics_dry
24
25    CASE DEFAULT
26       PRINT*, 'init_physics : Bad selector for variable physics <',TRIM(physics_type), &
27            '> options are <automatic>, <dcmip>, <dry>'
28       STOP
[81]29    END SELECT
[170]30
[81]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)
[170]34    USE icosa
35    USE physics_dry_mod
36    USE physics_dcmip_mod, physics_dcmip=>physics
37    USE etat0_mod
38    USE etat0_heldsz_mod
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
[170]48
[81]49    SELECT CASE(TRIM(physics_type))
[170]50    CASE ('automatic')
[149]51
[170]52       SELECT CASE(TRIM(etat0_type))
53       CASE('held_suarez')
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_suarez(f_ps,f_theta_rhodz,f_ue) 
58       CASE DEFAULT
59          PRINT*,"NO PHYSICAL PACAKAGE USED" ! FIXME MPI
60       END SELECT
[149]61
[170]62    CASE ('dcmip')
63       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)
67
68    CASE DEFAULT
69       PRINT*, 'Bad selector for variable physics <',TRIM(physics_type), &
70            '> options are <automatic>, <dcmip>, <dry>'
71       STOP
[81]72    END SELECT
[170]73
[81]74  END SUBROUTINE physics
75
76END MODULE physics_mod
Note: See TracBrowser for help on using the repository browser.