sources_c_accel.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: sources_c_accel.f90 #
5 !# #
6 !# Copyright (C) 2009-2019 #
7 !# Björn Sperling <sperling@astrophysik.uni-kiel.de> #
8 !# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
9 !# Jannes Klee <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 !----------------------------------------------------------------------------!
39  USE fluxes_base_mod
41  USE mesh_base_mod
42  USE marray_base_mod
44  USE common_dict
45  IMPLICIT NONE
46  !--------------------------------------------------------------------------!
47  PRIVATE
48  CHARACTER(LEN=32) :: source_name = "constant acceleration"
49 
50  TYPE, EXTENDS(sources_base) :: sources_c_accel
51  TYPE(marray_base) :: accel
52  CONTAINS
53  PROCEDURE :: initsources_c_accel
55  PROCEDURE :: calctimestep_single
56  PROCEDURE :: infosources
57  PROCEDURE :: finalize
58  END TYPE
59 
60  PUBLIC :: &
61  ! classes
63 
64 CONTAINS
65 
66  SUBROUTINE initsources_c_accel(this,Mesh,Physics,Fluxes,config,IO)
67  IMPLICIT NONE
68  !------------------------------------------------------------------------!
69  CLASS(sources_c_accel), INTENT(INOUT) :: this
70  CLASS(mesh_base), INTENT(IN) :: Mesh
71  CLASS(fluxes_base), INTENT(IN) :: Fluxes
72  CLASS(physics_base), INTENT(IN) :: Physics
73  TYPE(Dict_TYP), POINTER :: config, IO
74  !------------------------------------------------------------------------!
75  INTEGER :: k,stype
76  REAL :: accel(3)
77  !------------------------------------------------------------------------!
78  CALL getattr(config,"stype",stype)
79  CALL this%InitLogging(stype,source_name)
80  CALL this%InitSources(mesh,fluxes,physics,config,io)
81 
82  this%accel = marray_base(physics%VDIM)
83  this%accel%data1d(:) = 0.0
84 
85  ! initialize constant acceleration
86  CALL getattr(config, "xaccel", accel(1), 0.0)
87  CALL getattr(config, "yaccel", accel(2), 0.0)
88  CALL getattr(config, "zaccel", accel(3), 0.0)
89  DO k=1,physics%VDIM
90  this%accel%data2d(:,k) = accel(k)
91  END DO
92 
93  END SUBROUTINE initsources_c_accel
94 
95  SUBROUTINE externalsources_single(this,Mesh,Physics,Fluxes,Sources,time,dt,pvar,cvar,sterm)
96  IMPLICIT NONE
97  !------------------------------------------------------------------------!
98  CLASS(sources_c_accel),INTENT(INOUT):: this
99  CLASS(mesh_base),INTENT(IN) :: Mesh
100  CLASS(physics_base),INTENT(INOUT) :: Physics
101  CLASS(fluxes_base),INTENT(IN) :: Fluxes
102  CLASS(sources_base), INTENT(INOUT) :: Sources
103  REAL,INTENT(IN) :: time, dt
104  CLASS(marray_compound),INTENT(INOUT):: pvar,cvar,sterm
105  !------------------------------------------------------------------------!
106  ! compute source terms due to constant acceleration
107  CALL physics%ExternalSources(this%accel,pvar,cvar,sterm)
108  END SUBROUTINE
109 
110  SUBROUTINE calctimestep_single(this,Mesh,Physics,Fluxes,pvar,cvar,time,dt)
111  IMPLICIT NONE
112  !------------------------------------------------------------------------!
113  CLASS(sources_c_accel), INTENT(INOUT) :: this
114  CLASS(mesh_base), INTENT(IN) :: Mesh
115  CLASS(physics_base), INTENT(INOUT) :: Physics
116  CLASS(fluxes_base), INTENT(IN) :: Fluxes
117  CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
118  REAL, INTENT(IN) :: time
119  REAL, INTENT(OUT) :: dt
120  !------------------------------------------------------------------------!
121  dt = huge(dt)
122  END SUBROUTINE calctimestep_single
123 
124  SUBROUTINE infosources(this,Mesh)
125  IMPLICIT NONE
126  !------------------------------------------------------------------------!
127  CLASS(sources_c_accel), INTENT(IN) :: this
128  CLASS(mesh_base), INTENT(IN) :: Mesh
129  !------------------------------------------------------------------------!
130  END SUBROUTINE infosources
131 
132  SUBROUTINE finalize(this)
133  IMPLICIT NONE
134  !------------------------------------------------------------------------!
135  CLASS(sources_c_accel), INTENT(INOUT) :: this
136  !------------------------------------------------------------------------!
137  CALL this%accel%Destroy()
138  END SUBROUTINE finalize
139 
140 END MODULE sources_c_accel_mod
subroutine infosources(this, Mesh)
generic source terms module providing functionaly common to all source terms
source terms module for constant acceleration
derived class for compound of mesh arrays
base class for mesh arrays
Definition: marray_base.f90:36
character(len=32) source_name
subroutine initsources_c_accel(this, Mesh, Physics, Fluxes, config, IO)
basic mesh array class
Definition: marray_base.f90:64
subroutine finalize(this)
Basic physics module.
Dictionary for generic data types.
Definition: common_dict.f90:61
subroutine calctimestep_single(this, Mesh, Physics, Fluxes, pvar, cvar, time, dt)
base module for numerical flux functions
Definition: fluxes_base.f90:39
subroutine externalsources_single(this, Mesh, Physics, Fluxes, Sources, time, dt, pvar, cvar, sterm)