source: codes/icosagcm/trunk/src/guided_ncar_mod.f90 @ 352

Last change on this file since 352 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: 5.2 KB
Line 
1MODULE guided_ncar_mod
2  USE icosa
3  PRIVATE
4 
5  INTEGER,SAVE :: case_wind
6!$OMP THREADPRIVATE(case_wind)
7 
8  REAL(rstd), PARAMETER :: alpha=0.0 ! tilt of solid-body rotation
9  REAL(rstd), PARAMETER :: tau_hadley=daysec, tau = 12*daysec ! 12 days               ! see p. 16
10  REAL(rstd), PARAMETER :: w0_deform = 23000*pi/tau, b=0.2, ptop=25494.4  ! see p. 16
11  REAL(rstd), PARAMETER :: u0_hadley=40.,w0_hadley=0.15 ,ztop= 12000. 
12  INTEGER, PARAMETER    :: K_hadley=5
13
14  PUBLIC init_guided, guided
15
16CONTAINS
17
18  SUBROUTINE init_guided
19    IMPLICIT NONE
20    CHARACTER(LEN=255) :: wind
21    wind='deform'
22    CALL getin('dcmip1_wind',wind)
23    SELECT CASE(TRIM(wind))
24    CASE('solid')
25       case_wind=0
26    CASE('deform')
27       case_wind=1
28    CASE('hadley')
29       case_wind=2
30    CASE DEFAULT
31       PRINT*,'Bad selector for variable ncar_adv_wind : <', TRIM(wind),'> options are <solid>, <deform>, <hadley>'
32       END SELECT
33  END SUBROUTINE init_guided
34 
35  SUBROUTINE guided(tt, f_ps, f_theta_rhodz, f_u, f_q)
36  USE icosa
37    IMPLICIT NONE
38    REAL(rstd), INTENT(IN):: tt
39    TYPE(t_field),POINTER :: f_ps(:)
40    TYPE(t_field),POINTER :: f_phis(:)
41    TYPE(t_field),POINTER :: f_theta_rhodz(:)
42    TYPE(t_field),POINTER :: f_u(:) 
43    TYPE(t_field),POINTER :: f_q(:) 
44   
45    REAL(rstd),POINTER :: ue(:,:)
46    INTEGER :: ind
47   
48    DO ind = 1 , ndomain
49      IF (.NOT. assigned_domain(ind)) CYCLE
50      CALL swap_dimensions(ind)
51      CALL swap_geometry(ind) 
52      ue = f_u(ind) 
53      CALL wind_profile(tt,ue)
54    END DO   
55
56  END SUBROUTINE guided
57 
58
59  SUBROUTINE wind_profile(tt,ue)
60    USE icosa
61    USE disvert_mod
62    IMPLICIT NONE
63    REAL(rstd),INTENT(IN)  :: tt ! current time
64    REAL(rstd),INTENT(OUT) :: ue(iim*3*jjm,llm)
65    REAL(rstd) :: lon, lat
66    REAL(rstd) :: nx(3),n_norm,Velocity(3,llm)
67    REAL(rstd) :: rr1,rr2,bb,cc,aa,hmx
68    REAL(rstd) :: v1(3),v2(3),ny(3)
69    INTEGER :: i,j,n,l
70    REAL(rstd) :: pitbytau,kk, pr, zr, u0, u1, v0
71
72    pitbytau = pi*tt/tau
73    kk = 10*radius/tau
74    u0 = 2*pi*radius/tau ! for solid-body rotation
75!---------------------------------------------------------
76    DO l = 1,llm 
77       pr = presnivs(l)
78       zr = -kappa*cpp*ncar_T0/g*log(pr/ncar_p0)  ! reciprocal of (1) p. 13, isothermal atmosphere
79       u1 = w0_deform*radius/b/ptop*cos(2*pitbytau)*(exp((ptop-pr)/b/ptop)-exp((pr-ncar_p0)/b/ptop))
80       v0 = -radius*w0_hadley*pi/(5.0*ztop)*(ncar_p0/pr)*cos(pi*zr/ztop)*cos(pi*tt/tau_hadley) ! for Hadley cell
81
82       DO j=jj_begin-1,jj_end+1
83          DO i=ii_begin-1,ii_end+1
84             n=(j-1)*iim+i
85             CALL compute_velocity(xyz_e(n+u_right,:),l,velocity(:,l))
86             CALL cross_product2(xyz_v(n+z_rdown,:)/radius,xyz_v(n+z_rup,:)/radius,nx)       
87             ue(n+u_right,l)=1e-10
88             n_norm=sqrt(sum(nx(:)**2))
89             IF (n_norm>1e-30) THEN
90                nx=-nx/n_norm*ne(n,right)
91                ue(n+u_right,l)=sum(nx(:)*velocity(:,l))
92                IF (ABS(ue(n+u_right,l))<1e-100) PRINT *,"ue(n+u_right)==0",i,j,velocity(:,1)
93             ENDIF
94             
95             CALL compute_velocity(xyz_e(n+u_lup,:),l,velocity(:,l))
96             CALL cross_product2(xyz_v(n+z_up,:)/radius,xyz_v(n+z_lup,:)/radius,nx)
97             
98             ue(n+u_lup,l)=1e-10
99             n_norm=sqrt(sum(nx(:)**2))
100             IF (n_norm>1e-30) THEN
101                nx=-nx/n_norm*ne(n,lup)
102                ue(n+u_lup,l)=sum(nx(:)*velocity(:,l))
103             ENDIF
104             
105             CALL compute_velocity(xyz_e(n+u_ldown,:),l,velocity(:,l))
106             CALL cross_product2(xyz_v(n+z_ldown,:)/radius,xyz_v(n+z_down,:)/radius,nx)
107             
108             ue(n+u_ldown,l)=1e-10
109             n_norm=sqrt(sum(nx(:)**2))
110             IF (n_norm>1e-30) THEN
111                nx=-nx/n_norm*ne(n,ldown)
112                ue(n+u_ldown,l)=sum(nx(:)*velocity(:,l))
113                IF (ABS(ue(n+u_ldown,l))<1e-100) PRINT *,"ue(n+u_ldown)==0",i,j
114             ENDIF
115          ENDDO
116       ENDDO
117    END DO
118   
119  CONTAINS
120           
121    SUBROUTINE compute_velocity(x,l,velocity)
122      IMPLICIT NONE
123      REAL(rstd),INTENT(IN)  :: x(3)
124      INTEGER,INTENT(IN)::l
125      REAL(rstd),INTENT(OUT) :: velocity(3)
126      REAL(rstd) :: e_lat(3), e_lon(3)
127      REAL(rstd) :: lon,lat
128      REAL(rstd) :: u,v
129             
130      CALL xyz2lonlat(x/radius,lon,lat)
131      e_lat(1) = -cos(lon)*sin(lat)
132      e_lat(2) = -sin(lon)*sin(lat)
133      e_lat(3) = cos(lat)
134       
135      e_lon(1) = -sin(lon)
136      e_lon(2) = cos(lon)
137      e_lon(3) = 0
138
139      u = 0.0 ; v = 0.0
140   
141      SELECT CASE(case_wind) 
142      CASE(0)  ! Solid-body rotation
143         u=u0*(cos(lat)*cos(alpha)+sin(lat)*sin(alpha)*cos(lon))
144         v=-u0*sin(lon)*sin(alpha)
145      CASE(1)  ! 3D Deformational flow -
146         lon = lon-2*pitbytau
147         u = kk*sin(lon)*sin(lon)*sin(2*lat)*cos(pitbytau)+ u0*cos(lat)
148         u = u + u1*cos(lon)*cos(lat)**2
149         v = kk*sin(2*lon)*cos(lat)*cos(pitbytau) 
150      CASE(2) ! Hadley-like flow
151         u = u0_hadley*cos(lat)
152         v = v0*cos(lat)*sin(5.*lat)    ! Eq. 37 p. 19
153      CASE DEFAULT 
154         PRINT*,"not valid choice of wind" 
155      END SELECT
156     
157      Velocity(:)=(u*e_lon(:)+v*e_lat(:)+1e-50)
158     
159    END SUBROUTINE compute_velocity
160   
161  END SUBROUTINE  wind_profile
162
163
164END MODULE guided_ncar_mod
Note: See TracBrowser for help on using the repository browser.