source: codes/icosagcm/trunk/src/etat0_williamson.f90 @ 164

Last change on this file since 164 was 164, checked in by dubos, 11 years ago

Williamson (1991) test case

File size: 4.8 KB
Line 
1MODULE etat0_williamson_mod
2  USE icosa
3  PRIVATE
4    REAL(rstd), PARAMETER :: h0=8.E3
5    REAL(rstd), PARAMETER :: R0=4
6    REAL(rstd), PARAMETER :: K0=7.848E-6
7    REAL(rstd), PARAMETER :: omega0=K0
8   
9    PUBLIC  etat0_williamson, etat0_williamson_new
10   
11CONTAINS
12 
13 
14  SUBROUTINE etat0_williamson(f_h,f_u)
15  USE icosa
16  IMPLICIT NONE
17    TYPE(t_field),POINTER :: f_h(:)
18    TYPE(t_field),POINTER :: f_u(:)
19 
20    REAL(rstd),POINTER :: h(:)
21    REAL(rstd),POINTER :: u(:)
22    INTEGER :: ind
23   
24    DO ind=1,ndomain
25      CALL swap_dimensions(ind)
26      CALL swap_geometry(ind)
27      h=f_h(ind)
28      u=f_u(ind)
29      CALL compute_etat0_williamson(h, u)
30    ENDDO
31
32  END SUBROUTINE etat0_williamson 
33 
34  SUBROUTINE etat0_williamson_new(f_phis,f_mass,f_theta_rhodz,f_u, f_q)
35  USE icosa
36  USE mpipara, ONLY : is_mpi_root
37  USE disvert_mod, ONLY : caldyn_eta, eta_lag
38
39  IMPLICIT NONE
40    TYPE(t_field),POINTER :: f_phis(:)
41    TYPE(t_field),POINTER :: f_mass(:)
42    TYPE(t_field),POINTER :: f_theta_rhodz(:)
43    TYPE(t_field),POINTER :: f_u(:)
44    TYPE(t_field),POINTER :: f_q(:)
45 
46    REAL(rstd),POINTER :: phis(:)
47    REAL(rstd),POINTER :: h(:,:)
48    REAL(rstd),POINTER :: theta_rhodz(:,:)
49    REAL(rstd),POINTER :: u(:,:)
50    INTEGER :: ind
51
52    IF(caldyn_eta /= eta_lag) THEN
53       IF(is_mpi_root) PRINT *, 'etat0_type=williamson91.5 (Williamson,1991) must be used with caldyn_eta=eta_lag'
54       STOP
55    END IF
56
57    IF(llm>1) THEN
58       IF(is_mpi_root) PRINT *, 'etat0_type=williamson91.5 (Williamson,1991) must be used with llm=1 but llm =',llm
59       STOP
60    END IF
61
62    DO ind=1,ndomain
63      CALL swap_dimensions(ind)
64      CALL swap_geometry(ind)
65      h=f_mass(ind)
66      u=f_u(ind)
67      theta_rhodz=f_theta_rhodz(ind)
68      phis=f_phis(ind)
69      CALL compute_etat0_williamson(h(:,1), u(:,1))
70      phis(:)=0.
71      theta_rhodz(:,:) = h(:,:)
72    ENDDO
73
74  END SUBROUTINE etat0_williamson_new
75 
76  SUBROUTINE compute_etat0_williamson(hi, ue)
77  USE icosa
78  IMPLICIT NONE 
79    REAL(rstd),INTENT(OUT) :: hi(iim*jjm)
80    REAL(rstd),INTENT(OUT) :: ue(3*iim*jjm)
81    REAL(rstd) :: lon, lat
82    REAL(rstd) :: nx(3),n_norm,Velocity(3)
83    REAL(rstd) :: A,B,C
84    REAL(rstd) :: v1(3),v2(3),ny(3)
85    REAL(rstd) :: de_min
86   
87    INTEGER :: i,j,n
88
89 
90    DO j=jj_begin-1,jj_end+1
91      DO i=ii_begin-1,ii_end+1
92        n=(j-1)*iim+i
93        CALL xyz2lonlat(xyz_i(n,:),lon,lat)
94        A= 0.5*omega0*(2*omega+omega0)*cos(lat)**2   &
95         + 0.25*K0**2*cos(lat)**(2*R0)*((R0+1)*cos(lat)**2+(2*R0**2-R0-2)-2*R0**2/cos(lat)**2)
96        B=2*(omega+omega0)*K0/((R0+1)*(R0+2))*cos(lat)**R0*((R0**2+2*R0+2)-(R0+1)**2*cos(lat)**2)
97        C=0.25*K0**2*cos(lat)**(2*R0)*((R0+1)*cos(lat)**2-(R0+2))
98       
99        hi(n)=(g*h0+radius**2*A+radius**2*B*cos(R0*lon)+radius**2*C*cos(2*R0*lon))/g
100
101
102        CALL compute_velocity(xyz_e(n+u_right,:),velocity)
103        CALL cross_product2(xyz_v(n+z_rdown,:),xyz_v(n+z_rup,:),nx)
104       
105        ue(n+u_right)=1e-10
106        n_norm=sqrt(sum(nx(:)**2))
107        IF (n_norm>1e-30) THEN
108          nx=-nx/n_norm*ne(n,right)
109          ue(n+u_right)=sum(nx(:)*velocity(:))
110          IF (ABS(ue(n+u_right))<1e-100) PRINT *,"ue(n+u_right) ==0",i,j,velocity(:)
111        ENDIF
112       
113       
114       
115        CALL compute_velocity(xyz_e(n+u_lup,:),velocity)
116        CALL cross_product2(xyz_v(n+z_up,:),xyz_v(n+z_lup,:),nx)
117
118        ue(n+u_lup)=1e-10
119        n_norm=sqrt(sum(nx(:)**2))
120        IF (n_norm>1e-30) THEN
121          nx=-nx/n_norm*ne(n,lup)
122          ue(n+u_lup)=sum(nx(:)*velocity(:))
123          IF (ABS(ue(n+u_lup))<1e-100) PRINT *,"ue(n+u_lup) ==0",i,j,velocity(:)
124        ENDIF
125
126       
127        CALL compute_velocity(xyz_e(n+u_ldown,:),velocity)
128        CALL cross_product2(xyz_v(n+z_ldown,:),xyz_v(n+z_down,:),nx)
129
130        ue(n+u_ldown)=1e-10
131        n_norm=sqrt(sum(nx(:)**2))
132        IF (n_norm>1e-30) THEN
133          nx=-nx/n_norm*ne(n,ldown)
134          ue(n+u_ldown)=sum(nx(:)*velocity(:))
135          IF (ABS(ue(n+u_ldown))<1e-100) PRINT *,"ue(n+u_ldown) ==0",i,j
136        ENDIF
137       
138       
139      ENDDO
140    ENDDO
141
142  CONTAINS
143   
144    SUBROUTINE compute_velocity(x,velocity)
145      IMPLICIT NONE
146      REAL(rstd),INTENT(IN)  :: x(3)
147      REAL(rstd),INTENT(OUT) :: velocity(3)
148      REAL(rstd)  :: e_lat(3), e_lon(3)
149      REAL(rstd) :: lon,lat
150      REAL(rstd) :: u,v
151     
152      CALL xyz2lonlat(x/radius,lon,lat)
153      e_lat(1) = -cos(lon)*sin(lat)
154      e_lat(2) = -sin(lon)*sin(lat)
155      e_lat(3) = cos(lat)
156       
157      e_lon(1) = -sin(lon)
158      e_lon(2) = cos(lon)
159      e_lon(3) = 0
160       
161      u=radius*omega0*cos(lat)+radius*K0*cos(lat)**(R0-1)*(R0*sin(lat)**2-cos(lat)**2)*cos(R0*lon)
162      v=-radius*K0*R0*cos(lat)**(R0-1)*sin(lat)*sin(R0*lon)
163
164      Velocity=(u*e_lon+v*e_lat+1e-50)
165
166    END SUBROUTINE compute_velocity
167     
168  END SUBROUTINE compute_etat0_williamson
169 
170END MODULE etat0_williamson_mod
Note: See TracBrowser for help on using the repository browser.