source: codes/icosagcm/trunk/src/hevi_scheme.f90 @ 409

Last change on this file since 409 was 387, checked in by dubos, 8 years ago

Infrastructure for multiple dynamical tracers - tested with JW06 and moist baroclinic wave

File size: 5.3 KB
Line 
1MODULE hevi_scheme_mod
2  USE prec
3  USE domain_mod
4  USE field_mod
5  USE euler_scheme_mod
6  USE caldyn_kernels_base_mod, ONLY : DEC
7  IMPLICIT NONE
8  PRIVATE
9
10  REAL(rstd), SAVE :: wj(3), bjl(3,3), cjl(3,3), taujj(3)
11  REAL(rstd), PARAMETER, DIMENSION(3) :: zero = (/0.,0.,0./)
12
13  PUBLIC :: set_coefs_ark23, set_coefs_ark33, hevi_scheme
14
15CONTAINS
16
17  SUBROUTINE set_coefs_ark23(dt)
18    ! ARK2 scheme by Giraldo, Kelly, Constantinescu 2013
19    ! See Weller et al., 2013 - ARK2 scheme Fig. 2
20    REAL(rstd) :: dt
21    REAL(rstd), PARAMETER :: delta=.5/SQRT(2.), gamma=1.-2.*delta
22!    REAL(rstd), PARAMETER :: alpha=(3.+SQRT(8.))/6. ! original value in GKC2013
23    REAL(rstd), PARAMETER :: alpha=0.7
24    REAL(rstd), PARAMETER, DIMENSION(3) :: wj = (/delta,delta,gamma/)
25    CALL set_coefs_hevi(dt, &
26         (/ zero, (/2.*gamma,0.,0./), (/1-alpha,alpha,0./), wj /), &
27         (/ zero, (/gamma,gamma,0./), wj, wj /) )
28  END SUBROUTINE set_coefs_ark23
29
30  SUBROUTINE set_coefs_ark33(dt)
31    ! Fully-explicit RK3 scheme disguised as ARK
32    REAL(rstd) :: dt
33    CALL set_coefs_rk(dt, (/ zero, (/.5,0.,0./), (/-1.,2.,0./), (/1./6.,2./3.,1./6./) /) )
34  END SUBROUTINE set_coefs_ark33
35   
36  SUBROUTINE set_coefs_rk(dt, ajl)
37    REAL(rstd) :: dt, ajl(3,4)
38    CALL set_coefs_hevi(dt,ajl,ajl)
39  END SUBROUTINE set_coefs_rk
40
41  SUBROUTINE set_coefs_hevi(dt, ajl_slow, ajl_fast)
42    REAL(rstd) :: dt, ajl_slow(3,4), ajl_fast(3,4) ! fast/slow Butcher tableaus
43    INTEGER :: j
44    DO j=1,3
45       bjl(:,j) = dt*(ajl_slow(:,j+1)-ajl_slow(:,j))
46       cjl(:,j) = dt*(ajl_fast(:,j+1)-ajl_fast(:,j))
47       taujj(j) = dt*ajl_fast(j,j)
48    END DO
49    wj=dt*ajl_slow(:,4)
50  END SUBROUTINE set_coefs_hevi
51
52  SUBROUTINE HEVI_scheme(it, fluxt_zero)
53    USE time_mod
54    USE disvert_mod
55    USE caldyn_hevi_mod
56    LOGICAL :: fluxt_zero(ndomain) ! set to .TRUE. to start accumulating fluxes in time
57    INTEGER :: it,j,l, ind
58    REAL(rstd),POINTER :: hflux(:,:),wflux(:,:),hfluxt(:,:),wfluxt(:,:)
59
60    IF(DEC) CALL legacy_to_DEC(f_ps, f_u)
61    DO j=1,nb_stage
62       CALL caldyn_hevi((j==1) .AND. (MOD(it,itau_out)==0), taujj(j), &
63            f_phis, f_ps,f_mass,f_theta_rhodz,f_u,f_q, &
64            f_W, f_geopot, f_hflux, f_wflux, &
65            f_dps_slow(:,j), f_dmass_slow(:,j), f_dtheta_rhodz_slow(:,j), &
66            f_du_slow(:,j), f_du_fast(:,j), &
67            f_dPhi_slow(:,j), f_dPhi_fast(:,j), &
68            f_dW_slow(:,j), f_dW_fast(:,j) )
69       ! accumulate mass fluxes for transport scheme
70       DO ind=1,ndomain
71          IF (.NOT. assigned_domain(ind)) CYCLE
72          CALL swap_dimensions(ind)
73          hflux=f_hflux(ind);     hfluxt=f_hfluxt(ind)
74          wflux=f_wflux(ind);     wfluxt=f_wfluxt(ind)
75          CALL accumulate_fluxes(hflux,wflux, hfluxt,wfluxt, wj(j), fluxt_zero(ind))
76       END DO
77       ! update model state
78       DO l=1,j
79          IF(caldyn_eta==eta_mass) THEN
80             CALL update_2D(bjl(l,j), f_ps, f_dps_slow(:,l))
81          ELSE
82             CALL update_3D(bjl(l,j), f_mass, f_dmass_slow(:,l))
83          END IF
84          CALL update_4D(bjl(l,j), f_theta_rhodz, f_dtheta_rhodz_slow(:,l))
85          CALL update_3D(bjl(l,j), f_u, f_du_slow(:,l))
86          CALL update_3D(cjl(l,j), f_u, f_du_fast(:,l))
87          IF(.NOT. hydrostatic) THEN
88             CALL update_3D(bjl(l,j), f_W, f_dW_slow(:,l))
89             CALL update_3D(cjl(l,j), f_W, f_dW_fast(:,l))
90             CALL update_3D(bjl(l,j), f_geopot, f_dPhi_slow(:,l))
91             CALL update_3D(cjl(l,j), f_geopot, f_dPhi_fast(:,l))
92          END IF
93       END DO
94    END DO
95    IF(DEC) CALL DEC_to_legacy(f_ps, f_u)
96  END SUBROUTINE HEVI_scheme
97 
98  SUBROUTINE update_4D(w, f_y, f_dy)
99    USE dimensions
100    USE grid_param, ONLY : nqdyn
101    REAL(rstd) :: w
102    TYPE(t_field) :: f_y(:), f_dy(:)
103    REAL(rstd), POINTER :: y(:,:,:), dy(:,:,:)
104    INTEGER :: ind, iq
105    IF(w /= 0.) THEN
106       DO ind=1,ndomain
107          IF (.NOT. assigned_domain(ind)) CYCLE
108          CALL swap_dimensions(ind)
109          dy=f_dy(ind); y=f_y(ind)
110          DO iq=1,nqdyn
111             CALL compute_update_3D(w,y(:,:,iq),dy(:,:,iq))
112          END DO
113       ENDDO
114    END IF
115  END SUBROUTINE update_4D
116   
117  SUBROUTINE update_3D(w, f_y, f_dy)
118    USE dimensions
119    REAL(rstd) :: w
120    TYPE(t_field) :: f_y(:), f_dy(:)
121    REAL(rstd), POINTER :: y(:,:), dy(:,:)
122    INTEGER :: ind
123    IF(w /= 0.) THEN
124       DO ind=1,ndomain
125          IF (.NOT. assigned_domain(ind)) CYCLE
126          CALL swap_dimensions(ind)
127          dy=f_dy(ind); y=f_y(ind)
128          CALL compute_update_3D(w,y,dy)
129       ENDDO
130    END IF
131  END SUBROUTINE update_3D
132   
133  SUBROUTINE compute_update_3D(w, y, dy)
134    USE omp_para
135    USE disvert_mod
136    REAL(rstd) :: w
137    REAL(rstd) :: y(:,:), dy(:,:)
138    INTENT(INOUT) :: y
139    INTENT(IN) :: dy
140    INTEGER :: l
141    DO l=ll_begin,ll_end
142       y(:,l)=y(:,l)+w*dy(:,l)
143    ENDDO
144  END SUBROUTINE compute_update_3D
145 
146  SUBROUTINE update_2D(w, f_y, f_dy)
147    REAL(rstd) :: w
148    TYPE(t_field) :: f_y(:), f_dy(:)
149    REAL(rstd), POINTER :: y(:), dy(:)
150    INTEGER :: ind
151    DO ind=1,ndomain
152       IF (.NOT. assigned_domain(ind)) CYCLE
153       dy=f_dy(ind); y=f_y(ind)
154       CALL compute_update_2D(w,y,dy)
155    ENDDO
156  END SUBROUTINE update_2D
157   
158  SUBROUTINE compute_update_2D(w, y, dy)
159    REAL(rstd) :: w, y(:), dy(:)
160    INTENT(INOUT) :: y
161    INTENT(IN) :: dy
162    y(:)=y(:)+w*dy(:)
163  END SUBROUTINE compute_update_2D
164 
165END MODULE hevi_scheme_mod
Note: See TracBrowser for help on using the repository browser.