source: codes/icosagcm/trunk/src/theta_rhodz.f90 @ 78

Last change on this file since 78 was 35, checked in by ymipsl, 12 years ago

add compute_temperature2theta_rhodz functionnlity

YM

File size: 5.3 KB
Line 
1MODULE theta2theta_rhodz_mod
2
3CONTAINS
4 
5  SUBROUTINE theta_rhodz2theta(f_ps,f_theta_rhodz,f_theta)
6  USE icosa
7  IMPLICIT NONE
8    TYPE(t_field), POINTER :: f_ps(:)
9    TYPE(t_field), POINTER :: f_theta_rhodz(:)
10    TYPE(t_field), POINTER :: f_theta(:)
11 
12    REAL(rstd), POINTER :: ps(:)
13    REAL(rstd), POINTER :: theta_rhodz(:,:)
14    REAL(rstd), POINTER :: theta(:,:)
15    INTEGER :: ind
16
17    DO ind=1,ndomain
18      CALL swap_dimensions(ind)
19      CALL swap_geometry(ind)
20      ps=f_ps(ind)
21      theta_rhodz=f_theta_rhodz(ind)
22      theta=f_theta(ind)
23      CALL compute_theta_rhodz2theta(ps, theta_rhodz,theta,0)
24    ENDDO
25 
26  END SUBROUTINE theta_rhodz2theta
27
28  SUBROUTINE theta_rhodz2temperature(f_ps,f_theta_rhodz,f_temp)
29  USE icosa
30  IMPLICIT NONE
31    TYPE(t_field), POINTER :: f_ps(:)
32    TYPE(t_field), POINTER :: f_theta_rhodz(:)
33    TYPE(t_field), POINTER :: f_temp(:)
34 
35    REAL(rstd), POINTER :: ps(:)
36    REAL(rstd), POINTER :: theta_rhodz(:,:)
37    REAL(rstd), POINTER :: temp(:,:)
38    INTEGER :: ind
39
40    DO ind=1,ndomain
41      CALL swap_dimensions(ind)
42      CALL swap_geometry(ind)
43      ps=f_ps(ind)
44      theta_rhodz=f_theta_rhodz(ind)
45      temp=f_temp(ind)
46      CALL compute_theta_rhodz2temperature(ps, theta_rhodz,temp,0)
47    ENDDO
48 
49  END SUBROUTINE theta_rhodz2temperature
50   
51  SUBROUTINE theta2theta_rhodz(f_ps,f_theta,f_theta_rhodz)
52  USE icosa
53  IMPLICIT NONE
54    TYPE(t_field), POINTER :: f_ps(:)
55    TYPE(t_field), POINTER :: f_theta(:)
56    TYPE(t_field), POINTER :: f_theta_rhodz(:)
57 
58    REAL(rstd), POINTER :: ps(:)
59    REAL(rstd), POINTER :: theta(:,:)
60    REAL(rstd), POINTER :: theta_rhodz(:,:)
61    INTEGER :: ind
62
63    DO ind=1,ndomain
64      CALL swap_dimensions(ind)
65      CALL swap_geometry(ind)
66      ps=f_ps(ind)
67      theta=f_theta(ind)
68      theta_rhodz=f_theta_rhodz(ind)
69      CALL compute_theta2theta_rhodz(ps, theta, theta_rhodz,0)
70    ENDDO
71 
72  END SUBROUTINE theta2theta_rhodz
73 
74  SUBROUTINE compute_theta2theta_rhodz(ps,theta, theta_rhodz,offset)
75  USE icosa
76  USE pression_mod
77  IMPLICIT NONE
78    REAL(rstd),INTENT(IN) :: ps(iim*jjm)
79    REAL(rstd),INTENT(IN) :: theta(iim*jjm,llm)
80    REAL(rstd),INTENT(OUT) :: theta_rhodz(iim*jjm,llm)
81    INTEGER,INTENT(IN) :: offset
82    INTEGER :: i,j,ij,l
83    REAL(rstd),ALLOCATABLE,SAVE :: p(:,:)
84
85!$OMP BARRIER
86!$OMP MASTER
87      ALLOCATE( p(iim*jjm,llm+1))
88!$OMP END MASTER
89!$OMP BARRIER
90
91    CALL compute_pression(ps,p,offset)
92   
93    DO    l    = 1, llm
94!$OMP DO
95      DO j=jj_begin-offset,jj_end+offset
96        DO i=ii_begin-offset,ii_end+offset
97          ij=(j-1)*iim+i
98          theta_rhodz(ij,l) = theta(ij,l) * (p(ij,l)-p(ij,l+1))/g
99        ENDDO
100      ENDDO
101    ENDDO
102
103!$OMP BARRIER
104!$OMP MASTER
105      DEALLOCATE( p)
106!$OMP END MASTER
107!$OMP BARRIER   
108
109  END SUBROUTINE compute_theta2theta_rhodz
110
111  SUBROUTINE compute_theta_rhodz2theta(ps,theta_rhodz,theta,offset)
112  USE icosa
113  USE pression_mod
114  IMPLICIT NONE
115    REAL(rstd),INTENT(IN) :: ps(iim*jjm)
116    REAL(rstd),INTENT(IN) :: theta_rhodz(iim*jjm,llm)
117    REAL(rstd),INTENT(OUT) :: theta(iim*jjm,llm)
118    INTEGER,INTENT(IN) :: offset
119    INTEGER :: i,j,ij,l
120    REAL(rstd),SAVE,ALLOCATABLE :: p(:,:)
121
122!$OMP BARRIER
123!$OMP MASTER
124      ALLOCATE( p(iim*jjm,llm+1))
125!$OMP END MASTER
126!$OMP BARRIER
127    CALL compute_pression(ps,p,offset)
128   
129    DO    l    = 1, llm
130      DO j=jj_begin-offset,jj_end+offset
131        DO i=ii_begin-offset,ii_end+offset
132          ij=(j-1)*iim+i
133          theta(ij,l) = theta_rhodz(ij,l) / ((p(ij,l)-p(ij,l+1))/g)
134        ENDDO
135      ENDDO
136    ENDDO
137
138!$OMP BARRIER
139!$OMP MASTER
140      DEALLOCATE( p)
141!$OMP END MASTER
142!$OMP BARRIER   
143   
144  END SUBROUTINE compute_theta_rhodz2theta
145
146  SUBROUTINE compute_theta_rhodz2temperature(ps,theta_rhodz,temp,offset)
147  USE icosa
148  USE pression_mod
149  USE exner_mod
150  IMPLICIT NONE
151    REAL(rstd),INTENT(IN) :: ps(iim*jjm)
152    REAL(rstd),INTENT(IN) :: theta_rhodz(iim*jjm,llm)
153    REAL(rstd),INTENT(OUT) :: temp(iim*jjm,llm)
154    INTEGER,INTENT(IN) :: offset
155    INTEGER :: i,j,ij,l
156    REAL(rstd) :: p(iim*jjm,llm+1)
157    REAL(rstd) :: pk(iim*jjm,llm)
158    REAL(rstd) :: pks(iim*jjm)
159
160    CALL compute_pression(ps,p,offset)
161    CALL compute_exner(ps,p,pks,pk,offset)
162       
163    DO    l    = 1, llm
164      DO j=jj_begin-offset,jj_end+offset
165        DO i=ii_begin-offset,ii_end+offset
166          ij=(j-1)*iim+i
167          temp(ij,l) = ( theta_rhodz(ij,l) / ((p(ij,l)-p(ij,l+1))/g) ) * pk(ij,l) / cpp
168        ENDDO
169      ENDDO
170    ENDDO
171   
172  END SUBROUTINE compute_theta_rhodz2temperature
173
174  SUBROUTINE compute_temperature2theta_rhodz(ps,temp,theta_rhodz,offset)
175  USE icosa
176  USE pression_mod
177  USE exner_mod
178  IMPLICIT NONE
179    REAL(rstd),INTENT(IN) :: ps(iim*jjm)
180    REAL(rstd),INTENT(OUT) :: theta_rhodz(iim*jjm,llm)
181    REAL(rstd),INTENT(IN) :: temp(iim*jjm,llm)
182    INTEGER,INTENT(IN) :: offset
183    INTEGER :: i,j,ij,l
184    REAL(rstd) :: p(iim*jjm,llm+1)
185    REAL(rstd) :: pk(iim*jjm,llm)
186    REAL(rstd) :: pks(iim*jjm)
187
188    CALL compute_pression(ps,p,offset)
189    CALL compute_exner(ps,p,pks,pk,offset)
190       
191    DO    l    = 1, llm
192      DO j=jj_begin-offset,jj_end+offset
193        DO i=ii_begin-offset,ii_end+offset
194          ij=(j-1)*iim+i
195!          temp(ij,l) = ( theta_rhodz(ij,l) / ((p(ij,l)-p(ij,l+1))/g) ) * pk(ij,l) / cpp
196          theta_rhodz(ij,l) = temp(ij,l) * ((p(ij,l)-p(ij,l+1))/g) / (pk(ij,l) / cpp )
197        ENDDO
198      ENDDO
199    ENDDO
200   
201  END SUBROUTINE compute_temperature2theta_rhodz
202   
203END MODULE theta2theta_rhodz_mod
Note: See TracBrowser for help on using the repository browser.