source: codes/icosagcm/devel/src/dissip/guided_mod.f90 @ 533

Last change on this file since 533 was 533, checked in by dubos, 7 years ago

devel : reorganization of source tree

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