Skip to content

Commit 6b925cb

Browse files
author
Damian Rouson
authored
Merge pull request #18 from sourceryinstitute/units-tracking
Add runtime units-tracking utility
2 parents b533141 + dd80916 commit 6b925cb

File tree

2 files changed

+381
-0
lines changed

2 files changed

+381
-0
lines changed

src/units_implementation.F90

Lines changed: 130 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,130 @@
1+
!
2+
! (c) 2019-2020 Guide Star Engineering, LLC
3+
! This Software was developed for the US Nuclear Regulatory Commission (US NRC) under contract
4+
! "Multi-Dimensional Physics Implementation into Fuel Analysis under Steady-state and Transients (FAST)",
5+
! contract # NRC-HQ-60-17-C-0007
6+
!
7+
submodule(units_interface) units_implementation
8+
use assertions_interface, only : assertions,assert
9+
implicit none
10+
11+
contains
12+
13+
module procedure set_units
14+
!! define units exponents
15+
this%exponents_ = exponents
16+
this%system= system
17+
end procedure
18+
19+
module procedure get_system
20+
system_of_units = this%system
21+
end procedure
22+
23+
module procedure get_units
24+
exponents = this%exponents_
25+
end procedure
26+
27+
module procedure assign_units
28+
lhs%exponents_ = rhs%exponents_
29+
lhs%system = rhs%system
30+
end procedure
31+
32+
module procedure is_dimensionless
33+
nondimensional = all([this%exponents_==0]) .and. this%system==dimensionless
34+
end procedure
35+
36+
module procedure has_length_units
37+
length_units = this%exponents_(m)==1 .and. all(this%exponents_([kg,sec,K])==0)
38+
end procedure
39+
40+
module procedure has_mass_units
41+
mass_units = this%exponents_(kg)==1 .and. all(this%exponents_([m,sec,K])==0)
42+
end procedure
43+
44+
module procedure has_time_units
45+
time_units = this%exponents_(sec)==1 .and. all(this%exponents_([m,kg,K])==0)
46+
end procedure
47+
48+
module procedure has_temperature_units
49+
temperature_units = this%exponents_(K)==1 .and. all(this%exponents_([m,kg,sec])==0)
50+
end procedure
51+
52+
module procedure has_velocity_units
53+
velocity_units = all(this%exponents_([m,sec])==[1,-1]) .and. all(this%exponents_([kg,K])==0)
54+
end procedure
55+
56+
module procedure has_energy_units
57+
energy_units = all(this%exponents_([kg,m,sec])==[1,2,-2]) .and. this%exponents_(K)==0
58+
end procedure
59+
60+
module procedure has_density_units
61+
density_units = all(this%exponents_([kg,m])==[1,-3]) .and. all(this%exponents_([sec,K])==0)
62+
end procedure
63+
64+
module procedure has_specific_energy_units
65+
specific_energy_units = all(this%exponents_([m,sec])==[2,-2]) .and. all(this%exponents_([kg,K])==0)
66+
end procedure
67+
68+
module procedure has_stress_units
69+
stress_units = all(this%exponents_([kg,m,sec])==[1,-1,-2]) .and. this%exponents_(K)==0
70+
end procedure
71+
72+
module procedure has_power_units
73+
power_units = all(this%exponents_([kg,m,sec])==[1,2,-3]) .and. this%exponents_(K)==0
74+
end procedure
75+
76+
module procedure integer_power
77+
this_raised%system = this%system
78+
this_raised%exponents_ = exponent_*this%exponents_
79+
end procedure
80+
81+
module procedure real_power
82+
if (assertions) call assert(this%is_dimensionless(), &
83+
& "units%real_power: an entity raised to a real power must be dimensionless")
84+
!! Require dimensionless operand => result is default-initialized as dimensionless
85+
end procedure
86+
87+
module procedure negate
88+
negative_this%exponents_ = this%exponents_
89+
negative_this%system= this%system
90+
end procedure
91+
92+
module procedure add
93+
if (assertions) then
94+
!! Require consistent operand units
95+
associate(preconditions => [lhs%system==rhs%system, lhs%exponents_==rhs%exponents_] )
96+
call assert( all(preconditions), "units%add: consistent operands units")
97+
end associate
98+
end if
99+
total%exponents_ = lhs%exponents_
100+
total%system = lhs%system
101+
end procedure
102+
103+
module procedure subtract
104+
if (assertions) then
105+
!! Require consistent operand units
106+
associate(preconditions => [lhs%system==rhs%system, lhs%exponents_==rhs%exponents_] )
107+
call assert( all(preconditions), "units%subtract: consistent operand units")
108+
end associate
109+
end if
110+
difference%exponents_ = lhs%exponents_
111+
difference%system = lhs%system
112+
end procedure
113+
114+
module procedure multiply
115+
116+
if (assertions) call assert( lhs%system==rhs%system, "units%multiply: consistent operand units" )
117+
118+
product_%exponents_ = lhs%exponents_ + rhs%exponents_
119+
product_%system = lhs%system
120+
end procedure
121+
122+
module procedure divide
123+
124+
if (assertions) call assert( numerator%system==denominator%system, "units%divide: consistent operand units" )
125+
126+
ratio%exponents_ = numerator%exponents_ - denominator%exponents_
127+
ratio%system = merge(numerator%system,dimensionless,any(ratio%exponents_/=0))
128+
end procedure
129+
130+
end submodule units_implementation

