constants_cgs.f90
Go to the documentation of this file.
1 !#############################################################################
2 !# #
3 !# fosite - 3D hydrodynamical simulation program #
4 !# module: constants_cgs.f90 #
5 !# #
6 !# Copyright (C) 2007-2018 #
7 !# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8 !# Jannes Klee <jklee@astrophysik.uni-kiel.de> #
9 !# #
10 !# This program is free software; you can redistribute it and/or modify #
11 !# it under the terms of the GNU General Public License as published by #
12 !# the Free Software Foundation; either version 2 of the License, or (at #
13 !# your option) any later version. #
14 !# #
15 !# This program is distributed in the hope that it will be useful, but #
16 !# WITHOUT ANY WARRANTY; without even the implied warranty of #
17 !# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
18 !# NON INFRINGEMENT. See the GNU General Public License for more #
19 !# details. #
20 !# #
21 !# You should have received a copy of the GNU General Public License #
22 !# along with this program; if not, write to the Free Software #
23 !# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
24 !# #
25 !#############################################################################
26 
27 !----------------------------------------------------------------------------!
34 !----------------------------------------------------------------------------!
38  IMPLICIT NONE
39  !--------------------------------------------------------------------------!
40  PRIVATE
41  TYPE, EXTENDS(constants_si) :: constants_cgs
42  CONTAINS
43  PROCEDURE :: initconstants_cgs
44  END TYPE
45  CHARACTER(LEN=32), PARAMETER :: units_name = 'cgs'
46  !--------------------------------------------------------------------------!
47  PUBLIC :: &
48  ! classes
50  !--------------------------------------------------------------------------!
51 
52 CONTAINS
53 
55  SUBROUTINE initconstants_cgs(this)
56  IMPLICIT NONE
57  !------------------------------------------------------------------------!
58  CLASS(constants_cgs), INTENT(INOUT) :: this
59  !------------------------------------------------------------------------!
60  ! assign numerical values of physical constants in cgs units;
61  this%C = c*1.0e2
62  this%GN = gn*1.0e3
63  this%KB = kb*1.0e7
64  this%NA = na
65  this%SB = sb*1.0e3
66  this%KE = ke*1.0e1
67  ! conversion factors to from SI to cgs
68  this%cf_time = 1.0
69  this%cf_mass = 1.0e3
70  this%cf_momentum = 1.0e5
71  this%cf_energy = 1.0e7
72  this%cf_power = 1.0e7
73  this%cf_temperature = 1.0
74  this%cf_density = 1.0e-3
75  this%cf_opacity = 1.0e1
76 
77  CALL this%InitConstants(cgs,units_name)
78  END SUBROUTINE initconstants_cgs
79 
80 END MODULE constants_cgs_mod
module for cgs units and physical constants
real, parameter, public sb
Stefan-Boltzmann constant[W/m^2/K^4.
module for SI units and physical constants
real, parameter, public ke
electron scattering opacity [m^2/kg]
subroutine initconstants_cgs(this)
Constructor of physical constants module using cgs units.
real, parameter, public na
Avogadro constant [1/mol].
generic module for units and physical constants
real, parameter, public kb
Boltzmann constant[J/K].
real, parameter, public c
vacuum speed of light [m/s]
character(len=32), parameter units_name
real, parameter, public gn
gravitational constant [m^3/kg/s^2]
integer, parameter, public cgs