source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/DYNAMICO/src/dcmip/guided_ncar_mod.f90 @ 6612

Last change on this file since 6612 was 6612, checked in by acosce, 10 months ago

DYNAMICO used for ICOLMDZORINCA_CO2_Transport_GMD_2023

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