source: codes/icosagcm/trunk/src/guided_mod.f90 @ 20

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

Simplify the management of the module.

YM

File size: 1.2 KB
Line 
1MODULE guided_mod
2
3  CHARACTER(LEN=255),SAVE :: guided_type
4
5CONTAINS
6
7
8  SUBROUTINE init_guided(dt)
9  USE icosa
10  USE guided_ncar_mod, ONLY : init_guided_ncar => init_guided
11  IMPLICIT NONE
12    REAL(rstd),INTENT(IN) :: dt
13   
14    guided_type='none'
15    CALL getin("guided_type",guided_type)
16   
17    SELECT CASE(TRIM(guided_type))
18      CASE ('none')
19     
20      CASE ('ncar')
21        CALL init_guided_ncar(dt)
22       
23      CASE DEFAULT
24       
25         PRINT*,"Bad selector for varaible guided_type >",TRIM(guided_type),"> option are <none>, <ncar>"
26         STOP
27    END SELECT
28   
29  END SUBROUTINE init_guided
30
31 
32  SUBROUTINE guided(it, f_ps, f_theta_rhodz, f_u, f_q)
33  USE icosa
34  USE guided_ncar_mod, ONLY : guided_ncar => guided
35  IMPLICIT NONE
36    INTEGER, INTENT(IN)   :: it
37    TYPE(t_field),POINTER :: f_ps(:)
38    TYPE(t_field),POINTER :: f_phis(:)
39    TYPE(t_field),POINTER :: f_theta_rhodz(:)
40    TYPE(t_field),POINTER :: f_u(:) 
41    TYPE(t_field),POINTER :: f_q(:) 
42
43    SELECT CASE(TRIM(guided_type))
44      CASE ('none')
45     
46      CASE ('ncar')
47        CALL guided_ncar(it, f_ps, f_theta_rhodz, f_u, f_q)
48    END SELECT
49 
50  END SUBROUTINE guided
51 
52END MODULE guided_mod
53 
Note: See TracBrowser for help on using the repository browser.