fileio_generic.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: fileio_generic.f90 #
5!# #
6!# Copyright (C) 2015-2024 #
7!# Manuel Jung <mjung@astrophysik.uni-kiel.de> #
8!# Jannes Klee <jklee@astrophysik.uni-kiel.de> #
9!# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
10!# #
11!# This program is free software; you can redistribute it and/or modify #
12!# it under the terms of the GNU General Public License as published by #
13!# the Free Software Foundation; either version 2 of the License, or (at #
14!# your option) any later version. #
15!# #
16!# This program is distributed in the hope that it will be useful, but #
17!# WITHOUT ANY WARRANTY; without even the implied warranty of #
18!# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
19!# NON INFRINGEMENT. See the GNU General Public License for more #
20!# details. #
21!# #
22!# You should have received a copy of the GNU General Public License #
23!# along with this program; if not, write to the Free Software #
24!# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
25!# #
26!#############################################################################
27!----------------------------------------------------------------------------!
36!----------------------------------------------------------------------------!
47 USE common_dict
48
49CONTAINS
50
52 SUBROUTINE new_fileio(Fileio,Mesh,Physics,Timedisc,Sources,config,IO)
53 IMPLICIT NONE
54 !------------------------------------------------------------------------!
55 CLASS(fileio_base), ALLOCATABLE :: Fileio
56 CLASS(mesh_base), INTENT(IN) :: Mesh
57 CLASS(physics_base), INTENT(IN) :: Physics
58 CLASS(timedisc_base), INTENT(IN) :: Timedisc
59 CLASS(sources_list), ALLOCATABLE, INTENT(IN) :: Sources
60 TYPE(dict_typ), INTENT(IN), POINTER :: config
61 TYPE(dict_typ), INTENT(IN), POINTER :: IO
62 !------------------------------------------------------------------------!
63 INTEGER :: fileformat
64 !------------------------------------------------------------------------!
65 CALL getattr(config,"fileformat",fileformat)
66
67 ! allocate data
68 SELECT CASE(fileformat)
69 CASE(gnuplot)
70 ALLOCATE(fileio_gnuplot::fileio)
71 CASE(vtk)
72 ALLOCATE(fileio_vtk::fileio)
73 CASE(binary)
74 ALLOCATE(fileio_binary::fileio)
75 CASE(xdmf)
76 ALLOCATE(fileio_xdmf::fileio)
77 CASE DEFAULT
78 CALL fileio%Error("new_fileio","Unknown filetype.")
79 END SELECT
80
81 ! call initialization
82 CALL fileio%InitFileIO(mesh,physics,timedisc,sources,config,io)
83 END SUBROUTINE
84
85END MODULE fileio_generic_mod
Dictionary for generic data types.
Definition: common_dict.f90:61
Generic file I/O module.
Definition: fileio_base.f90:54
integer, parameter, public xdmf
integer, parameter, public vtk
integer, parameter, public gnuplot
integer, parameter, public binary
file I/O types
module for binary file I/O
constructor for fileio class
subroutine new_fileio(Fileio, Mesh, Physics, Timedisc, Sources, config, IO)
constructor for FileIO class
I/O for GNUPLOT readable tabular files.
I/O for VTK files in XML format (vtkStructuredGrid)
Definition: fileio_vtk.f90:52
module for XDMF file I/O
Definition: fileio_xdmf.f90:52
basic mesh module
Definition: mesh_base.f90:72
Basic physics module.
module to manage list of source terms
FileIO class for VTK output.
Definition: fileio_vtk.f90:108
FileIO gnuplot class.
Definition: fileio_xdmf.f90:70
mesh data structure
Definition: mesh_base.f90:122
container class to manage the list of source terms