src/units_interface.F90

Lines changed: 251 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,251 @@
1+
!
2+
! (c) 2019-2020 Guide Star Engineering, LLC
3+
! This Software was developed for the US Nuclear Regulatory Commission (US NRC) under contract
4+
! "Multi-Dimensional Physics Implementation into Fuel Analysis under Steady-state and Transients (FAST)",
5+
! contract # NRC-HQ-60-17-C-0007
6+
!
7+
module units_interface
8+
!! author: Damian Rouson
9+
!! date: 9/9/2019
10+
!!
11+
!! Define SI and British units of measurement and associated arithmetic operators
12+
implicit none
13+
14+
private
15+
public :: units
16+
public :: K, m, kg, sec
17+
public :: R, ft, lbm
18+
public :: dimensionless, SI, British
19+
public :: num_fundamental
20+
public :: units_system_names
21+
public :: SI_units_names, British_units_names
22+
23+
enum, bind(C)
24+
!! Enumerate the fundamental units for dimensional units quantities
25+
!! (meters, kilograms, seconds, and degrees Kelvin)
26+
enumerator :: K=1, m, kg, sec
27+
enumerator :: R=1, ft, lbm
28+
enumerator :: dimensionless=0, SI, British
29+
end enum
30+
31+
integer, parameter :: num_fundamental=4, num_systems=2
32+
character(len=*), parameter :: units_system_names(num_systems)=[character(len=len("British")) :: "SI","British"]
33+
character(len=*), parameter :: SI_units_names(num_fundamental)=[character(len=len("sec")) :: "K", "m", "kg", "sec"]
34+
character(len=*), parameter :: British_units_names(num_fundamental)=[character(len=len("sec")) :: "R", "ft", "lbm", "sec"]
35+
36+
type units
37+
!! Morfeus universal base type for all units
38+
private
39+
integer :: exponents_(num_fundamental)=dimensionless !! Store the exponents for fundamental units
40+
integer :: system=dimensionless !! Default to SI units
41+
character(len=:), allocatable :: description
42+
contains
43+
procedure :: set_units
44+
procedure :: get_units
45+
procedure :: get_system
46+
procedure :: is_dimensionless
47+
procedure :: has_length_units
48+
procedure :: has_mass_units
49+
procedure :: has_time_units
50+
procedure :: has_temperature_units
51+
procedure :: has_velocity_units
52+
procedure :: has_energy_units
53+
procedure :: has_density_units
54+
procedure :: has_specific_energy_units
55+
procedure :: has_stress_units
56+
procedure :: has_power_units
57+
procedure :: add
58+
procedure :: multiply
59+
procedure :: divide
60+
procedure :: subtract,negate
61+
procedure :: integer_power
62+
procedure :: real_power
63+
procedure :: assign_units
64+
#ifndef FORD
65+
generic :: operator(+)=>add
66+
generic :: operator(*)=>multiply
67+
generic :: operator(/)=>divide
68+
generic :: operator(-)=>subtract,negate
69+
generic :: operator(**)=>integer_power,real_power
70+
generic :: assignment(=)=>assign_units
71+
#endif
72+
end type
73+
74+
interface
75+
76+
pure module subroutine set_units(this,exponents,system)
77+
!! define units
78+
implicit none
79+
class(units), intent(inout) :: this
80+
integer, intent(in) :: exponents(num_fundamental)
81+
integer, intent(in) :: system
82+
end subroutine
83+
84+
pure module subroutine assign_units(lhs,rhs)
85+
!! copy units information
86+
implicit none
87+
class(units), intent(inout) :: lhs
88+
class(units), intent(in) :: rhs
89+
end subroutine
90+
91+
#ifndef HAVE_ERROR_STOP_IN_PURE
92+
impure &
93+
#endif
94+
elemental module function integer_power(this,exponent_) result(this_raised)
95+
!! result has units of the opearand raised to the power "exponent_"
96+
implicit none
97+
class(units), intent(in) :: this
98+
integer, intent(in) :: exponent_
99+
type(units) :: this_raised
100+
end function
101+
102+
module function get_units(this) result(exponents)
103+
!! result holds the exponents of each unit in the argument (most useful when the actual argument is an expression)
104+
implicit none
105+
class(units), intent(in) :: this
106+
integer :: exponents(num_fundamental)
107+
end function
108+
109+
#ifndef HAVE_ERROR_STOP_IN_PURE
110+
impure &
111+
#endif
112+
elemental module function get_system(this) result(system_of_units)
113+
!! result is enumerated value designating units system
114+
implicit none
115+
class(units), intent(in) :: this
116+
integer :: system_of_units
117+
end function
118+
119+
120+
#ifndef HAVE_ERROR_STOP_IN_PURE
121+
impure &
122+
#endif
123+
elemental module function real_power(this,exponent_) result(this_raised)
124+
!! result is the units of the operand raised to the power "exponent_"; includes check that operand is dimensionless
125+
implicit none
126+
class(units), intent(in) :: this
127+
real, intent(in) :: exponent_
128+
type(units) :: this_raised
129+
end function
130+
131+
#ifndef HAVE_ERROR_STOP_IN_PURE
132+
impure &
133+
#endif
134+
elemental module function add(lhs,rhs) result(total)
135+
!! result is the units of the sum of two dimensional quantities; includes operand consistency check
136+
implicit none
137+
class(units), intent(in) :: lhs,rhs
138+
type(units) :: total
139+
end function
140+
141+
#ifndef HAVE_ERROR_STOP_IN_PURE
142+
impure &
143+
#endif
144+
elemental module function subtract(lhs,rhs) result(difference)
145+
!! result is the units of the difference of two dimensional quantities; includes operand consistency check
146+
implicit none
147+
class(units), intent(in) :: lhs,rhs
148+
type(units) :: difference
149+
end function
150+
151+
elemental module function negate(this) result(negative_this)
152+
!! result is the units of the negative of a dimensional quantities
153+
implicit none
154+
class(units), intent(in) :: this
155+
type(units) :: negative_this
156+
end function
157+
158+
elemental module function multiply(lhs,rhs) result(product_)
159+
!! result is the units of the product of two dimensional quantities; includes units-system consistency check
160+
implicit none
161+
class(units), intent(in) :: lhs,rhs
162+
type(units) :: product_
163+
end function
164+
165+
elemental module function divide(numerator,denominator) result(ratio)
166+
!! result is the units of the ratio of two dimensional quantities; includes units-sysetm consistency check
167+
implicit none
168+
class(units), intent(in) :: numerator,denominator
169+
type(units) :: ratio
170+
end function
171+
172+
elemental module function is_dimensionless(this) result(nondimensional)
173+
!! Return true if all units exponents are zero; false otherwise.
174+
implicit none
175+
class(units), intent(in) :: this
176+
logical :: nondimensional
177+
end function
178+
179+
elemental module function has_length_units(this) result(length_units)
180+
!! Return true if units match meters (m)
181+
implicit none
182+
class(units), intent(in) :: this
183+
logical :: length_units
184+
end function
185+
186+
elemental module function has_mass_units(this) result(mass_units)
187+
!! Return true if units match kilograms (kg)
188+
implicit none
189+
class(units), intent(in) :: this
190+
logical :: mass_units
191+
end function
192+
193+
elemental module function has_time_units(this) result(time_units)
194+
!! Return true if units match seconds (s)
195+
implicit none
196+
class(units), intent(in) :: this
197+
logical :: time_units
198+
end function
199+
200+
elemental module function has_temperature_units(this) result(temperature_units)
201+
!! Return true if units match degrees Kelvin (K)
202+
implicit none
203+
class(units), intent(in) :: this
204+
logical :: temperature_units
205+
end function
206+
207+
elemental module function has_velocity_units(this) result(velocity_units)
208+
!! Return true if units match meters/second^2 (m/s^2)
209+
implicit none
210+
class(units), intent(in) :: this
211+
logical :: velocity_units
212+
end function
213+
214+
elemental module function has_energy_units(this) result(energy_units)
215+
!! Return true if units match joules (J)
216+
implicit none
217+
class(units), intent(in) :: this
218+
logical :: energy_units
219+
end function
220+
221+
elemental module function has_density_units(this) result(density_units)
222+
!! Return true if units match kilograms (kg/m^3)
223+
implicit none
224+
class(units), intent(in) :: this
225+
logical :: density_units
226+
end function
227+
228+
elemental module function has_specific_energy_units(this) result(specific_energy_units)
229+
!! Return true if units match Joules per kilogram (J/kg)
230+
implicit none
231+
class(units), intent(in) :: this
232+
logical :: specific_energy_units
233+
end function
234+
235+
elemental module function has_stress_units(this) result(stress_units)
236+
!! Return true if units match Newtons per square meter (N/m^2)
237+
implicit none
238+
class(units), intent(in) :: this
239+
logical :: stress_units
240+
end function
241+
242+
elemental module function has_power_units(this) result(power_units)
243+
!! Return true if units match Watts (W)
244+
implicit none
245+
class(units), intent(in) :: this
246+
logical :: power_units
247+
end function
248+
249+
end interface
250+
251+
end module

0 commit comments

Comments
 (0)