boundary_nogradients.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: boundary_nogradients.f90 #
5 !# #
6 !# Copyright (C) 2006-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 
27 !----------------------------------------------------------------------------!
35 !----------------------------------------------------------------------------!
39  USE mesh_base_mod
41  USE common_dict
42  IMPLICIT NONE
43  !--------------------------------------------------------------------------!
44  PRIVATE
46  CONTAINS
48  PROCEDURE :: setboundarydata
49  PROCEDURE :: finalize
50  END TYPE boundary_nogradients
51  CHARACTER(LEN=32), PARAMETER :: boundcond_name = "nogradients"
52  !--------------------------------------------------------------------------!
53  PUBLIC :: &
54  ! types
56  !--------------------------------------------------------------------------!
57 
58 CONTAINS
59 
61  SUBROUTINE initboundary_nogradients(this,Mesh,Physics,dir,config)
62  IMPLICIT NONE
63  !------------------------------------------------------------------------!
64  CLASS(boundary_nogradients), INTENT(INOUT) :: this
65  CLASS(physics_base), INTENT(IN) :: Physics
66  CLASS(mesh_base), INTENT(IN) :: Mesh
67  TYPE(Dict_TYP), POINTER :: config
68  INTEGER :: dir
69  !------------------------------------------------------------------------!
70  INTENT(IN) :: dir
71  !------------------------------------------------------------------------!
72  CALL this%InitBoundary(mesh,physics,no_gradients,boundcond_name,dir,config)
73  END SUBROUTINE initboundary_nogradients
74 
76  PURE SUBROUTINE setboundarydata(this,Mesh,Physics,time,pvar)
77  IMPLICIT NONE
78  !------------------------------------------------------------------------!
79  CLASS(boundary_nogradients), INTENT(INOUT) :: this
80  CLASS(mesh_base), INTENT(IN) :: mesh
81  CLASS(physics_base), INTENT(IN) :: physics
82  REAL, INTENT(IN) :: time
83  CLASS(marray_compound), INTENT(INOUT) :: pvar
84  !------------------------------------------------------------------------!
85  INTEGER :: i,j,k
86  !------------------------------------------------------------------------!
87  SELECT CASE(this%direction%GetType())
88  CASE(west)
89  ! UNROLL=Mesh%GNUM would be sufficient, but the compiler does
90  ! not know the value of Mesh%GNUM, hence we set UNROLL=4 and
91  ! hope that nobody sets Mesh%GNUM to a value greater than 4
92 !NEC$ UNROLL(4)
93  DO i=1,mesh%GINUM
94  pvar%data4d(mesh%IMIN-i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:) = &
95  pvar%data4d(mesh%IMIN,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
96  END DO
97  CASE(east)
98 !NEC$ UNROLL(4)
99  DO i=1,mesh%GINUM
100  pvar%data4d(mesh%IMAX+i,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:) = &
101  pvar%data4d(mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
102  END DO
103  CASE(south)
104 !NEC$ UNROLL(4)
105  DO j=1,mesh%GJNUM
106  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN-j,mesh%KMIN:mesh%KMAX,:) = &
107  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN,mesh%KMIN:mesh%KMAX,:)
108  END DO
109  CASE(north)
110 !NEC$ UNROLL(4)
111  DO j=1,mesh%GJNUM
112  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX+j,mesh%KMIN:mesh%KMAX,:) = &
113  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMAX,mesh%KMIN:mesh%KMAX,:)
114  END DO
115  CASE(bottom)
116 !NEC$ UNROLL(4)
117  DO k=1,mesh%GKNUM
118  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN-k,:) = &
119  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN,:)
120  END DO
121  CASE(top)
122 !NEC$ UNROLL(4)
123  DO k=1,mesh%GKNUM
124  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX+k,:) = &
125  pvar%data4d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMAX,:)
126  END DO
127  END SELECT
128 
129  END SUBROUTINE setboundarydata
130 
132  SUBROUTINE finalize(this)
133  IMPLICIT NONE
134  !------------------------------------------------------------------------!
135  CLASS(boundary_nogradients), INTENT(INOUT) :: this
136  !------------------------------------------------------------------------!
137  CALL this%Finalize_base()
138  END SUBROUTINE finalize
139 
140 END MODULE boundary_nogradients_mod
Boundary module for reflecting boundaries.
type(logging_base), save this
derived class for compound of mesh arrays
subroutine finalize(this)
Destructor for nogradients boundary conditions.
pure subroutine setboundarydata(this, Mesh, Physics, time, pvar)
Applies the nogradients boundary condition.
subroutine initboundary_nogradients(this, Mesh, Physics, dir, config)
Constructor for nogradients boundary conditions.
named integer constants for flavour of state vectors
Basic physics module.
Dictionary for generic data types.
Definition: common_dict.f90:61
character(len=32), parameter boundcond_name