reconstruction_constant.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: reconstruction_constant.f90 #
5!# #
6!# Copyright (C) 2007-2017 #
7!# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8!# Jannes Klee <jklee@astrophysik.uni-kiel.de> #
9!# #
10!# This program is free software; you can redistribute it and/or modify #
11!# it under the terms of the GNU General Public License as published by #
12!# the Free Software Foundation; either version 2 of the License, or (at #
13!# your option) any later version. #
14!# #
15!# This program is distributed in the hope that it will be useful, but #
16!# WITHOUT ANY WARRANTY; without even the implied warranty of #
17!# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
18!# NON INFRINGEMENT. See the GNU General Public License for more #
19!# details. #
20!# #
21!# You should have received a copy of the GNU General Public License #
22!# along with this program; if not, write to the Free Software #
23!# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
24!# #
25!#############################################################################
26!----------------------------------------------------------------------------!
34!----------------------------------------------------------------------------!
41 USE common_dict
42 IMPLICIT NONE
43 !--------------------------------------------------------------------------!
44 PRIVATE
46 ! no data declarations
47 CONTAINS
49 PROCEDURE :: calculatestates
50 PROCEDURE :: finalize
52 !--------------------------------------------------------------------------!
53 CHARACTER(LEN=32), PARAMETER :: recontype_name = "constant"
54 !--------------------------------------------------------------------------!
55 PUBLIC :: &
56 ! types
58 !--------------------------------------------------------------------------!
59
60CONTAINS
61
62 SUBROUTINE initreconstruction_constant(this,Mesh,Physics,config,IO)
63 IMPLICIT NONE
64 !------------------------------------------------------------------------!
65 CLASS(reconstruction_constant), INTENT(INOUT) :: this
66 CLASS(mesh_base), INTENT(IN) :: Mesh
67 CLASS(physics_base), INTENT(IN) :: Physics
68 TYPE(dict_typ),POINTER :: config,IO
69 !-----------------------------------------------------------------------!
70 CALL this%InitReconstruction(mesh,physics,config,io,constant,recontype_name)
71 END SUBROUTINE initreconstruction_constant
72
73
74 SUBROUTINE calculatestates(this,Mesh,Physics,rvar,rstates)
75 IMPLICIT NONE
76 !------------------------------------------------------------------------!
77 CLASS(reconstruction_constant), INTENT(INOUT) :: this
78 CLASS(mesh_base), INTENT(IN) :: Mesh
79 CLASS(physics_base), INTENT(IN) :: Physics
80 CLASS(marray_compound), INTENT(INOUT) :: rvar
81 CLASS(marray_compound), INTENT(INOUT) :: rstates
82 !------------------------------------------------------------------------!
83 INTEGER :: l,n
84 !------------------------------------------------------------------------!
85 ! reconstruct cell face values
86!NEC$ SHORTLOOP
87 DO l=1,physics%VNUM
88!NEC$ SHORTLOOP
89 DO n=1,mesh%NFACES
90 rstates%data3d(:,n,l) = rvar%data2d(:,l)
91 END DO
92 END DO
93 END SUBROUTINE calculatestates
94
95
96 SUBROUTINE finalize(this)
97 IMPLICIT NONE
98 !------------------------------------------------------------------------!
99 CLASS(reconstruction_constant), INTENT(INOUT) :: this
100 !------------------------------------------------------------------------!
101 CALL this%Finalize_base()
102 END SUBROUTINE finalize
103
Dictionary for generic data types.
Definition: common_dict.f90:61
Basic fosite module.
subroutine finalize(this)
Destructor of logging_base class.
derived class for compound of mesh arrays
basic mesh module
Definition: mesh_base.f90:72
Basic physics module.
base module for reconstruction process
integer, parameter, public constant
basic module for constant (zero order) reconstruction
subroutine calculatestates(this, Mesh, Physics, rvar, rstates)
character(len=32), parameter recontype_name
subroutine initreconstruction_constant(this, Mesh, Physics, config, IO)
mesh data structure
Definition: mesh_base.f90:122