introducing dimensional

57
Introducing dimensional: Statically Checked Physical Dimensions for Haskell Björn Buckwalter & Doug McClean January 2016

Upload: douglas-mcclean

Post on 19-Jan-2017

284 views

Category:

Software


0 download

TRANSCRIPT

Introducing dimensional: Statically CheckedPhysical Dimensions for Haskell

Björn Buckwalter & Doug McClean

January 2016

Why Check Dimensions?

The usual reasons:

I Mars Climate OrbiterI Gimli Glider (Air Canada Flight 143)

Both incidents involved more than just software, but you get theidea.

Why Check Dimensions?

The usual reasons:

I Mars Climate OrbiterI Gimli Glider (Air Canada Flight 143)

Both incidents involved more than just software, but you get theidea.

Why Check Dimensions?

The usual reasons:

I Mars Climate OrbiterI Gimli Glider (Air Canada Flight 143)

Both incidents involved more than just software, but you get theidea.

Why Check Dimensions?

I Types as DocumentationI Type system requires source code documentation of units

where raw numeric values enter/leave the program

Existing Solutions

I units (Richard Eisenberg)I uom-plugin (Adam Gundry)I dimensional-tf (Björn Buckwalter)

Why dimensional?

What Goodies Do We Have?

I Types Reflect Dimensions, Not UnitsI Type-Level and Term-Level DimensionsI Strongly Kinded

What Goodies Do We Have?

I Dimensional ArithmeticI Convenient Quantity Synonyms

I type DLength = 'Dim 1 0 0 0 0 0 0 (morally)I type Length a = Quantity DLength aI type Capacitance a = ...

I Pretty PrintingI Choose display units with showInI Show instance defaults to SI base units

I Exact Conversion Factors Using exact-pi

What Goodies Do We Have?

I Ultra-Minimal DependenciesI No Need for TH or Solver Plugins

I Even to define new units

What Don’t We Have?

I Custom dimensions or polymorphism over basis

I No frogs / square mileI You have to live with our decision not to encode angle as a

dimension, although doing so is potentially useful from anengineering perspective

I CGS ESU units are treated as equivalents in SI basis

What Don’t We Have?

I Custom dimensions or polymorphism over basisI No frogs / square mile

I You have to live with our decision not to encode angle as adimension, although doing so is potentially useful from anengineering perspective

I CGS ESU units are treated as equivalents in SI basis

What Don’t We Have?

I Custom dimensions or polymorphism over basisI No frogs / square mileI You have to live with our decision not to encode angle as a

dimension, although doing so is potentially useful from anengineering perspective

I CGS ESU units are treated as equivalents in SI basis

What Don’t We Have?

I Custom dimensions or polymorphism over basisI No frogs / square mileI You have to live with our decision not to encode angle as a

dimension, although doing so is potentially useful from anengineering perspective

I CGS ESU units are treated as equivalents in SI basis

What Don’t We Have?

I TorsorsI No absolute temperatures, absolute times, etc.I See dimensional-dk-experimental

What Don’t We Have?

I A Functor instanceI Intentionally omitted, since it can be used to break

scale-invariance

What Don’t We Have?

I A solid benchmark suiteI Appropriate INLINE, SPECIALIZE, and RULES pragmas arising

from same

What Don’t We Have?

I A type solver plugin, like Adam Gundry’s

It’s very useful for code that is heavily polymorphic in dimension.For example, our attempts to build a usable dimensionally-typedlinear algebra library have been hampered by error messages of theform:

