constants_SI.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: constants_SI.f90 #
5!# #
6!# Copyright (C) 2007-2016 #
7!# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
8!# Manuel Jung <mjung@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!----------------------------------------------------------------------------!
35!----------------------------------------------------------------------------!
38 IMPLICIT NONE
39 !--------------------------------------------------------------------------!
40 PRIVATE
41 TYPE, EXTENDS(constants_base) :: constants_si
42 CONTAINS
43 PROCEDURE :: initconstants_si
44 END TYPE
45 CHARACTER(LEN=32), PARAMETER :: units_name = 'SI'
46 !--------------------------------------------------------------------------!
47 ! basic numerical constants
48 !!#### Physical constants in SI units
49 REAL, PARAMETER :: &
50 c = 2.99792458e+08, &
51 gn = 6.6742e-11, &
52 kb = 1.3806505e-23, &
53 na = 6.022e+23, &
54 sb = 5.6704e-8, &
55 ke = 3.48e-02, &
56 au = 1.49597870691d+11, &
57 msun = 1.9885d+30, &
58 mjupiter = 1.89819d+27, &
59 mearth = 5.9723d+24, &
60 rsun = 6.957e+8, &
61 rjupiter = 6.9911e+7, &
62 rearth = 6.371e+6, &
63 day = 8.64e+4, &
64 pi = 3.1415926535897932384626433832795028842
65 !--------------------------------------------------------------------------!
66 PUBLIC :: &
67 ! types
69 c, gn, kb, na, sb, ke, au, &
71 !--------------------------------------------------------------------------!
72
73CONTAINS
74
76 SUBROUTINE initconstants_si(this)
77 IMPLICIT NONE
78 !------------------------------------------------------------------------!
79 CLASS(constants_si), INTENT(INOUT) :: this
80 !------------------------------------------------------------------------!
81 ! assign numerical values of physical constants in SI units;
82 ! (C, GN, etc. are defined in constants_common)
83 this%C = c
84 this%GN = gn
85 this%KB = kb
86 this%NA = na
87 this%SB = sb
88 this%KE = ke
89 this%AU = au
90 this%MSUN = msun
91 this%MJUPITER = mjupiter
92 this%MEARTH = mearth
93 this%RSUN = rsun
94 this%RJUPITER = rjupiter
95 this%REARTH = rearth
96 this%DAY = day
97 this%PI = pi
98 ! conversion factors to SI units are unity
99 this%cf_time = 1.0
100 this%cf_mass = 1.0
101 this%cf_momentum = 1.0
102 this%cf_energy = 1.0
103 this%cf_power = 1.0
104 this%cf_temperature = 1.0
105 this%cf_density = 1.0
106 this%cf_opacity = 1.0
107
108 CALL this%InitConstants(si,units_name)
109 END SUBROUTINE initconstants_si
110
111END MODULE constants_si_mod
generic module for units and physical constants
integer, parameter, public si
module for SI units and physical constants
subroutine initconstants_si(this)
Constructor of physical constants module using SI units.
real, parameter, public mjupiter
jupiter mass [kg]
real, parameter, public mearth
earth mass [kg]
real, parameter, public gn
gravitational constant [m^3/kg/s^2]
real, parameter, public rsun
sun radius [m]
real, parameter, public ke
electron scattering opacity [m^2/kg]
real, parameter, public c
vacuum speed of light [m/s]
real, parameter, public day
length of a day [s]
character(len=32), parameter units_name
real, parameter, public sb
Stefan-Boltzmann constant [W/m^2/K^4].
real, parameter, public au
astronomical unit [m]
real, parameter, public na
Avogadro constant [1/mol].
real, parameter, public kb
Boltzmann constant [J/K].
real, parameter, public pi
real, parameter, public rjupiter
jupiter radius [m]
real, parameter, public rearth
earth radius [m]
real, parameter, public msun
sun mass [kg]
physical constants data structure