MFIX  2016-1
reset_new.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Module name: RESET_NEW C
4 ! Purpose: Reset the new variables with the stored previous-time-step C
5 ! values of field variables. C
6 ! *****Remember to modify update_old also
7 ! C
8 ! Author: M. Syamlal Date: FEB-6-97 C
9 ! C
10 ! Literature/Document References: C
11 ! C
12 ! Variables referenced: ROP_g, EP_g, ROP_s, IJKMAX2, MMAX, U_s, V_s, C
13 ! W_s C
14 ! C
15 ! Variables modified: ROP_go, ROP_so, IJK, M, U_so, V_so, W_so C
16 ! C
17 ! Local variables: NONE C
18 ! C
19 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
20  SUBROUTINE reset_new
21 
22 !...Translated by Pacific-Sierra Research VAST-90 2.06G5 12:17:31 12/09/98
23 !...Switches: -xf
24 !
25 !-----------------------------------------------
26 ! M o d u l e s
27 !-----------------------------------------------
28 
29  USE fldvar
30  USE physprop, only: mmax, nmax
32  USE scalars, only: nscalar
33  USE trace, only: trd_s_c, trd_s_co
34 
35  IMPLICIT NONE
36 !-----------------------------------------------
37 ! G l o b a l P a r a m e t e r s
38 !-----------------------------------------------
39 !-----------------------------------------------
40 ! L o c a l P a r a m e t e r s
41 !-----------------------------------------------
42 !-----------------------------------------------
43 ! L o c a l V a r i a b l e s
44 !-----------------------------------------------
45 !
46 ! Indices
47  INTEGER :: M
48 !
49 ! error index
50  INTEGER :: IER
51 
52 !-----------------------------------------------
53 
54  ep_g(:) = ep_go(:)
55  p_g(:) = p_go(:)
56  p_star(:) = p_staro(:)
57  ro_g(:) = ro_go(:)
58  rop_g(:) = rop_go(:)
59  u_g(:) = u_go(:)
60  v_g(:) = v_go(:)
61  w_g(:) = w_go(:)
62  IF (energy_eq) t_g(:) = t_go(:)
63  IF (species_eq(0)) THEN
64  IF (nmax(0) > 0) THEN
65  x_g(:,:nmax(0)) = x_go(:,:nmax(0))
66  ENDIF
67  ENDIF
68 
69  IF (nscalar > 0) THEN
70  scalar(:,:nscalar) = scalaro(:,:nscalar)
71  ENDIF
72 
73  IF (k_epsilon) THEN
74  k_turb_g(:) = k_turb_go(:)
75  e_turb_g(:) = e_turb_go(:)
76  ENDIF
77 
78  DO m = 1, mmax
79  rop_s(:,m) = rop_so(:,m)
80 ! add by rong
81  If (call_dqmom) d_p(:,m)=d_po(:,m)
82 ! If (NScalar>0) ome(:,M)=ome_o(:,M)
83 ! add by rong
84  IF (energy_eq) t_s(:,m) = t_so(:,m)
85  IF (granular_energy) THEN
86  theta_m(:,m) = theta_mo(:,m)
87  trd_s_c(:,m) = trd_s_co(:,m)
88  ENDIF
89  u_s(:,m) = u_so(:,m)
90  v_s(:,m) = v_so(:,m)
91  w_s(:,m) = w_so(:,m)
92  IF (species_eq(m)) THEN
93  IF (nmax(m) > 0) THEN
94  x_s(:,m,:nmax(m)) = x_so(:,m,:nmax(m))
95  ENDIF
96 
97  ro_s(:,m) = ro_so(:,m)
98  ENDIF
99  END DO
100 
101 ! Recalculate all coefficients
102  CALL calc_coeff_all (0, ier)
103 
104  RETURN
105  END SUBROUTINE reset_new
106 
107 !// Comments on the modifications for DMP version implementation
108 !// 120 Replaced the index for initialization: (:IJKMAX2) to just (:)
double precision, dimension(:,:), allocatable v_s
Definition: fldvar_mod.f:105
double precision, dimension(:,:), allocatable v_so
Definition: fldvar_mod.f:108
double precision, dimension(:), allocatable e_turb_go
Definition: fldvar_mod.f:166
double precision, dimension(:,:), allocatable trd_s_c
Definition: trace_mod.f:6
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
double precision, dimension(:,:), allocatable ro_so
Definition: fldvar_mod.f:48
subroutine calc_coeff_all(FLAG, IER)
Definition: calc_coeff.f:18
double precision, dimension(:), allocatable k_turb_g
Definition: fldvar_mod.f:161
double precision, dimension(:,:,:), allocatable x_so
Definition: fldvar_mod.f:84
double precision, dimension(:,:), allocatable w_s
Definition: fldvar_mod.f:117
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
double precision, dimension(:), allocatable t_g
Definition: fldvar_mod.f:63
double precision, dimension(:), allocatable k_turb_go
Definition: fldvar_mod.f:165
double precision, dimension(:,:), allocatable scalar
Definition: fldvar_mod.f:155
double precision, dimension(:), allocatable p_g
Definition: fldvar_mod.f:26
double precision, dimension(:), allocatable ep_go
Definition: fldvar_mod.f:23
double precision, dimension(:), allocatable v_go
Definition: fldvar_mod.f:102
double precision, dimension(:,:), allocatable t_so
Definition: fldvar_mod.f:72
double precision, dimension(:), allocatable t_go
Definition: fldvar_mod.f:69
double precision, dimension(:), allocatable u_go
Definition: fldvar_mod.f:90
double precision, dimension(:,:), allocatable d_po
Definition: fldvar_mod.f:60
double precision, dimension(:,:), allocatable u_s
Definition: fldvar_mod.f:93
double precision, dimension(:,:), allocatable scalaro
Definition: fldvar_mod.f:158
double precision, dimension(:,:), allocatable theta_mo
Definition: fldvar_mod.f:152
double precision, dimension(:,:), allocatable d_p
Definition: fldvar_mod.f:57
integer mmax
Definition: physprop_mod.f:19
double precision, dimension(:,:), allocatable trd_s_co
Definition: trace_mod.f:12
double precision, dimension(:,:,:), allocatable x_s
Definition: fldvar_mod.f:78
double precision, dimension(:,:), allocatable t_s
Definition: fldvar_mod.f:66
double precision, dimension(:,:), allocatable x_g
Definition: fldvar_mod.f:75
double precision, dimension(:,:), allocatable theta_m
Definition: fldvar_mod.f:149
double precision, dimension(:), allocatable v_g
Definition: fldvar_mod.f:99
double precision, dimension(:), allocatable w_g
Definition: fldvar_mod.f:111
logical call_dqmom
Definition: run_mod.f:127
double precision, dimension(:,:), allocatable u_so
Definition: fldvar_mod.f:96
double precision, dimension(:,:), allocatable rop_so
Definition: fldvar_mod.f:54
Definition: run_mod.f:13
double precision, dimension(:,:), allocatable w_so
Definition: fldvar_mod.f:120
double precision, dimension(:), allocatable w_go
Definition: fldvar_mod.f:114
double precision, dimension(:,:), allocatable ro_s
Definition: fldvar_mod.f:45
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
double precision, dimension(:), allocatable rop_go
Definition: fldvar_mod.f:41
logical k_epsilon
Definition: run_mod.f:97
double precision, dimension(:), allocatable p_star
Definition: fldvar_mod.f:142
logical energy_eq
Definition: run_mod.f:100
double precision, dimension(:,:), allocatable x_go
Definition: fldvar_mod.f:81
double precision, dimension(:), allocatable u_g
Definition: fldvar_mod.f:87
integer nscalar
Definition: scalars_mod.f:7
double precision, dimension(:), allocatable p_staro
Definition: fldvar_mod.f:146
double precision, dimension(:,:), allocatable rop_s
Definition: fldvar_mod.f:51
double precision, dimension(:), allocatable p_go
Definition: fldvar_mod.f:29
subroutine reset_new
Definition: reset_new.f:21
Definition: trace_mod.f:1
double precision, dimension(:), allocatable e_turb_g
Definition: fldvar_mod.f:162
logical granular_energy
Definition: run_mod.f:112
double precision, dimension(:), allocatable ro_g
Definition: fldvar_mod.f:32
double precision, dimension(:), allocatable rop_g
Definition: fldvar_mod.f:38
double precision, dimension(:), allocatable ro_go
Definition: fldvar_mod.f:35