CameraObjects: problem.f90

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

problem.f90 for clump example

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 Projections
41 USE Cameras
42 IMPLICIT NONE
43 SAVE
44 PUBLIC ProblemModuleInit, ProblemGridInit, ProblemBeforeStep, &
45 ProblemAfterStep, ProblemSetErrFlag, ProblemBeforeGlobalStep
46 PRIVATE
47 REAL(KIND=qPREC) :: rho, radius
48
49CONTAINS
50
51 SUBROUTINE ProblemModuleInit()
52 TYPE(AmbientDef), POINTER :: Ambient
53 TYPE(ClumpDef), POINTER :: Clump
54 TYPE(ProjectionDef), POINTER :: Projection
55 TYPE(CameraDef), POINTER :: Camera
56 INTEGER :: ncameras, i, res
57 REAL(KIND=qPREC) :: pos(3), focus(3), upvector(3), time, temperature
58 NAMELIST/ProblemData/ rho, radius, ncameras, temperature, res
59 NAMELIST/CameraData/ pos, focus, upvector, time
60 OPEN(UNIT=PROBLEM_DATA_HANDLE, FILE='problem.data', STATUS="OLD")
61 READ(PROBLEM_DATA_HANDLE,NML=ProblemData)
62
63 CALL CreateProjection(Projection)
64 Projection%Field(1)%id=MASS_FIELD
65! CALL CreateCamera(Projection%Camera)
66! Projection%Camera%pos=(/-12,0,-12/)
67! Projection%Camera%UpVector=(/0,1,0/)
68! Projection%Camera%Focus=(/2,0,0/)
69! CALL UpdateCamera(Projection%Camera)
70
71 CALL InitMovie(Projection%Movie, ncameras)
72 Projection%Movie%res=res
73 CALL CreateCamera(Camera)
74 DO i=1, ncameras
75 READ(PROBLEM_DATA_HANDLE, NML=CameraData)
76 Camera%pos=pos
77 Camera%focus=focus
78 Camera%upvector=upvector
79 CALL AddMovieCamera(Projection%Movie, Camera, time)
80 END DO
81 CALL FinalizeMovie(Projection%Movie)
82 CLOSE(PROBLEM_DATA_HANDLE)
83
84 CALL UpdateProjection(Projection)
85
86 CALL CreateAmbient(Ambient)
87
88 CALL CreateClump(Clump)
89 Clump%density=rho
90 Clump%radius=radius
91 Clump%temperature=temperature
92 CALL UpdateClump(Clump)
93
94 END SUBROUTINE
95
96 SUBROUTINE ProblemGridInit(Info)
97 TYPE(InfoDef) :: Info
98 END SUBROUTINE
99
100 SUBROUTINE ProblemBeforeStep(Info)
101 TYPE(InfoDef) :: Info
102 END SUBROUTINE ProblemBeforeStep
103
104 SUBROUTINE ProblemAfterStep(Info)
105 TYPE(InfoDef) :: Info
106 END SUBROUTINE ProblemAfterStep
107
108 SUBROUTINE ProblemSetErrFlag(Info)
109 TYPE(InfoDef) :: Info
110 END SUBROUTINE ProblemSetErrFlag
111
112 SUBROUTINE ProblemBeforeGlobalStep(n)
113 INTEGER :: n
114 END SUBROUTINE ProblemBeforeGlobalStep
115
116END MODULE