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

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

Towards HEVI time stepping

File size: 4.4 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_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), &
57       !            taujj(j), f_phis, f_geopot, &
58       !            f_ps,f_mass,f_theta_rhodz,f_u, &
59       !            f_hflux, f_wflux, &
60       !            f_dps_slow(:,j), f_dmass_slow(:,j), f_dtheta_rhodz_slow(:,j), &
61       !            f_du_slow(:,j), f_du_fast(:,j) )
62
63       CALL caldyn((j==1) .AND. (MOD(it,itau_out)==0), &
64            f_phis, f_ps,f_mass,f_theta_rhodz,f_u,f_q, &
65            f_geopot, f_hflux, f_wflux, &
66            f_dps_slow(:,j), f_dmass_slow(:,j), f_dtheta_rhodz_slow(:,j), &
67            f_du_slow(:,j))
68
69       ! cumulate 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
78       ! update model state
79       DO l=1,j
80          IF(caldyn_eta==eta_mass) THEN
81             CALL update_2D(bjl(l,j), f_ps, f_dps_slow(:,l))
82          ELSE
83             CALL update(bjl(l,j), f_mass, f_dmass_slow(:,l))
84          END IF
85          CALL update(bjl(l,j), f_theta_rhodz, f_dtheta_rhodz_slow(:,l))
86          CALL update(bjl(l,j), f_u, f_du_slow(:,l))
87!          CALL update(cjl(l,j), f_u, f_du_fast(:,l)) ! FIXME - only slow terms right now
88       END DO
89    END DO
90  END SUBROUTINE HEVI_scheme
91 
92  SUBROUTINE update(w, f_y, f_dy)
93    USE dimensions
94    REAL(rstd) :: w
95    TYPE(t_field) :: f_y(:), f_dy(:)
96    REAL(rstd), POINTER :: y(:,:), dy(:,:)
97    INTEGER :: ind
98    DO ind=1,ndomain
99       IF (.NOT. assigned_domain(ind)) CYCLE
100       CALL swap_dimensions(ind)
101       dy=f_dy(ind); y=f_y(ind)
102       CALL compute_update(w,y,dy)
103    ENDDO
104  END SUBROUTINE update
105   
106  SUBROUTINE compute_update(w, y, dy)
107    USE omp_para
108    USE disvert_mod
109    REAL(rstd) :: w
110    REAL(rstd) :: y(:,:), dy(:,:)
111    INTENT(INOUT) :: y
112    INTENT(IN) :: dy
113    INTEGER :: l
114    DO l=ll_begin,ll_end
115       y(:,l)=y(:,l)+w*dy(:,l)
116    ENDDO
117  END SUBROUTINE compute_update
118 
119  SUBROUTINE update_2D(w, f_y, f_dy)
120    REAL(rstd) :: w
121    TYPE(t_field) :: f_y(:), f_dy(:)
122    REAL(rstd), POINTER :: y(:), dy(:)
123    INTEGER :: ind
124    DO ind=1,ndomain
125       IF (.NOT. assigned_domain(ind)) CYCLE
126       dy=f_dy(ind); y=f_y(ind)
127       CALL compute_update_2D(w,y,dy)
128    ENDDO
129  END SUBROUTINE update_2D
130   
131  SUBROUTINE compute_update_2D(w, y, dy)
132    REAL(rstd) :: w, y(:), dy(:)
133    INTENT(INOUT) :: y
134    INTENT(IN) :: dy
135    y(:)=y(:)+w*dy(:)
136  END SUBROUTINE compute_update_2D
137 
138END MODULE hevi_scheme_mod
Note: See TracBrowser for help on using the repository browser.