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

Last change on this file since 519 was 186, checked in by ymipsl, 10 years ago

Add new openMP parallelism based on distribution of domains on threads. There is no more limitation of number of threads by MPI process.

YM

File size: 1.3 KB
Line 
1MODULE guided_mod
2
3  CHARACTER(LEN=255),SAVE :: guided_type
4!$OMP THREADPRIVATE(guided_type)
5
6CONTAINS
7
8
9  SUBROUTINE init_guided
10  USE icosa
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     
20      CASE ('dcmip1')
21        CALL init_guided_ncar
22       
23      CASE DEFAULT
24         PRINT*,"Bad selector for varaible guided_type >",TRIM(guided_type),"> option are <none>, <dcmip1>"
25         STOP
26    END SELECT
27   
28  END SUBROUTINE init_guided
29
30 
31  SUBROUTINE guided(tt, f_ps, f_theta_rhodz, f_u, f_q)
32  USE icosa
33  USE guided_ncar_mod, ONLY : guided_ncar => guided
34  IMPLICIT NONE
35    REAL(rstd), INTENT(IN):: tt
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')
44      CASE ('dcmip1')
45        CALL guided_ncar(tt, f_ps, f_theta_rhodz, f_u, f_q)
46      CASE DEFAULT
47         PRINT*,"Bad selector for varaible guided_type >",TRIM(guided_type),"> option are <none>, <dcmip1>"
48         STOP
49    END SELECT
50 
51  END SUBROUTINE guided
52 
53END MODULE guided_mod
54 
Note: See TracBrowser for help on using the repository browser.