Couldn't match type `((x / iv) / u) * u'with `((x / iv) / x) * x'

I’m working on developing this, but could use some help.

Examples

Getting Started

cabal updatecabal install dimensional

Getting Started

Here’s an example word problem from the readme file:

A car travels at 60 kilometers per hour for one mile, at 50 kph forone mile, at 40 kph for one mile, and at 30 kph for one mile.

I How many minutes does the journey take?I What is the average speed of the car?I How many seconds does the journey take, rounded up to the

next whole second?

Readme Example Continued

{-# LANGUAGE NoImplicitPrelude #-}

module ReadmeExample where

import Numeric.Units.Dimensional.Preludeimport Numeric.Units.Dimensional.NonSI (mile)

leg :: Length Doubleleg = 1 *~ mile

speeds :: [Velocity Double]speeds = [60, 50, 40, 30] *~~ (kilo meter / hour)

Readme Example Continued

{-# LANGUAGE NoImplicitPrelude #-}

module ReadmeExample where

import Numeric.Units.Dimensional.Preludeimport Numeric.Units.Dimensional.NonSI (mile)

leg :: Length Doubleleg = 1 *~ mile

speeds :: [Velocity Double]speeds = [60, 50, 40, 30] *~~ (kilo meter / hour)

Readme Example Continued

{-# LANGUAGE NoImplicitPrelude #-}

module ReadmeExample where

import Numeric.Units.Dimensional.Preludeimport Numeric.Units.Dimensional.NonSI (mile)

leg :: Length Doubleleg = 1 *~ mile

speeds :: [Velocity Double]speeds = [60, 50, 40, 30] *~~ (kilo meter / hour)

Readme Example Continued

timeOfJourney :: Time DoubletimeOfJourney = sum $ fmap (leg /) speeds

averageSpeed :: Velocity DoubleaverageSpeed = _4 * leg / timeOfJourney-- = (4 *~ one) * leg / timeOfJourney

wholeSeconds :: IntegerwholeSeconds = ceiling $ timeOfJourney /~ second

Readme Example Continued

timeOfJourney :: Time DoubletimeOfJourney = sum $ fmap (leg /) speeds

averageSpeed :: Velocity DoubleaverageSpeed = _4 * leg / timeOfJourney-- = (4 *~ one) * leg / timeOfJourney

wholeSeconds :: IntegerwholeSeconds = ceiling $ timeOfJourney /~ second

Readme Example Continued

timeOfJourney :: Time DoubletimeOfJourney = sum $ fmap (leg /) speeds

averageSpeed :: Velocity DoubleaverageSpeed = _4 * leg / timeOfJourney-- = (4 *~ one) * leg / timeOfJourney

wholeSeconds :: IntegerwholeSeconds = ceiling $ timeOfJourney /~ second

Reading Aircraft State from FlightGearreadState :: [Double] -> VehicleState'readState [r, p, y, rDot, pDot, yDot, ax, ay, az, slip, as, vx, vy, vz, msl, agl, lat, lon, et, rpm, temp, statpres, dynpres]

= VehicleState' { ... }where

_orientation = quaternionFromTaitBryan (y *~ degree) (p *~ degree) (r *~ degree)_orientationRate = quaternionFromTaitBryan (yDot *~ degree) (pDot *~ degree) (rDot *~ degree)_velocity = (V3 vx vy vz) *~~ (foot / second)_acceleration = (V3 ax ay az) *~~ (foot / second / second)_sideSlip = slip *~ degree_airspeed = as *~ (nauticalMile / hour)_altitudeMSL = msl *~ foot_altitudeAGL = agl *~ foot_location = GeodeticPlace . fromJust $ lat <°> lon_elapsedTime = et *~ second_propellerSpeed = rpm *~ (revolution / minute)_staticPressure = statpres *~ inHg_dynamicPressure = dynpres *~ (poundForce / square foot)

Defining Custom Units

Internals

Ecosystem

dimensional-codata

I CODATA Values (not to be confused with codata. . . )I Speed of lightI Planck constantI etc.

exact-pi

data ExactPi = Exact Integer Rational| Approximate (forall a.Floating a => a)

approximateValue :: Floating a => ExactPi -> a

I Provides an exact representation of rational multiples of integerpowers of pi

I Provides Num, Fractional, Floating instances which fallback to Approximate where necessary

I Non-zero such numbers form a group under multiplicationI All exactly defined units we have encountered in practice have

an exact representationI Universal type of Approximate defers computations with pi,

+, etc. until after the desired result type has been selected.

exact-pi

data ExactPi = Exact Integer Rational| Approximate (forall a.Floating a => a)

approximateValue :: Floating a => ExactPi -> a

I Provides an exact representation of rational multiples of integerpowers of pi

I Provides Num, Fractional, Floating instances which fallback to Approximate where necessary

I Non-zero such numbers form a group under multiplicationI All exactly defined units we have encountered in practice have

an exact representationI Universal type of Approximate defers computations with pi,

+, etc. until after the desired result type has been selected.

exact-pi

data ExactPi = Exact Integer Rational| Approximate (forall a.Floating a => a)

approximateValue :: Floating a => ExactPi -> a

I Provides an exact representation of rational multiples of integerpowers of pi

I Provides Num, Fractional, Floating instances which fallback to Approximate where necessary

I Non-zero such numbers form a group under multiplication

I All exactly defined units we have encountered in practice havean exact representation

I Universal type of Approximate defers computations with pi,+, etc. until after the desired result type has been selected.

exact-pi

data ExactPi = Exact Integer Rational| Approximate (forall a.Floating a => a)

approximateValue :: Floating a => ExactPi -> a

I Provides an exact representation of rational multiples of integerpowers of pi

I Provides Num, Fractional, Floating instances which fallback to Approximate where necessary

I Non-zero such numbers form a group under multiplicationI All exactly defined units we have encountered in practice have

an exact representation

I Universal type of Approximate defers computations with pi,+, etc. until after the desired result type has been selected.

exact-pi

data ExactPi = Exact Integer Rational| Approximate (forall a.Floating a => a)

approximateValue :: Floating a => ExactPi -> a

I Provides an exact representation of rational multiples of integerpowers of pi

I Provides Num, Fractional, Floating instances which fallback to Approximate where necessary

I Non-zero such numbers form a group under multiplicationI All exactly defined units we have encountered in practice have

an exact representationI Universal type of Approximate defers computations with pi,

+, etc. until after the desired result type has been selected.

igrf and atmos

We have dimensionally typed wrappers around some libraries thatprovide physical information, for example

I igrf, which implements the International GeomagneticReference Field

I atmos, which implements the 1976 International StandardAtmosphere

Future Work

Forthcoming Version 1.1

I Improved support for dynamic quantities

I Improvements to unit names that are necessary for properparsing

I Fixed-point quantities (details on next slide)I User manual

Forthcoming Version 1.1

I Improved support for dynamic quantitiesI Improvements to unit names that are necessary for proper

parsing

I Fixed-point quantities (details on next slide)I User manual

Forthcoming Version 1.1

I Improved support for dynamic quantitiesI Improvements to unit names that are necessary for proper

parsingI Fixed-point quantities (details on next slide)

I User manual

Forthcoming Version 1.1

I Improved support for dynamic quantitiesI Improvements to unit names that are necessary for proper

parsingI Fixed-point quantities (details on next slide)I User manual

Forthcoming Fixed-Point Support

data Variant = DQuantity| DUnit Metricality

type Quantity = Dimensional DQuantity

becomes

data Variant = DQuantity ExactPi -- scale factor| DUnit Metricality

type SQuantity s = Dimensional (DQuantity s)

type Quantity = SQuantity One

Forthcoming Fixed-Point Support

data Variant = DQuantity| DUnit Metricality

type Quantity = Dimensional DQuantity

becomes

data Variant = DQuantity ExactPi -- scale factor| DUnit Metricality

type SQuantity s = Dimensional (DQuantity s)

type Quantity = SQuantity One

Forthcoming Fixed-Point Support

import qualified GHC.TypeLits as Nimport qualified Data.ExactPi.TypeLevel as E

-- A dimensionless number with n fractional bits,-- using a representation of type a.type Q n a = SQuantity (E.One E./

(E.ExactNatural (2 N.^ n))) DOne a

-- A single-turn angle represented as-- a signed 16-bit integer.type Angle16 = SQuantity (E.Pi E./

(E.ExactNatural (2 N.^ 15)))DPlaneAngle Int16

fast_sin :: Angle16 -> Q 15 Int16

With Template Haskell we can do even better tricks.

Forthcoming Fixed-Point Support

import qualified GHC.TypeLits as Nimport qualified Data.ExactPi.TypeLevel as E

-- A dimensionless number with n fractional bits,-- using a representation of type a.type Q n a = SQuantity (E.One E./

(E.ExactNatural (2 N.^ n))) DOne a

-- A single-turn angle represented as-- a signed 16-bit integer.type Angle16 = SQuantity (E.Pi E./

(E.ExactNatural (2 N.^ 15)))DPlaneAngle Int16

fast_sin :: Angle16 -> Q 15 Int16

With Template Haskell we can do even better tricks.

Forthcoming Fixed-Point Support

import qualified GHC.TypeLits as Nimport qualified Data.ExactPi.TypeLevel as E

-- A dimensionless number with n fractional bits,-- using a representation of type a.type Q n a = SQuantity (E.One E./

(E.ExactNatural (2 N.^ n))) DOne a

-- A single-turn angle represented as-- a signed 16-bit integer.type Angle16 = SQuantity (E.Pi E./

(E.ExactNatural (2 N.^ 15)))DPlaneAngle Int16

fast_sin :: Angle16 -> Q 15 Int16

With Template Haskell we can do even better tricks.

Forthcoming Fixed-Point Support

import qualified GHC.TypeLits as Nimport qualified Data.ExactPi.TypeLevel as E

-- A dimensionless number with n fractional bits,-- using a representation of type a.type Q n a = SQuantity (E.One E./

(E.ExactNatural (2 N.^ n))) DOne a

-- A single-turn angle represented as-- a signed 16-bit integer.type Angle16 = SQuantity (E.Pi E./

(E.ExactNatural (2 N.^ 15)))DPlaneAngle Int16

fast_sin :: Angle16 -> Q 15 Int16

With Template Haskell we can do even better tricks.

Forthcoming Fixed-Point Support

data VehicleState = VehicleState {lat :: Angle32,lon :: Angle32,altitutde :: [exact| mm ] Int32,vnorth :: [exact| cm / s ] Int16,veast :: [exact| cm / s ] Int16,vdown :: [exact| cm / s ] Int16,elapsedTime :: [exact| ms ] Word32,pressure :: [exact| 0.1 Pa ] Word32

}

The only holdup here is some remaining work on the parser.

Fixed-Point Arithmetic

(+), (-) :: (Num a) => SQuantity s d a-> SQuantity s d a-> SQuantity s d a

abs, negate :: (Num a) => SQuantity s d a-> SQuantity s d a

epsilon :: (Integral a) => SQuantity s d a

_0 :: Num a => SQuantity s d a

pi :: (Integral a, E.KnownExactPi s) => SQuantity s DOne a

Fixed-Point Arithmetic

(*~) :: (RealFrac a, Integral b, E.MinCtxt s a)=> a -> Unit m d a -> SQuantity s d b

rescale :: (Integral a, Integral b,E.KnownExactPi s1, E.KnownExactPi s2)

=> SQuantity s1 d a -> SQuantity s2 d b

rescaleVia :: (Integral a, Integral c,RealFrac b, Floating b,E.KnownExactPi s1, E.KnownExactPi s2)

=> Proxy b-> SQuantity s1 d a -> SQuantity s2 d c

Fixed-Point Arithmetic

(*~) :: (RealFrac a, Integral b, E.MinCtxt s a)=> a -> Unit m d a -> SQuantity s d b

rescale :: (Integral a, Integral b,E.KnownExactPi s1, E.KnownExactPi s2)

=> SQuantity s1 d a -> SQuantity s2 d b

rescaleVia :: (Integral a, Integral c,RealFrac b, Floating b,E.KnownExactPi s1, E.KnownExactPi s2)

=> Proxy b-> SQuantity s1 d a -> SQuantity s2 d c

Fixed-Point Arithmetic

(*~) :: (RealFrac a, Integral b, E.MinCtxt s a)=> a -> Unit m d a -> SQuantity s d b

rescale :: (Integral a, Integral b,E.KnownExactPi s1, E.KnownExactPi s2)

=> SQuantity s1 d a -> SQuantity s2 d b

rescaleVia :: (Integral a, Integral c,RealFrac b, Floating b,E.KnownExactPi s1, E.KnownExactPi s2)

=> Proxy b-> SQuantity s1 d a -> SQuantity s2 d c

Linear Algebra

An n * m matrix doesn’t have n * m independent choices ofdimension, it only has n + m - 1. You can multiply A and B onlywhen the relationship between the dimensions of the columns of A isthe inverse of the relationship between the dimensions of the rowsof B.

We have a library that models this, but it isn’t particularly usefulwithout the typechecker plugin because only monomorphic uses of itare checked.

If we can fix it up it will be very useful for control engineeringproblems.

Contributing

Suggestions and pull requests are welcome.

Issue tracker and source repository are at:

https://github.com/bjornbm/dimensional

Questions