source: codes/icosagcm/trunk/src/etat0.f90 @ 67

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

bug fix for dcmip4.1 testcase

YM

File size: 1.6 KB
Line 
1MODULE etat0_mod
2
3CONTAINS
4 
5  SUBROUTINE etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
6    USE icosa
7    USE etat0_jablonowsky06_mod, ONLY : etat0_jablonowsky06=>etat0
8    USE etat0_academic_mod, ONLY : etat0_academic=>etat0 
9    USE etat0_dcmip1_mod, ONLY : etat0_dcmip1=>etat0
10    USE etat0_dcmip2_mod, ONLY : etat0_dcmip2=>etat0
11    USE etat0_dcmip3_mod, ONLY : etat0_dcmip3=>etat0 
12    USE etat0_dcmip41_mod, ONLY : etat0_dcmip41=>etat0 
13    IMPLICIT NONE
14    TYPE(t_field),POINTER :: f_ps(:)
15    TYPE(t_field),POINTER :: f_phis(:)
16    TYPE(t_field),POINTER :: f_theta_rhodz(:)
17    TYPE(t_field),POINTER :: f_u(:)
18    TYPE(t_field),POINTER :: f_q(:)
19   
20    CHARACTER(len=255) :: etat0_type
21    etat0_type='jablonowsky06'
22    CALL getin("etat0",etat0_type)
23   
24    SELECT CASE (TRIM(etat0_type))
25    CASE ('jablonowsky06')
26       CALL etat0_jablonowsky06(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
27    CASE ('academic')
28       CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
29    CASE ('dcmip1')
30       CALL etat0_dcmip1(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
31    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
32       CALL etat0_dcmip2(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
33    CASE ('dcmip3')
34       CALL etat0_dcmip3(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
35     CASE ('dcmip41')
36       CALL etat0_dcmip41(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
37   CASE DEFAULT
38       PRINT*, 'Bad selector for variable etat0 <',etat0_type, &
39            '> options are <jablonowsky06>, <academic>, <dcmip[1-4]> '
40       STOP
41    END SELECT
42   
43  END SUBROUTINE etat0
44         
45END MODULE etat0_mod
Note: See TracBrowser for help on using the repository browser.