I suggest that you also check out the Julia package Unitful.jl which is the defacto standard package for unit support in Julia. It accommodates both SI and arbitrary units, and supports arithmetic involving quantities with different units, dimensional analysis, etc.
Just to add to the list of languages that considers this problem, Iâve seen units of measure included in F#.
Identifying the use cases up front is critical if only so people can identify which unit issue theyâre trying to resolve. An issue to consider is how solutions for one use case interact with or preclude the solutions of others. For example, would native dimensioned types simplify writing contracts?
This is a much needed effort to clarify what we mean when we say Fortran should handle units. If this was an easy problem, someone would have sorted it out by nowâŚ
As @pmk said, I also always assumed this would be part of the Fortran language, and the compiler checks this at compile time with no runtime overhead. It would be an extension to the type system in a way. I like this idea at this general level. I donât know after syntax is developed and all corner cases handled, if it will be straightforward in the compiler and easy to use for the user. But we should try to implement a prototype in a compiler and play with it.
I agree with @certik and @pmk above.
As a practicing engineer and scientist, already have an inhouse, proprietary, and also user-friendly library solution that is workable. The same situation applies to many other teams and products, particularly in the commercial domains. Thus there is little to no interest in anything different i.e., unless itâs part of the Fortran language and is also compile-time in nature.
In another thread, I am trying to encourage Fortran standard-bearers and its Community to start envisioning enhanced compile-time functionality.
Along the same vein, I encourage anyone interested in the topic of this thread to see this paper by Dos Reis and Stroustrup. See how their vision for enhanced constant expression
support as well as compile-time computing and reduced or zero runtime overheads is enabled as well as illustrated by a scientific use case, the one involving physical quantities and unit-of-measure conversions.
Fortran needs the same kind of visionary thinking and practitionary zeal as those shown by Dos Reis and Stroustrup et al. for other languages. Unfortunately so much of the thinking around Fortran is relentlessly clouded and hampered by a focus on costs rather than better formula translation that consequently helps advance science, technology, engineering, etc. whose benefits to life and the planet are immeasurably positive.
I would hope instead that anything which becomes part of the language will be more fundamental and the notional syntax can be illustrated as
real, physical_quantity(dimension="LMT-2") :: some_force ! or some such representation of dimension of quantities
and later when conversions can be introduced, it may include
real, physical_quantity(dimension="LMT-2",unit="N") :: some_force
Letâs do that.
Maybe unit
instead of units
, but thatâs minor.
Here is a more developed proposal:
This might be enough details to prototype. At this level, these are only used in semantic checking, no code generation will change. One would have to store them in the mod
files. But I think thatâs it.
What are some good use cases for units? I donât have too many right now, but once we have a prototype, people will play with it and create some nice use cases hopefully.
Here is an example to work out:
function laplace(N, Niter, dx, dy) result(u)
integer, intent(in) :: N, Niter
real(dp), intent(in) :: dx, dy
real(dp) :: u(N,N)
integer :: i
u(1,:) = 1
u(2:,:) = 0
do i = 1, Niter
u(2:N-1,2:N-1) = ((u(3:,2:N-1) + u(:N-2,2:N-1))*dy**2 + &
(u(2:N-1,3:) + u(2:N-1,:N-2))*dx**2) / (2*(dx**2 + dy**2))
end do
end function
The u
is a scalar physical quantity, say itâs a temperature, so units will be Kelvin [K]. Here is how it could look like with units
:
function laplace(N, Niter, dx, dy) result(u)
use iso_fortran_units, only: m, K
integer, intent(in) :: N, Niter
real(dp), unit(m), intent(in) :: dx, dy
real(dp), unit(K) :: u(N,N)
integer :: i
u(1,:) = 1
u(2:,:) = 0
do i = 1, Niter
u(2:N-1,2:N-1) = ((u(3:,2:N-1) + u(:N-2,2:N-1))*dy**2 + &
(u(2:N-1,3:) + u(2:N-1,:N-2))*dx**2) / (2*(dx**2 + dy**2))
end do
end function
I can already see some questions:
-
This would work with any units, the array
u
does not have to be a temperature, it could be an electrostatic potential, or something else. The code would not change otherwise. -
The same with
dx
, perhaps they can be inmm
instead ofm
(I think the spacing ofu
must change accordingly, but nothing in this could would change otherwise).
A few ways to generalize:
-
One can set
dx
as unit of length, but can be any unit. -
the unit of
u
can be inferred from the caller (so this becomes a âtemplatedâ or a âgenericâ function in a sense), sinceu
can really be any unit. Alternatively, we can replacereal(dp), unit(K) :: u(N,N)
withreal(dp), unit(*) :: u(N,N)
or something like that. It would still be a strictly a compile time check.
@certik et al.,
Please see upthread:
To point out the very obvious to you, length (L) and temperature (\theta) are two of the seven basic quantities and one would hope Fortran language would first recognize the dimensionality of the physical nature of variables and constants in code including in your Laplace
function example with your illustrative Fortran syntax with the dummy argument definition.
And that units, whether it be m
, ft
, etc. or K
, F
, etc., would follow the dimensional characterization and which would ultimately help with compile-time inclusion of conversion constants, as needed.
@Arjen, unsure if anyone pointed out a long-standing proposal for Fortran by @vsnyder : https://github.com/j3-fortran/fortran_proposals/files/3776442/wishlist.pdf
âPhysicalâ or âEngineeringâ Units of Measure ¡ Issue #50 ¡ j3-fortran/fortran_proposals ¡ GitHub
(apologies if this is a duplicate post)
See this comment by @vsnyder about the background of his âunitsâ proposal:
FWIW, I have read a number of the descriptions referred to here, including the proposal by @vsnyder. Thank you for al lthe reactions. I hope Brad and I can come with a draft paper before my holidays (in a few weeksâ time), so that you can see what - in my perosnal view - complicates matters. In this I agree with @arclight that it is far from clear and that a solution is therefore not trivial, despite all the efforts.
And I realise this is a gargantuan cliffhanger (is that the right word?)
Okay, I have created a repository for this paper. Right now, there is only the raw text, but Brad will add the CI stuff to turn the Latex source into a PDF. It is all very âgreenâ and we have just discuss some of the almost philosophical aspects of the topic. But the outcome was a list of concrete actions.
Iâve gotten the CI set up so you can preview the pdf of the paper here.
As @Arjen mentioned, we discussed some of the âphilosophicalâ aspects, which I will give a brief overview of in terms of some vague requirements.
- A solution should be less strict than having variables declared with specific units for two reasons:
a. A program ought to be able to work with user input in any units (i.e. a variable declared in meters likely couldnât read user input in feet)
b. A library ought not to restrict its users to specific units (i.e. a program to solve the convection equation on domain specified in cm couldnât make use of a solver library written to only work on miles) - A solution should be more strict than tracking the powers of fundamental units at run time. This is to prevent the point the error is reported from diverging from the place a mistake is made. I.e. perhaps the library youâre using needs an acceleration, but you gave it
distance_traveled / time_taken
, you may not see an error reported until trying to output a force but the value is missing an extra second in the denominator. Good luck tracing that bug down.
Our next steps are to put more âmeatâ into our use cases and examples, and express the resulting ârequirementsâ in an easier to understand way. Weâre still open to input from everybody as we continue working.
Have you looked into C++ unit libraries? There appear to be quite a few (list sourced from the LLNL/units README file):
- LLNL/units - A library that provides runtime unit values
- boost units - Zero-overhead dimensional analysis and unit/quantity manipulation and conversion in C++
-
Units - A compile-time, header-only, dimensional analysis library built on
C++14
with no dependencies. - Units - Another compile time library
- PhysUnits-CT - A C++ library for compile-time dimensional analysis and unit/quantity manipulation and conversion.
- PhysUnits-RT - A C++ library for run-time dimensional analysis and unit/quantity manipulation and conversion.
- Libunits - The ultimate shared library to do calculations(!) and conversions with any units! Includes all SI and pseudo SI units and thousands of US, Imperial and other units.
- unitscpp - A lightweight C++ library for physical calculation with units.
- mpusz/units - A compile-time enabled Modern C++ library that provides compile-time dimensional analysis and unit/quantity manipulation.
- bernedom/SI - A header only C++ library that provides type safety and user defined literals for handling physical values defined in the International System of Units
I guess that more than one of these libraries are linked with proposals to the C++ standards comittee (e.g. P1935R0 A C++ Approach to Physical Units). Since C++ shares both programming paradigms and userspace with Fortran, I think itâs important to keep an eye out on what theyâre doing.
We have not made an exhaustive search for them, but at least we have seen mp-units, as well as libraries in Rust, Nim, Ada and other languages. But it is well worth looking into these. Thanks for these references. That does not change much in our observation that seldom attention is paid to the usage patterns: whether a particular approach supports it or not. (See our paper at https://github.com/arjenmarkus/handling-units.)
@Beliavsky : SimCon has a project for Automatic Analysis of Physical Units and Dimensions . I donât know if anything is ready for use.
I am afraid not yet. We have looked at two approaches:
i. Static analysis of the code, inferring the relationships between the units of objects. The user does not need to specify any units, but may do so. The first step is to identify the separate lives of symbols - see: http://simconglobal.com/farrimond_and_collins_2007_dimensional_inference_using_symbol_lives.pdf . That step is done within fpt, but we still have work to do in propagating the inferences of units.
ii. Dynamic analysis. We replace all real declarations with declarations of derived types and attach units information to the types. We then apply the inference rules whenever an operation is performed. The first step is to make the replacement and to overload the operators and intrinsic functions. That we have done, again within fpt. What we havenât yet done is to implement the routines which propagate the inferences. The advantage of this approach is that it handles array elements (which may have different units) and automatically handles sub-program interfaces.
If anyone would like to take part in a collaborative project we would be happy to do this.
Best wishes,
John
The static analysis has the advantage of not influencing the performance, whereas the second most probably does influence it. That said, the dynamic analysis allows for, as you say, array elements to have different units.
How can we experiment with this feature? I feel pretty strongly about the topic
The easy case to start with is the dynamic analysis. The work in fpt is already done (although there could be problems if the original program uses implied EQUIVALENCE in COMMON blocks). The fpt process is described at fpt Reference: EMULATE REAL ARITHMETIC . What is needed next is the set of routines to implement the overloads of operators and intrinsics, and the handlers to propagate the units inferences. For the first cases we tried, the overload routines were generated by a set of Fortran programs which I will make available. We would need to change these to call the routines which handle the propagation of the units inferences. And we would need to write those routines. These routines already exist inside fpt to handle the static analysis case, and when I have time I shall try to extract them (as @Arjen knows I am a little busy at the moment). These are actually quite simple. +, - and = imply that the units are the same, * and / imply relationships between the units and so on.
The static case requires more work within the internals of fpt (or writing an alternative to fpt). We have not done this yet because of pressure of other work, but I would very much like to return to it.