[Haskell-cafe] ANN: dimensional-1.0 for statically checked physical dimensions

Douglas McClean douglas.mcclean at gmail.com
Mon Nov 2 19:38:50 UTC 2015


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20151102/8c276343/attachment.html>


More information about the Haskell-Cafe mailing list