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-2024 #
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!----------------------------------------------------------------------------!
44 USE common_dict
45 IMPLICIT NONE
46 !--------------------------------------------------------------------------!
47 PRIVATE
48 CHARACTER(LEN=32), PARAMETER :: source_name = "constant acceleration"
49 !--------------------------------------------------------------------------!
50 TYPE, EXTENDS(sources_base) :: sources_c_accel
51 TYPE(marray_base), ALLOCATABLE :: accel
52 CONTAINS
53 PROCEDURE :: initsources
54 PROCEDURE :: externalsources
55 PROCEDURE :: calctimestep
56 final :: finalize
57 END TYPE
58 !--------------------------------------------------------------------------!
59 PUBLIC :: &
60 ! classes
62
63CONTAINS
64
65 SUBROUTINE initsources(this,Mesh,Physics,Fluxes,config,IO)
66 IMPLICIT NONE
67 !------------------------------------------------------------------------!
68 CLASS(sources_c_accel), INTENT(INOUT) :: this
69 CLASS(mesh_base), INTENT(IN) :: Mesh
70 CLASS(physics_base), INTENT(IN) :: Physics
71 CLASS(fluxes_base), INTENT(IN) :: Fluxes
72 TYPE(dict_typ), POINTER :: config, IO
73 !------------------------------------------------------------------------!
74 INTEGER :: k,stype,valwrite
75 REAL :: accel(3)
76 !------------------------------------------------------------------------!
77 CALL getattr(config,"stype",stype)
78 CALL this%InitSources_base(stype,source_name)
79 ALLOCATE(this%accel)
80 this%accel = marray_base(physics%VDIM)
81 this%accel%data1d(:) = 0.0
82
83 ! initialize constant acceleration
84 CALL getattr(config, "xaccel", accel(1), 0.0)
85 CALL getattr(config, "yaccel", accel(2), 0.0)
86 CALL getattr(config, "zaccel", accel(3), 0.0)
87 DO k=1,physics%VDIM
88 this%accel%data2d(:,k) = accel(k)
89 END DO
90
91 ! register acceleration array for output if requested
92 CALL getattr(config, "output/accel", valwrite, 0)
93 IF (valwrite .EQ. 1) &
94 CALL setattr(io, "accel", &
95 this%accel%data3d(mesh%IMIN:mesh%IMAX,mesh%JMIN:mesh%JMAX,mesh%KMIN:mesh%KMAX))
96 END SUBROUTINE initsources
97
98 SUBROUTINE externalsources(this,Mesh,Physics,Fluxes,Sources,time,dt,pvar,cvar,sterm)
99 IMPLICIT NONE
100 !------------------------------------------------------------------------!
101 CLASS(sources_c_accel),INTENT(INOUT):: this
102 CLASS(mesh_base),INTENT(IN) :: Mesh
103 CLASS(physics_base),INTENT(INOUT) :: Physics
104 CLASS(fluxes_base),INTENT(IN) :: Fluxes
105 CLASS(sources_base), INTENT(INOUT) :: Sources
106 REAL,INTENT(IN) :: time, dt
107 CLASS(marray_compound),INTENT(INOUT):: pvar,cvar,sterm
108 !------------------------------------------------------------------------!
109 ! compute source terms due to constant acceleration
110 CALL physics%ExternalSources(this%accel,pvar,cvar,sterm)
111 END SUBROUTINE externalsources
112
113 SUBROUTINE calctimestep(this,Mesh,Physics,Fluxes,pvar,cvar,time,dt,dtcause)
114 IMPLICIT NONE
115 !------------------------------------------------------------------------!
116 CLASS(sources_c_accel), INTENT(INOUT) :: this
117 CLASS(mesh_base), INTENT(IN) :: Mesh
118 CLASS(physics_base), INTENT(INOUT) :: Physics
119 CLASS(fluxes_base), INTENT(IN) :: Fluxes
120 CLASS(marray_compound), INTENT(INOUT) :: pvar,cvar
121 REAL, INTENT(IN) :: time
122 REAL, INTENT(INOUT) :: dt
123 INTEGER, INTENT(OUT) :: dtcause
124 !------------------------------------------------------------------------!
125 dt = huge(dt)
126 END SUBROUTINE calctimestep
127
128 SUBROUTINE finalize(this)
129 IMPLICIT NONE
130 !------------------------------------------------------------------------!
131 TYPE(sources_c_accel), INTENT(INOUT) :: this
132 !------------------------------------------------------------------------!
133 IF (ALLOCATED(this%accel)) DEALLOCATE(this%accel)
134 END SUBROUTINE finalize
135
136END MODULE sources_c_accel_mod
Dictionary for generic data types.
Definition: common_dict.f90:61
base module for numerical flux functions
Definition: fluxes_base.f90:39
base class for mesh arrays
Definition: marray_base.f90:36
subroutine finalize(this)
derived class for compound of mesh arrays
basic mesh module
Definition: mesh_base.f90:72
Basic physics module.
generic source terms module providing functionaly common to all source terms
source terms module for constant acceleration
character(len=32), parameter source_name
subroutine calctimestep(this, Mesh, Physics, Fluxes, pvar, cvar, time, dt, dtcause)
subroutine externalsources(this, Mesh, Physics, Fluxes, Sources, time, dt, pvar, cvar, sterm)
subroutine initsources(this, Mesh, Physics, Fluxes, config, IO)
basic mesh array class
Definition: marray_base.f90:69
mesh data structure
Definition: mesh_base.f90:122