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

Last change on this file since 78 was 73, checked in by dubos, 12 years ago

Keyword changes in guide_mod and guided_ncar_mod

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