!######################################################################### ! ! Copyright (C) 2003-2012 Department of Physics and Astronomy, ! University of Rochester, ! Rochester, NY ! ! problem.f90 of module Template is part of AstroBEAR. ! ! AstroBEAR is free software: you can redistribute it and/or modify ! it under the terms of the GNU General Public License as published by ! the Free Software Foundation, either version 3 of the License, or ! (at your option) any later version. ! ! AstroBEAR is distributed in the hope that it will be useful, ! but WITHOUT ANY WARRANTY; without even the implied warranty of ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ! GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License ! along with AstroBEAR. If not, see . ! !######################################################################### !> @dir Template !! @brief Contains files necessary for the Template Calculation !> @file problem.f90 !! @brief Main file for module Problem !> @defgroup Template Template Module !! @brief Module for calculating collapse of a uniform cloud !! @ingroup Modules !> Template Module !! @ingroup Template MODULE Problem USE GlobalDeclarations USE DataDeclarations USE Clumps USE Ambients USE Projections USE Cameras IMPLICIT NONE SAVE PUBLIC ProblemModuleInit, ProblemGridInit, ProblemBeforeStep, & ProblemAfterStep, ProblemSetErrFlag, ProblemBeforeGlobalStep PRIVATE REAL(KIND=qPREC) :: rho, radius CONTAINS SUBROUTINE ProblemModuleInit() TYPE(AmbientDef), POINTER :: Ambient TYPE(ClumpDef), POINTER :: Clump TYPE(ProjectionDef), POINTER :: Projection TYPE(CameraDef), POINTER :: Camera INTEGER :: ncameras, i, res REAL(KIND=qPREC) :: pos(3), focus(3), upvector(3), time, temperature NAMELIST/ProblemData/ rho, radius, ncameras, temperature, res NAMELIST/CameraData/ pos, focus, upvector, time OPEN(UNIT=PROBLEM_DATA_HANDLE, FILE='problem.data', STATUS="OLD") READ(PROBLEM_DATA_HANDLE,NML=ProblemData) CALL CreateProjection(Projection) Projection%Field(1)%id=MASS_FIELD ! CALL CreateCamera(Projection%Camera) ! Projection%Camera%pos=(/-12,0,-12/) ! Projection%Camera%UpVector=(/0,1,0/) ! Projection%Camera%Focus=(/2,0,0/) ! CALL UpdateCamera(Projection%Camera) CALL InitMovie(Projection%Movie, ncameras) Projection%Movie%res=res CALL CreateCamera(Camera) DO i=1, ncameras READ(PROBLEM_DATA_HANDLE, NML=CameraData) Camera%pos=pos Camera%focus=focus Camera%upvector=upvector CALL AddMovieCamera(Projection%Movie, Camera, time) END DO CALL FinalizeMovie(Projection%Movie) CLOSE(PROBLEM_DATA_HANDLE) CALL UpdateProjection(Projection) CALL CreateAmbient(Ambient) CALL CreateClump(Clump) Clump%density=rho Clump%radius=radius Clump%temperature=temperature CALL UpdateClump(Clump) END SUBROUTINE SUBROUTINE ProblemGridInit(Info) TYPE(InfoDef) :: Info END SUBROUTINE SUBROUTINE ProblemBeforeStep(Info) TYPE(InfoDef) :: Info END SUBROUTINE ProblemBeforeStep SUBROUTINE ProblemAfterStep(Info) TYPE(InfoDef) :: Info END SUBROUTINE ProblemAfterStep SUBROUTINE ProblemSetErrFlag(Info) TYPE(InfoDef) :: Info END SUBROUTINE ProblemSetErrFlag SUBROUTINE ProblemBeforeGlobalStep(n) INTEGER :: n END SUBROUTINE ProblemBeforeGlobalStep END MODULE