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

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

Put time variable : dt, itaumax, write_period, itau_out in the time module

YM

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