Blog: Fly through test 1: problem.f90

File problem.f90, 3.6 KB (added by madams, 10 years ago)

problem module used

Line 
1!#########################################################################
2!
3! Copyright (C) 2003-2012 Department of Physics and Astronomy,
4! University of Rochester,
5! Rochester, NY
6!
7! problem.f90 of module Template is part of AstroBEAR.
8!
9! AstroBEAR is free software: you can redistribute it and/or modify
10! it under the terms of the GNU General Public License as published by
11! the Free Software Foundation, either version 3 of the License, or
12! (at your option) any later version.
13!
14! AstroBEAR is distributed in the hope that it will be useful,
15! but WITHOUT ANY WARRANTY; without even the implied warranty of
16! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17! GNU General Public License for more details.
18!
19! You should have received a copy of the GNU General Public License
20! along with AstroBEAR. If not, see <http://www.gnu.org/licenses/>.
21!
22!#########################################################################
23!> @dir Template
24!! @brief Contains files necessary for the Template Calculation
25
26!> @file problem.f90
27!! @brief Main file for module Problem
28
29!> @defgroup Template Template Module
30!! @brief Module for calculating collapse of a uniform cloud
31!! @ingroup Modules
32
33!> Template Module
34!! @ingroup Template
35MODULE Problem
36 USE GlobalDeclarations
37 USE DataDeclarations
38 USE Clumps
39 USE Ambients
40 USE Winds
41 USE Projections
42 USE Cameras
43 IMPLICIT NONE
44 SAVE
45 PUBLIC ProblemModuleInit, ProblemGridInit, ProblemBeforeStep, &
46 ProblemAfterStep, ProblemSetErrFlag, ProblemBeforeGlobalStep
47 PRIVATE
48 REAL(KIND=qPREC) :: rho, radius, velocity
49
50CONTAINS
51
52 SUBROUTINE ProblemModuleInit()
53 TYPE(AmbientDef), POINTER :: Ambient
54 TYPE(ClumpDef), POINTER :: Clump
55 TYPE(WindDef), POINTER :: Wind
56 TYPE(ProjectionDef), POINTER :: Projection
57 TYPE(CameraDef), POINTER :: Camera
58 INTEGER :: ncameras, i
59 REAL(KIND=qPREC) :: pos(3), focus(3), upvector(3), time
60 NAMELIST/ProblemData/ rho, radius, velocity, ncameras
61 NAMELIST/CameraData/ pos, focus, upvector, time
62 OPEN(UNIT=PROBLEM_DATA_HANDLE, FILE='problem.data', STATUS="OLD")
63 READ(PROBLEM_DATA_HANDLE,NML=ProblemData)
64
65 CALL CreateProjection(Projection)
66 Projection%Field(1)%id=MASS_FIELD
67! CALL CreateCamera(Projection%Camera)
68! Projection%Camera%pos=(/-12,0,-12/)
69! Projection%Camera%UpVector=(/0,1,0/)
70! Projection%Camera%Focus=(/2,0,0/)
71! CALL UpdateCamera(Projection%Camera)
72
73 CALL InitMovie(Projection%Movie, ncameras)
74 CALL CreateCamera(Camera)
75 DO i=1, ncameras
76 READ(PROBLEM_DATA_HANDLE, NML=CameraData)
77 Camera%pos=pos
78 Camera%focus=focus
79 Camera%upvector=upvector
80 CALL AddMovieCamera(Projection%Movie, Camera, time)
81 END DO
82 CALL FinalizeMovie(Projection%Movie)
83 CLOSE(PROBLEM_DATA_HANDLE)
84
85! CALL UpdateProjection(Projection)
86
87 CALL CreateAmbient(Ambient)
88
89 CALL CreateClump(Clump)
90 Clump%density=rho
91 Clump%radius=radius
92 CALL UpdateClump(Clump)
93
94 CALL CreateWind(Wind)
95 Wind%velocity=velocity
96 CALL UpdateWind(Wind)
97
98 END SUBROUTINE
99
100 SUBROUTINE ProblemGridInit(Info)
101 TYPE(InfoDef) :: Info
102 END SUBROUTINE
103
104 SUBROUTINE ProblemBeforeStep(Info)
105 TYPE(InfoDef) :: Info
106 END SUBROUTINE ProblemBeforeStep
107
108 SUBROUTINE ProblemAfterStep(Info)
109 TYPE(InfoDef) :: Info
110 END SUBROUTINE ProblemAfterStep
111
112 SUBROUTINE ProblemSetErrFlag(Info)
113 TYPE(InfoDef) :: Info
114 END SUBROUTINE ProblemSetErrFlag
115
116 SUBROUTINE ProblemBeforeGlobalStep(n)
117 INTEGER :: n
118 END SUBROUTINE ProblemBeforeGlobalStep
119
120END MODULE