gravity_generic.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: gravity_generic.f90 #
5!# #
6!# Copyright (C) 2016-2018 #
7!# Manuel Jung <mjung@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!! \author Jannes Klee
28!!
29!! \brief constructor for gravity class
30!!
31!! This module allocates the gravity class and decides which specific
32!! source to use from the config.
33!----------------------------------------------------------------------------!
43 USE common_dict
44
45CONTAINS
46
47 SUBROUTINE new_gravity(this,Mesh,Fluxes,Physics,config,IO)
48 IMPLICIT NONE
49 !------------------------------------------------------------------------!
50 CLASS(gravity_base), POINTER :: this
51 CLASS(mesh_base) :: Mesh
52 CLASS(fluxes_base) :: Fluxes
53 CLASS(physics_base) :: Physics
54 TYPE(dict_typ), POINTER :: config, IO
55 !------------------------------------------------------------------------!
56 CLASS(gravity_base), POINTER :: newgrav, tmpgrav
57 TYPE(dict_typ), POINTER :: dir,grav,IOgrav
58 INTEGER :: gtype
59 !------------------------------------------------------------------------!
60 dir => config
61 DO WHILE(ASSOCIATED(dir))
62 NULLIFY(iograv)
63 IF (haschild(dir) .AND. (trim(getkey(dir)).NE."output")) THEN
64 grav => getchild(dir)
65 CALL getattr(grav, "gtype", gtype)
66
67 ! object creation
68 SELECT CASE(gtype)
69 CASE(pointmass)
70 ALLOCATE(gravity_pointmass::newgrav)
72 ALLOCATE(gravity_binary::newgrav)
73 CASE(sboxspectral)
74 ALLOCATE(gravity_sboxspectral::newgrav)
75 CASE(spectral)
76 ALLOCATE(gravity_spectral::newgrav)
77 CASE DEFAULT
78 CALL this%Error("new_gravity","Unknown gravity type")
79 END SELECT
80
81 IF (.NOT.ASSOCIATED(this)) THEN
82 this => newgrav
83 NULLIFY(this%next)
84 ELSE
85 tmpgrav => this
86 this => newgrav
87 this%next => tmpgrav
88 END IF
89
90 SELECT TYPE(obj => newgrav)
91 TYPE IS (gravity_pointmass)
92 ! gravitational acceleration due to point mass
93 CALL obj%InitGravity_pointmass(mesh,physics,grav,iograv)
94 TYPE IS (gravity_binary)
95 ! gravitational acceleration due to two circling point masses
96 CALL obj%InitGravity_binary(mesh,physics,grav,iograv)
97 TYPE IS (gravity_sboxspectral)
98 ! self-gravitation in flat geometries periodic in both dimensions
99 CALL obj%InitGravity_sboxspectral(mesh,physics,grav,iograv)
100 TYPE IS (gravity_spectral)
101 ! self-gravitation in flat polar geometries
102 CALL obj%InitGravity_spectral(mesh,physics,grav,iograv)
103 END SELECT
104 IF(ASSOCIATED(iograv)) CALL setattr(io, getkey(dir), iograv)
105 END IF
106 dir => getnext(dir)
107 END DO
108 END SUBROUTINE new_gravity
109
110END MODULE gravity_generic_mod
Dictionary for generic data types.
Definition: common_dict.f90:61
logical function, public haschild(root)
Check if the node 'root' has one or more children.
function, public getkey(root)
Get the key of pointer 'root'.
type(dict_typ) function, pointer, public getnext(root)
Get the pointer to the next child.
type(dict_typ) function, pointer, public getchild(root)
Get the pointer to a direct child of the pointer 'root'.
base module for numerical flux functions
Definition: fluxes_base.f90:39
generic gravity terms module providing functionaly common to all gravity terms
integer, parameter, public spectral
integer, parameter, public pointmass_binary
integer, parameter, public sboxspectral
integer, parameter, public pointmass
source terms module for gravitational acceleration due to two pointmasses
subroutine new_gravity(this, Mesh, Fluxes, Physics, config, IO)
source terms module for gravitational acceleration due to a point mass at the center of the coordinat...
Poisson solver using spectral methods within the shearingbox.
2D poisson solver using spectral methods for direct integration
basic mesh module
Definition: mesh_base.f90:72
Basic physics module.
mesh data structure
Definition: mesh_base.f90:122