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

Last change on this file since 61 was 54, checked in by dubos, 12 years ago

Test cases DCMIP2 - no Rayleigh relaxation yet

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