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

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

Progress towards NH

File size: 4.7 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 :: alpha=(3.+SQRT(8.))/6., delta=.5/SQRT(2.), gamma=1.-2.*delta
22    REAL(rstd), PARAMETER, DIMENSION(3) :: wj = (/delta,delta,gamma/)
23    CALL set_coefs_hevi(dt, &
24         (/ zero, (/2.*gamma,0.,0./), (/1-alpha,alpha,0./), wj /), &
25         (/ zero, (/gamma,gamma,0./), wj, wj /) )
26  END SUBROUTINE set_coefs_ark23
27
28  SUBROUTINE set_coefs_ark33(dt)
29    ! Fully-explicit RK3 scheme disguised as ARK
30    REAL(rstd) :: dt
31    CALL set_coefs_rk(dt, (/ zero, (/.5,0.,0./), (/-1.,2.,0./), (/1./6.,2./3.,1./6./) /) )
32  END SUBROUTINE set_coefs_ark33
33   
34  SUBROUTINE set_coefs_rk(dt, ajl)
35    REAL(rstd) :: dt, ajl(3,4)
36    CALL set_coefs_hevi(dt,ajl,ajl)
37  END SUBROUTINE set_coefs_rk
38
39  SUBROUTINE set_coefs_hevi(dt, ajl_slow, ajl_fast)
40    REAL(rstd) :: dt, ajl_slow(3,4), ajl_fast(3,4) ! fast/slow Butcher tableaus
41    INTEGER :: j
42    DO j=1,3
43       bjl(:,j) = dt*(ajl_slow(:,j+1)-ajl_slow(:,j))
44       cjl(:,j) = dt*(ajl_fast(:,j+1)-ajl_fast(:,j))
45       taujj(j) = dt*ajl_fast(j,j)
46    END DO
47    wj=dt*ajl_slow(:,4)
48  END SUBROUTINE set_coefs_hevi
49
50  SUBROUTINE HEVI_scheme(it, fluxt_zero)
51    USE time_mod
52    USE disvert_mod
53    USE caldyn_hevi_mod
54    LOGICAL :: fluxt_zero(ndomain) ! set to .TRUE. to start accumulating fluxes in time
55    INTEGER :: it,j,l, ind
56    REAL(rstd),POINTER :: hflux(:,:),wflux(:,:),hfluxt(:,:),wfluxt(:,:)
57
58    IF(DEC) CALL legacy_to_DEC(f_ps, f_u)
59    DO j=1,nb_stage
60       CALL caldyn_hevi((j==1) .AND. (MOD(it,itau_out)==0), taujj(j), &
61            f_phis, f_ps,f_mass,f_theta_rhodz,f_u,f_q, &
62            f_W, f_geopot, f_hflux, f_wflux, &
63            f_dps_slow(:,j), f_dmass_slow(:,j), f_dtheta_rhodz_slow(:,j), &
64            f_du_slow(:,j), f_du_fast(:,j), &
65            f_dPhi_slow(:,j), f_dPhi_fast(:,j), &
66            f_dW_slow(:,j), f_dW_fast(:,j) )
67       ! accumulate mass fluxes for transport scheme
68       DO ind=1,ndomain
69          IF (.NOT. assigned_domain(ind)) CYCLE
70          CALL swap_dimensions(ind)
71          hflux=f_hflux(ind);     hfluxt=f_hfluxt(ind)
72          wflux=f_wflux(ind);     wfluxt=f_wfluxt(ind)
73          CALL accumulate_fluxes(hflux,wflux, hfluxt,wfluxt, wj(j), fluxt_zero(ind))
74       END DO
75       ! update model state
76       DO l=1,j
77          IF(caldyn_eta==eta_mass) THEN
78             CALL update_2D(bjl(l,j), f_ps, f_dps_slow(:,l))
79          ELSE
80             CALL update(bjl(l,j), f_mass, f_dmass_slow(:,l))
81          END IF
82          CALL update(bjl(l,j), f_theta_rhodz, f_dtheta_rhodz_slow(:,l))
83          CALL update(bjl(l,j), f_u, f_du_slow(:,l))
84          CALL update(cjl(l,j), f_u, f_du_fast(:,l))
85          IF(.NOT. hydrostatic) THEN
86 !            CALL update(bjl(l,j), f_W, f_dW_slow(:,l)) ! slow tendencies of w, Phi not implemented yet
87             CALL update(cjl(l,j), f_W, f_dW_fast(:,l))
88 !            CALL update(bjl(l,j), f_geopot, f_dPhi_slow(:,l))
89             CALL update(cjl(l,j), f_geopot, f_dPhi_fast(:,l))
90          END IF
91       END DO
92    END DO
93    IF(DEC) CALL DEC_to_legacy(f_ps, f_u)
94  END SUBROUTINE HEVI_scheme
95 
96  SUBROUTINE update(w, f_y, f_dy)
97    USE dimensions
98    REAL(rstd) :: w
99    TYPE(t_field) :: f_y(:), f_dy(:)
100    REAL(rstd), POINTER :: y(:,:), dy(:,:)
101    INTEGER :: ind
102    IF(w /= 0.) THEN
103       DO ind=1,ndomain
104          IF (.NOT. assigned_domain(ind)) CYCLE
105          CALL swap_dimensions(ind)
106          dy=f_dy(ind); y=f_y(ind)
107          CALL compute_update(w,y,dy)
108       ENDDO
109    END IF
110  END SUBROUTINE update
111   
112  SUBROUTINE compute_update(w, y, dy)
113    USE omp_para
114    USE disvert_mod
115    REAL(rstd) :: w
116    REAL(rstd) :: y(:,:), dy(:,:)
117    INTENT(INOUT) :: y
118    INTENT(IN) :: dy
119    INTEGER :: l
120    DO l=ll_begin,ll_end
121       y(:,l)=y(:,l)+w*dy(:,l)
122    ENDDO
123  END SUBROUTINE compute_update
124 
125  SUBROUTINE update_2D(w, f_y, f_dy)
126    REAL(rstd) :: w
127    TYPE(t_field) :: f_y(:), f_dy(:)
128    REAL(rstd), POINTER :: y(:), dy(:)
129    INTEGER :: ind
130    DO ind=1,ndomain
131       IF (.NOT. assigned_domain(ind)) CYCLE
132       dy=f_dy(ind); y=f_y(ind)
133       CALL compute_update_2D(w,y,dy)
134    ENDDO
135  END SUBROUTINE update_2D
136   
137  SUBROUTINE compute_update_2D(w, y, dy)
138    REAL(rstd) :: w, y(:), dy(:)
139    INTENT(INOUT) :: y
140    INTENT(IN) :: dy
141    y(:)=y(:)+w*dy(:)
142  END SUBROUTINE compute_update_2D
143 
144END MODULE hevi_scheme_mod
Note: See TracBrowser for help on using the repository browser.