units-2.2: A domain-specific type system for dimensional analysis

Copyright(C) 2014 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (eir@cis.upenn.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Metrology.Parser

Contents

Description

This module exports functions allowing users to create their own unit quasiquoters to make for compact unit expressions.

A typical use case is this:

$(makeQuasiQuoter "unit" [''Kilo, ''Milli] [''Meter, ''Second])

and then, in a separate module (due to GHC's staging constraints)

x = 3 % [unit| m/s^2 ]

The unit expressions can refer to the prefixes and units specified in the call to makeQuasiQuoter. The spellings of the prefixes and units are taken from their Show instances.

The syntax for these expressions is like F#'s. There are four arithmetic operators (*, /, ^, and juxtaposition). Exponentiation binds the tightest, and it allows an integer to its right (possibly with minus signs and parentheses). Next tightest is juxtaposition, which indicates multiplication. Because juxtaposition binds tighter than division, the expressions m/s^2 and m/s s are equivalent. Multiplication and division bind the loosest and are left-associative, meaning that m/s*s is equivalent to (m/s)*s, probably not what you meant. Parentheses in unit expressions are allowed, of course.

Within a unit string (that is, a unit with an optional prefix), there may be ambiguity. If a unit string can be interpreted as a unit without a prefix, that parsing is preferred. Thus, min would be minutes, not milli-inches (assuming appropriate prefixes and units available.) There still may be ambiguity between unit strings, even interpreting the string as a prefix and a base unit. If a unit string is amiguous in this way, it is rejected. For example, if we have prefixes da and d and units m and am, then dam is ambiguous like this.

Synopsis

Quasiquoting interface

makeQuasiQuoter :: String -> [Name] -> [Name] -> Q [Dec] Source

makeQuasiQuoter "qq" prefixes units makes a quasi-quoter named qq that considers the prefixes and units provided. These are provided via names of the type constructors, not the data constructors. See the module documentation for more info and an example.

allUnits :: Q [Name] Source

Warning: Retrieving the list of all units and prefixes in scope does not work under GHC 7.8.*. Please upgrade GHC to use these functions.

Gets a list of the names of all units with Show instances in scope. Example usage:

$( do units <- allUnits
      makeQuasiQuoter "unit" [] units )

allPrefixes :: Q [Name] Source

Warning: Retrieving the list of all units and prefixes in scope does not work under GHC 7.8.*. Please upgrade GHC to use these functions.

Gets a list of the names of all unit prefixes with Show instances in scope. Example usage:

$( do units    <- allUnits
      prefixes <- allPrefixes
      makeQuasiQuoter "unit" prefixes units )

Direct interface

The definitions below allow users to access the unit parser directly. The parser produces UnitExps which can then be further processed as necessary.

parseUnit :: (Show pre, Show u) => SymbolTable pre u -> String -> Either String (UnitExp pre u) Source

Parse a unit expression, interpreted with respect the given symbol table. Returns either an error message or the successfully-parsed unit expression.

data UnitExp pre u Source

Parsed unit expressions, parameterized by a prefix identifier type and a unit identifier type

Constructors

Unity

"1"

Unit (Maybe pre) u

a unit with, perhaps, a prefix

Mult (UnitExp pre u) (UnitExp pre u) 
Div (UnitExp pre u) (UnitExp pre u) 
Pow (UnitExp pre u) Integer 

Instances

(Show pre, Show u) => Show (UnitExp pre u) 

data SymbolTable pre u Source

A "symbol table" for the parser, mapping prefixes and units to their representations.

mkSymbolTable Source

Arguments

:: (Show pre, Show u) 
=> [(String, pre)]

Association list of prefixes

-> [(String, u)]

Association list of units

-> Either String (SymbolTable pre u) 

Build a symbol table from prefix mappings and unit mappings. The prefix mapping can be empty. This function checks to make sure that the strings are not inherently ambiguous and are purely alphabetic.