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

Last change on this file since 361 was 361, checked in by dubos, 9 years ago

ARK2.3 HEVI time stepping - tested with DCMIP4 only

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