boundary_inner.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: boundary_inner.f90 #
5!# #
6!# Copyright (C) 2006-2018 #
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
27!----------------------------------------------------------------------------!
40!----------------------------------------------------------------------------!
46 USE common_dict
47#ifdef PARALLEL
48#ifdef HAVE_MPI_MOD
49 USE mpi
50#endif
51#endif
52 IMPLICIT NONE
53#ifdef PARALLEL
54#ifdef HAVE_MPIF_H
55 include 'mpif.h'
56#endif
57#endif
58 !--------------------------------------------------------------------------!
59 PRIVATE
60 TYPE, EXTENDS(boundary_base) :: boundary_inner
61 CONTAINS
62 PROCEDURE :: initboundary_inner
63 PROCEDURE :: finalize
64 PROCEDURE :: setboundarydata
65 END TYPE
66 CHARACTER(LEN=32), PARAMETER :: boundcond_name = "none"
67 !--------------------------------------------------------------------------!
68 PUBLIC :: boundary_inner
69 !--------------------------------------------------------------------------!
70
71CONTAINS
72
74 SUBROUTINE initboundary_inner(this,Mesh,Physics,dir,config)
75 IMPLICIT NONE
76 !------------------------------------------------------------------------!
77 CLASS(boundary_inner), INTENT(INOUT) :: this
78 CLASS(physics_base), INTENT(IN) :: Physics
79 CLASS(mesh_base), INTENT(IN) :: Mesh
80 TYPE(dict_typ), POINTER :: config
81 INTEGER :: dir
82 !------------------------------------------------------------------------!
83 INTENT(IN) :: dir
84 !------------------------------------------------------------------------!
85#ifdef PARALLEL
86 CALL this%InitBoundary(mesh,physics,none,boundcond_name,dir,config)
87#endif
88 END SUBROUTINE initboundary_inner
89
93 SUBROUTINE setboundarydata(this,Mesh,Physics,time,pvar)
94 IMPLICIT NONE
95 !------------------------------------------------------------------------!
96 CLASS(boundary_inner), INTENT(INOUT) :: this
97 CLASS(mesh_base), INTENT(IN) :: Mesh
98 CLASS(physics_base), INTENT(IN) :: Physics
99 REAL, INTENT(IN) :: time
100 CLASS(marray_compound), INTENT(INOUT) :: pvar
101 !------------------------------------------------------------------------!
102 ! nothing to do
103 END SUBROUTINE setboundarydata
104
106 SUBROUTINE finalize(this)
107 IMPLICIT NONE
108 !------------------------------------------------------------------------!
109 CLASS(boundary_inner), INTENT(INOUT) :: this
110 !------------------------------------------------------------------------!
111 CALL this%Finalize_base()
112 END SUBROUTINE finalize
113
114
115END MODULE boundary_inner_mod
integer, parameter none
Boundary module for the inner boundaries (only necessary in parallel runs)
character(len=32), parameter boundcond_name
subroutine finalize(this)
Destructor for inner boundary conditions.
subroutine setboundarydata(this, Mesh, Physics, time, pvar)
Applies the inner boundary condition.
subroutine initboundary_inner(this, Mesh, Physics, dir, config)
Constructor for inner boundary conditions.
Dictionary for generic data types.
Definition: common_dict.f90:61
derived class for compound of mesh arrays
basic mesh module
Definition: mesh_base.f90:72
Basic physics module.
mesh data structure
Definition: mesh_base.f90:122