boundary_periodic.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: boundary_periodic.f90 #
5 !# #
6 !# Copyright (C) 2006-2014 #
7 !# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8 !# Jubin Lirawi <jlirawi@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 !----------------------------------------------------------------------------!
34 !----------------------------------------------------------------------------!
38  USE mesh_base_mod
40  USE common_dict
41  IMPLICIT NONE
42  !--------------------------------------------------------------------------!
43  PRIVATE
44  TYPE, EXTENDS(boundary_base) :: boundary_periodic
45  CONTAINS
46  PROCEDURE :: initboundary_periodic
47  PROCEDURE :: finalize
48  PROCEDURE :: setboundarydata
49  END TYPE
50  CHARACTER(LEN=32), PARAMETER :: boundcond_name = "periodic"
51  !--------------------------------------------------------------------------!
52  PUBLIC :: boundary_periodic
53  !--------------------------------------------------------------------------!
54 
55 CONTAINS
56 
58  SUBROUTINE initboundary_periodic(this,Mesh,Physics,dir,config)
59  IMPLICIT NONE
60  !------------------------------------------------------------------------!
61  CLASS(boundary_periodic), INTENT(INOUT) :: this
62  CLASS(physics_base), INTENT(IN) :: Physics
63  CLASS(mesh_base), INTENT(IN) :: Mesh
64  TYPE(Dict_TYP),POINTER :: config
65  INTEGER :: dir
66  !------------------------------------------------------------------------!
67  INTENT(IN) :: dir
68  !------------------------------------------------------------------------!
69  CALL this%InitBoundary(mesh,physics,periodic,boundcond_name,dir,config)
70  END SUBROUTINE initboundary_periodic
71 
73  PURE SUBROUTINE setboundarydata(this,Mesh,Physics,time,pvar)
74  IMPLICIT NONE
75  !------------------------------------------------------------------------!
76  CLASS(boundary_periodic), INTENT(INOUT) :: this
77  CLASS(mesh_base), INTENT(IN) :: mesh
78  CLASS(physics_base), INTENT(IN) :: physics
79  REAL, INTENT(IN) :: time
80  CLASS(marray_compound), INTENT(INOUT) :: pvar
81  !------------------------------------------------------------------------!
82  INTEGER :: i,j,k
83  !------------------------------------------------------------------------!
84  SELECT CASE(this%Direction%GetType())
85  CASE(west)
86 !NEC$ IVDEP
87  DO i=1,mesh%GINUM
88  pvar%data4d(mesh%IMIN-i,:,:,:) = pvar%data4d(mesh%IMAX-i+1,:,:,:)
89  END DO
90  CASE(east)
91 !NEC$ IVDEP
92  DO i=1,mesh%GINUM
93  pvar%data4d(mesh%IMAX+i,:,:,:) = pvar%data4d(mesh%IMIN+i-1,:,:,:)
94  END DO
95  CASE(south)
96 !NEC$ IVDEP
97  DO j=1,mesh%GJNUM
98  pvar%data4d(:,mesh%JMIN-j,:,:) = pvar%data4d(:,mesh%JMAX-j+1,:,:)
99  END DO
100  CASE(north)
101 !NEC$ IVDEP
102  DO j=1,mesh%GJNUM
103  pvar%data4d(:,mesh%JMAX+j,:,:) = pvar%data4d(:,mesh%JMIN+j-1,:,:)
104  END DO
105  CASE(bottom)
106 !NEC$ IVDEP
107  DO k=1,mesh%GKNUM
108  pvar%data4d(:,:,mesh%KMIN-k,:) = pvar%data4d(:,:,mesh%KMAX-k+1,:)
109  END DO
110  CASE(top)
111 !NEC$ IVDEP
112  DO k=1,mesh%GKNUM
113  pvar%data4d(:,:,mesh%KMAX+k,:) = pvar%data4d(:,:,mesh%KMIN+k-1,:)
114  END DO
115  END SELECT
116  END SUBROUTINE setboundarydata
117 
118 
120  SUBROUTINE finalize(this)
121  IMPLICIT NONE
122  !------------------------------------------------------------------------!
123  CLASS(boundary_periodic), INTENT(INOUT) :: this
124  !------------------------------------------------------------------------!
125  CALL this%Finalize_base()
126  END SUBROUTINE finalize
127 
128 
129 END MODULE boundary_periodic_mod
subroutine initboundary_periodic(this, Mesh, Physics, dir, config)
Constructor for periodic boundary conditions.
type(logging_base), save this
derived class for compound of mesh arrays
subroutine finalize(this)
Destructor for periodic boundary conditions.
pure subroutine setboundarydata(this, Mesh, Physics, time, pvar)
Applies the periodic boundary condition.
character(len=32), parameter boundcond_name
named integer constants for flavour of state vectors
Basic physics module.
Dictionary for generic data types.
Definition: common_dict.f90:61
Boundary module for periodic boundary conditions.