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

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

Add dcmip 5 testcase

YM

File size: 1.7 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_dcmip4_mod, ONLY : etat0_dcmip4=>etat0 
13    USE etat0_dcmip5_mod, ONLY : etat0_dcmip5=>etat0 
14    IMPLICIT NONE
15    TYPE(t_field),POINTER :: f_ps(:)
16    TYPE(t_field),POINTER :: f_phis(:)
17    TYPE(t_field),POINTER :: f_theta_rhodz(:)
18    TYPE(t_field),POINTER :: f_u(:)
19    TYPE(t_field),POINTER :: f_q(:)
20   
21    CHARACTER(len=255) :: etat0_type
22    etat0_type='jablonowsky06'
23    CALL getin("etat0",etat0_type)
24   
25    SELECT CASE (TRIM(etat0_type))
26    CASE ('jablonowsky06')
27       CALL etat0_jablonowsky06(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
28    CASE ('academic')
29       CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
30    CASE ('dcmip1')
31       CALL etat0_dcmip1(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
32    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
33       CALL etat0_dcmip2(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
34    CASE ('dcmip3')
35       CALL etat0_dcmip3(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
36     CASE ('dcmip4')
37       CALL etat0_dcmip4(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
38     CASE ('dcmip5')
39       CALL etat0_dcmip5(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
40   CASE DEFAULT
41       PRINT*, 'Bad selector for variable etat0 <',etat0_type, &
42            '> options are <jablonowsky06>, <academic>, <dcmip[1-4]> '
43       STOP
44    END SELECT
45   
46  END SUBROUTINE etat0
47         
48END MODULE etat0_mod
Note: See TracBrowser for help on using the repository browser.