ANN: dimensional-1.0 for statically checked physical dimensions

Hello Haskellers, Björn Buckwalter and I are pleased to announce the release to Hackage of version 1.0 of the dimensional library, which statically tracks physical dimensions in Haskell code, as in the example below, preventing dimensional mistakes and requiring explicit documentation of units where raw values are exchanged with external systems. {-# LANGUAGE NoImplicitPrelude #-} module Example where import Numeric.Units.Dimensional.Prelude import Numeric.Units.Dimensional.NonSI -- a function that computes with dimensional values escapeVelocity :: (Floating a) => Mass a -> Length a -> Velocity a escapeVelocity m r = sqrt (two * g * m / r) where two = 2 *~ one g = 6.6720e-11 *~ (newton * meter ^ pos2 / kilo gram ^ pos2)
let re = 6372.792 *~ kilo meter let me = 5.9742e24 *~ kilo gram let ve = escapeVelocity me re ve -- Show defaults to SI base units 11184.537332296259 m s^-1 showIn (mile / hour) ve -- but we can show in other units "25019.09746845083 mi / h" let vekph = ve /~ (kilo meter / hour) -- and extract raw values when needed 40264.33439626653
This version is a major upgrade, consolidating features from the classic dimensional package and the dimensional-tf package. It takes advantage of the DataKinds and ClosedTypeFamilies extensions in GHC 7.8 to offer even safer types with a nearly identical interface. Also included: - Units carry names which can be combined by multiplication, division, and (only where appropriate) application of metric prefixes. You can use expressions like: showIn (milli meter / second) timeTravelSpeed to get "39339.52 mm / s" - Exact conversion factors between units are available, even when those conversion factors involve multiples of pi, thanks to the exact-pi library - The dimensionally-polymorphic siUnit term represents the coherent SI base unit of any dimension, which can be convenient for wrapping and unwrapping quantities in some contexts. - Storable and Unbox instances for Quantity types are available thanks to the efforts of Alberto Valverde González. - The Numeric.Units.Dimensional.Dynamic module offers types for safely manipulating quantities and units whose dimensions are not known statically. Also available is a term-level representation for dimensions. - Several other missing instances have been provided, including Bounded, Data, and Typeable instances. - New commonly used US customary units have been added, including US fluid measures and the knot. We have several other development efforts underway, including a type-checker plugin inspired by Adam Gundry's work, and on which he has provided valuable advice, which we hope will lead to a clean library for dimensionally typed linear algebra. Comments and contributions are welcome at http://github.com/bjornbm/dimensional-dk. (The repository name is a carryover from the name we were using while developing this version.) One particularly welcome contribution would be assistance with developing a patch for GHC issue 10391 https://ghc.haskell.org/trac/ghc/ticket/10391. Cheers, Doug McClean

On Mon, 2 Nov 2015, Douglas McClean wrote:
* Exact conversion factors between units are available, even when those conversion factors involve multiples of pi, thanks to the exact-pi library
Since pi is transcendental with respect to the rational numbers, I can use exact-pi for any other transcendental number, can't I?

Henning, Yes, if you wish. However you might run into surprises because the Floating class defines pi polymorphically, and the Floating instance for ExactPi uses exactly pi. We are also considering adding exact evaluation of trignonmetric functions at those points in the domain that can be exactly represented. As long as you are aware of this issue you can use it for any other transcendental function you might be more interested in. You could also consider copying the entire thing but changing the: instance Floating ExactPi where pi = Exact 1 1 bit to: instance Floating ExactSomethingElse where pi = Approximate pi If this related type would be useful to you and you have a suggested name for it, I can add it to the library? -Doug On Mon, Nov 2, 2015 at 2:49 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Mon, 2 Nov 2015, Douglas McClean wrote:
* Exact conversion factors between units are available, even when those
conversion factors involve multiples of pi, thanks to the exact-pi library
Since pi is transcendental with respect to the rational numbers, I can use exact-pi for any other transcendental number, can't I?
-- J. Douglas McClean (781) 561-5540 (cell)
participants (2)
-
Douglas McClean
-
Henning Thielemann