geometry_generic.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: geometry_generic.f90 #
5!# #
6!# Copyright (C) 2016 Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
7!# Jannes Klee <jklee@astrophysik.uni-kiel.de> #
8!# Manuel Jung <mjung@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!----------------------------------------------------------------------------!
44 USE common_dict
45
46! INTERFACE geometry_base
47! MODULE PROCEDURE new_geometry
48! END INTERFACE
49
50CONTAINS
51
52 SUBROUTINE new_geometry(Geometry,config)
53 IMPLICIT NONE
54 !------------------------------------------------------------------------!
55 CLASS(geometry_base), ALLOCATABLE :: Geometry
56 TYPE(dict_typ), POINTER :: config
57 !------------------------------------------------------------------------!
58 INTEGER :: geometry_type
59 !------------------------------------------------------------------------!
60 CALL getattr(config,"geometry",geometry_type)
61 ! allocate data
62 SELECT CASE(geometry_type)
63 CASE(cartesian)
64 ALLOCATE(geometry_cartesian::geometry)
65 CASE(cylindrical)
66 ALLOCATE(geometry_cylindrical::geometry)
67 CASE(logcylindrical)
68 ALLOCATE(geometry_logcylindrical::geometry)
69 CASE(tancylindrical)
70 ALLOCATE(geometry_tancylindrical::geometry)
71 CASE(logspherical)
72 ALLOCATE(geometry_logspherical::geometry)
73 CASE(spherical)
74 ALLOCATE(geometry_spherical::geometry)
76 ALLOCATE(geometry_spherical_planet::geometry)
77 CASE DEFAULT
78 CALL geometry%Error("new_geometry","Unknown geometry")
79 END SELECT
80
81 ! call initialization
82 SELECT TYPE(geometry_child => geometry)
83 TYPE IS (geometry_cartesian)
84 CALL geometry_child%InitGeometry_cartesian(config)
85 TYPE IS (geometry_cylindrical)
86 CALL geometry_child%InitGeometry_cylindrical(config)
88 CALL geometry_child%InitGeometry_logcylindrical(config)
90 CALL geometry_child%InitGeometry_tancylindrical(config)
91 TYPE IS (geometry_logspherical)
92 CALL geometry_child%InitGeometry_logspherical(config)
93 TYPE IS (geometry_spherical)
94 CALL geometry_child%InitGeometry_spherical(config)
96 CALL geometry_child%InitGeometry_spherical_planet(config)
97 END SELECT
98 END SUBROUTINE
99END MODULE geometry_generic_mod
Dictionary for generic data types.
Definition: common_dict.f90:61
base class for geometrical properties
integer, parameter, public spherical
integer, parameter, public tancylindrical
integer, parameter, public cartesian
integer, parameter, public cylindrical
integer, parameter, public logcylindrical
integer, parameter, public spherical_planet
integer, parameter, public logspherical
defines properties of a 3D cartesian mesh
defines properties of a 3D cylindrical mesh
constructor for geometry class
subroutine new_geometry(Geometry, config)
defines properties of a 3D logcylindrical mesh
defines properties of a 3D logspherical mesh
defines properties of a 3D spherical mesh
defines properties of a 3D spherical mesh
define properties of a 3D tancylindrical mesh