source: codes/icosagcm/trunk/src/etat0_dcmip2.f90 @ 186

Last change on this file since 186 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: 4.2 KB
Line 
1MODULE etat0_dcmip2_mod
2
3! test cases DCMIP 2012, category 2 : Orographic gravity waves
4
5  USE genmod
6
7  PRIVATE
8
9  PUBLIC  etat0
10
11CONTAINS
12
13
14  SUBROUTINE etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
15  USE icosa
16  IMPLICIT NONE
17    TYPE(t_field),POINTER :: f_ps(:)
18    TYPE(t_field),POINTER :: f_phis(:)
19    TYPE(t_field),POINTER :: f_theta_rhodz(:)
20    TYPE(t_field),POINTER :: f_u(:)
21    TYPE(t_field),POINTER :: f_q(:)
22   
23    REAL(rstd),POINTER :: ps(:)
24    REAL(rstd),POINTER :: phis(:)
25    REAL(rstd),POINTER :: u(:,:)
26    REAL(rstd),POINTER :: theta_rhodz(:,:)
27    REAL(rstd),POINTER :: q(:,:,:)
28
29    INTEGER :: ind, icase
30    CHARACTER(len=255) :: etat0_type
31    etat0_type='jablonowsky06'
32    CALL getin("etat0",etat0_type)
33
34    SELECT CASE (TRIM(etat0_type))
35    CASE('dcmip2_mountain')
36       icase=0
37    CASE('dcmip2_schaer_noshear')
38       icase=1
39    CASE('dcmip2_schaer_shear')
40       icase=2
41    CASE DEFAULT
42       PRINT *, 'This should not happen : etat0_type =', TRIM(etat0_type), ' in etat0_dcmip2.f90/etat0'
43       STOP
44    END SELECT
45    PRINT *, 'Orographic gravity-wave test case :', TRIM(etat0_type)
46
47    DO ind=1,ndomain
48      IF (.NOT. assigned_domain(ind)) CYCLE
49      CALL swap_dimensions(ind)
50      CALL swap_geometry(ind)
51
52      ps=f_ps(ind)
53      phis=f_phis(ind)
54      u=f_u(ind)
55      theta_rhodz=f_theta_rhodz(ind)
56      q=f_q(ind)
57      CALL compute_etat0_DCMIP2(icase,ps,phis,u,theta_rhodz,q)
58    ENDDO
59           
60  END SUBROUTINE etat0
61 
62  SUBROUTINE compute_etat0_DCMIP2(icase, ps, phis, u, theta_rhodz,q)
63    USE icosa
64    USE disvert_mod, ONLY : ap,bp
65    USE pression_mod
66    USE theta2theta_rhodz_mod
67    USE wind_mod
68    IMPLICIT NONE
69    INTEGER, INTENT(IN) :: icase
70    REAL(rstd), INTENT(OUT) :: ps(iim*jjm)
71    REAL(rstd), INTENT(OUT) :: phis(iim*jjm)
72    REAL(rstd), INTENT(OUT) :: u(3*iim*jjm,llm)
73    REAL(rstd), INTENT(OUT) :: theta_rhodz(iim*jjm,llm)
74    REAL(rstd), INTENT(OUT) :: q(iim*jjm,llm)
75    REAL(rstd) :: ulon(3*iim*jjm,llm), ulat(3*iim*jjm,llm), temp(iim*jjm,llm)
76   
77    INTEGER :: i,j,l,ij
78    REAL(rstd) :: hyam, hybm, pp, dummy1, dummy2, dummy3 
79   
80    ! Hexagons : ps,phis,temp
81    DO l=1,llm
82       ! The surface pressure is not set yet so we provide the hybrid coefficients
83       hyam = .5*(ap(l)+ap(l+1))/preff
84       hybm = .5*(bp(l)+bp(l+1))
85       DO j=jj_begin,jj_end
86          DO i=ii_begin,ii_end
87             ij=(j-1)*iim+i
88             CALL comp_all(xyz_i(ij,:), ps(ij),phis(ij),temp(ij,l), dummy1,dummy2)
89          END DO
90       END DO
91    END DO
92    CALL compute_temperature2theta_rhodz(ps,temp,theta_rhodz,1)
93   
94    ! Edges : ulon,ulat
95    DO l=1,llm
96       ! The surface pressure is not set yet so we provide the hybrid coefficients
97       hyam = .5*(ap(l)+ap(l+1))/preff
98       hybm = .5*(bp(l)+bp(l+1))
99       DO j=jj_begin,jj_end
100          DO i=ii_begin,ii_end
101             ij=(j-1)*iim+i
102             CALL comp_all(xyz_e(ij+u_right,:), dummy1,dummy2,dummy3, ulon(ij+u_right,l),ulat(ij+u_right,l))
103             CALL comp_all(xyz_e(ij+u_lup,:), dummy1,dummy2,dummy3, ulon(ij+u_lup,l),ulat(ij+u_lup,l))
104             CALL comp_all(xyz_e(ij+u_ldown,:), dummy1,dummy2,dummy3, ulon(ij+u_ldown,l),ulat(ij+u_ldown,l))
105          END DO
106       END DO
107    END DO
108    CALL compute_wind_perp_from_lonlat_compound(ulon,ulat,u)
109
110    q=1.
111
112    CONTAINS
113     
114      SUBROUTINE comp_all(xyz, psj,phisj,tempj, ulonj,ulatj)
115        USE dcmip_initial_conditions_test_1_2_3
116        REAL(rstd), INTENT(IN) :: xyz(3)
117        REAL(rstd), INTENT(OUT) :: psj,phisj,tempj,ulonj,ulatj
118        REAL :: lon,lat, dummy
119        dummy=0.
120        CALL xyz2lonlat(xyz,lon,lat)
121        SELECT CASE (icase)
122        CASE(0)
123           CALL test2_steady_state_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm, &
124                ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy)
125        CASE(1)
126           CALL test2_schaer_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm,0,&
127                ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy)
128        CASE(2)
129           CALL test2_schaer_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm,1, &
130                ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy)
131        END SELECT
132      END SUBROUTINE comp_all
133
134  END SUBROUTINE compute_etat0_DCMIP2
135
136
137END MODULE etat0_dcmip2_mod
Note: See TracBrowser for help on using the repository browser.