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  !--------------------------------------------------------------------------!
57  PUBLIC :: &
58  ! types
59  constants_si, &
60  c, gn, kb, na, sb, ke
61  !--------------------------------------------------------------------------!
62 
63 CONTAINS
64 
66  SUBROUTINE initconstants_si(this)
67  IMPLICIT NONE
68  !------------------------------------------------------------------------!
69  CLASS(constants_SI), INTENT(INOUT) :: this
70  !------------------------------------------------------------------------!
71  ! assign numerical values of physical constants in SI units;
72  ! (C, GN, etc. are defined in constants_common)
73  this%C = c
74  this%GN = gn
75  this%KB = kb
76  this%NA = na
77  this%SB = sb
78  this%KE = ke
79  ! conversion factors to SI units are unity
80  this%cf_time = 1.0
81  this%cf_mass = 1.0
82  this%cf_momentum = 1.0
83  this%cf_energy = 1.0
84  this%cf_power = 1.0
85  this%cf_temperature = 1.0
86  this%cf_density = 1.0
87  this%cf_opacity = 1.0
88 
89  CALL this%InitConstants(si,units_name)
90  END SUBROUTINE initconstants_si
91 
92 END MODULE constants_si_mod
real, parameter, public sb
Stefan-Boltzmann constant[W/m^2/K^4.
integer, parameter, public si
module for SI units and physical constants
character(len=32), parameter units_name
real, parameter, public ke
electron scattering opacity [m^2/kg]
real, parameter, public na
Avogadro constant [1/mol].
generic module for units and physical constants
real, parameter, public kb
Boltzmann constant[J/K].
subroutine initconstants_si(this)
Constructor of physical constants module using SI units.
physical constants data structure
real, parameter, public c
vacuum speed of light [m/s]
real, parameter, public gn
gravitational constant [m^3/kg/s^2]