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

Last change on this file since 181 was 178, checked in by mtort, 11 years ago

Fixed no-physics message

File size: 2.2 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
[178]9    USE mpipara
10    USE etat0_mod
[170]11    USE icosa
12    USE physics_dcmip_mod,init_physics_dcmip=>init_physics
13    USE physics_dry_mod
14    IMPLICIT NONE
15
[178]16    physics_type='automatic'
[81]17    CALL getin("physics",physics_type)
[170]18
[81]19    SELECT CASE(TRIM(physics_type))
[170]20    CASE ('automatic')
[178]21       etat0_type='jablonowsky06'
22       CALL getin("etat0",etat0_type)
23       SELECT CASE(TRIM(etat0_type))
24       CASE('held_suarez')
25       CASE DEFAULT
26          IF(is_mpi_root) PRINT*,"NO PHYSICAL PACKAGE USED"
27       END SELECT
[149]28
[178]29
[170]30    CASE ('dcmip')
31       CALL init_physics_dcmip
[149]32
[170]33    CASE ('dry')
34       CALL init_physics_dry
35
36    CASE DEFAULT
37       PRINT*, 'init_physics : Bad selector for variable physics <',TRIM(physics_type), &
38            '> options are <automatic>, <dcmip>, <dry>'
39       STOP
[81]40    END SELECT
[170]41
[81]42  END SUBROUTINE init_physics
43
[149]44  SUBROUTINE physics(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
[170]45    USE icosa
46    USE physics_dry_mod
47    USE physics_dcmip_mod, physics_dcmip=>physics
48    USE etat0_mod
49    USE etat0_heldsz_mod
50    IMPLICIT NONE
[99]51    INTEGER, INTENT(IN)   :: it
[149]52    REAL(rstd),INTENT(IN)::jD_cur,jH_cur
[81]53    TYPE(t_field),POINTER :: f_phis(:)
54    TYPE(t_field),POINTER :: f_ps(:)
55    TYPE(t_field),POINTER :: f_theta_rhodz(:)
56    TYPE(t_field),POINTER :: f_ue(:)
57    TYPE(t_field),POINTER :: f_q(:)
[149]58    LOGICAL:: firstcall,lastcall
[170]59
[81]60    SELECT CASE(TRIM(physics_type))
[170]61    CASE ('automatic')
[149]62
[170]63       SELECT CASE(TRIM(etat0_type))
64       CASE('held_suarez')
65          !     CALL transfert_request(f_ps,req_i1)
66          !     CALL transfert_request(f_theta_rhodz,req_i1)
67          !     CALL transfert_request(f_ue,req_e1_vect)
68          CALL held_suarez(f_ps,f_theta_rhodz,f_ue) 
69       END SELECT
[149]70
[170]71    CASE ('dcmip')
72       CALL physics_dcmip(it, f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
73
74    CASE ('dry')
75       CALL physics_dry(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q)
76
77    CASE DEFAULT
78       PRINT*, 'Bad selector for variable physics <',TRIM(physics_type), &
79            '> options are <automatic>, <dcmip>, <dry>'
80       STOP
[81]81    END SELECT
[170]82
[81]83  END SUBROUTINE physics
84
85END MODULE physics_mod
Note: See TracBrowser for help on using the repository browser.