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

Last change on this file since 187 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: 3.3 KB
RevLine 
[12]1MODULE etat0_mod
[149]2    CHARACTER(len=255),SAVE :: etat0_type
[186]3!$OMP THREADPRIVATE(etat0_type)
[12]4
[17]5CONTAINS
6 
[159]7  SUBROUTINE etat0(f_ps,f_mass,f_phis,f_theta_rhodz,f_u, f_q)
[54]8    USE icosa
[159]9    USE disvert_mod
[164]10    USE etat0_williamson_mod, ONLY : etat0_williamson_new
[54]11    USE etat0_jablonowsky06_mod, ONLY : etat0_jablonowsky06=>etat0
12    USE etat0_academic_mod, ONLY : etat0_academic=>etat0 
13    USE etat0_dcmip1_mod, ONLY : etat0_dcmip1=>etat0
14    USE etat0_dcmip2_mod, ONLY : etat0_dcmip2=>etat0
15    USE etat0_dcmip3_mod, ONLY : etat0_dcmip3=>etat0 
[78]16    USE etat0_dcmip4_mod, ONLY : etat0_dcmip4=>etat0 
[113]17    USE etat0_dcmip5_mod, ONLY : etat0_dcmip5=>etat0 
[149]18    USE etat0_heldsz_mod, ONLY : etat0_heldsz=>etat0 
19    USE dynetat0_gcm_mod, ONLY : dynetat0_start=>etat0 
20    USE dynetat0_hz_mod,  ONLY : dynetat0_hz=>etat0 
21
[54]22    IMPLICIT NONE
[17]23    TYPE(t_field),POINTER :: f_ps(:)
[159]24    TYPE(t_field),POINTER :: f_mass(:)
[17]25    TYPE(t_field),POINTER :: f_phis(:)
26    TYPE(t_field),POINTER :: f_theta_rhodz(:)
27    TYPE(t_field),POINTER :: f_u(:)
28    TYPE(t_field),POINTER :: f_q(:)
[186]29   
[159]30    REAL(rstd),POINTER :: ps(:), mass(:,:)
31    LOGICAL :: init_mass
32    INTEGER :: ind,i,j,ij,l
33
34    ! most etat0 routines set ps and not mass
35    ! in that case and if caldyn_eta == eta_lag
36    ! the initial distribution of mass is taken to be the same
37    ! as what the mass coordinate would dictate
38    ! however if etat0_XXX defines mass then the flag init_mass must be set to .FALSE.
39    ! otherwise mass will be overwritten
40    init_mass = (caldyn_eta == eta_lag)
41
[17]42    etat0_type='jablonowsky06'
43    CALL getin("etat0",etat0_type)
44   
45    SELECT CASE (TRIM(etat0_type))
[168]46    CASE ('williamson91.6')
[164]47       CALL etat0_williamson_new(f_phis,f_mass,f_theta_rhodz,f_u, f_q)
48       init_mass=.FALSE.
[54]49    CASE ('jablonowsky06')
50       CALL etat0_jablonowsky06(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
51    CASE ('academic')
52       CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[170]53    CASE ('held_suarez')
54       PRINT *,"Held & Suarez (1994) test case"
[149]55       CALL etat0_heldsz(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[54]56    CASE ('dcmip1')
57       CALL etat0_dcmip1(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
58    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
59       CALL etat0_dcmip2(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
60    CASE ('dcmip3')
61       CALL etat0_dcmip3(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[78]62     CASE ('dcmip4')
63       CALL etat0_dcmip4(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[113]64     CASE ('dcmip5')
65       CALL etat0_dcmip5(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
[149]66     CASE ('readnf_start') 
67          print*,"readnf_start used"   
68       CALL dynetat0_start(f_ps,f_phis,f_theta_rhodz,f_u,f_q) 
69        CASE ('readnf_hz') 
70          print*,"readnf_hz used"
71       CALL dynetat0_hz(f_ps,f_phis,f_theta_rhodz,f_u,f_q) 
[62]72   CASE DEFAULT
[54]73       PRINT*, 'Bad selector for variable etat0 <',etat0_type, &
[67]74            '> options are <jablonowsky06>, <academic>, <dcmip[1-4]> '
[54]75       STOP
76    END SELECT
[159]77
78    IF(init_mass) THEN ! initialize mass distribution using ps
[186]79!       !$OMP BARRIER
[159]80       DO ind=1,ndomain
[186]81          IF (.NOT. assigned_domain(ind)) CYCLE
[159]82          CALL swap_dimensions(ind)
83          CALL swap_geometry(ind)
84          mass=f_mass(ind); ps=f_ps(ind)
85          CALL compute_rhodz(.TRUE., ps, mass)
86       END DO
87    END IF
88
[54]89  END SUBROUTINE etat0
[17]90         
[12]91END MODULE etat0_mod
[159]92
Note: See TracBrowser for help on using the repository browser.