| Copyright | (C) 2014 Richard Eisenberg | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Text.Parse.Units
Contents
Description
This module defines a parser for unit expressions.  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
- data UnitExp pre u
- parseUnit :: (Show pre, Show u) => SymbolTable pre u -> String -> Either String (UnitExp pre u)
- data SymbolTable pre u = SymbolTable {- prefixTable :: PrefixTable pre
- unitTable :: UnitTable u
 
- type PrefixTable pre = Map String pre
- type UnitTable u = String -> Maybe u
- mkSymbolTable :: (Show pre, Show u) => [(String, pre)] -> [(String, u)] -> Either String (SymbolTable pre u)
- unsafeMkSymbolTable :: PrefixTable pre -> UnitTable u -> SymbolTable pre u
- universalSymbolTable :: SymbolTable a String
Parsing units
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
| (Eq pre, Eq u) => Eq (UnitExp pre u) Source # | |
| (Data pre, Data u) => Data (UnitExp pre u) Source # | |
| Defined in Text.Parse.Units Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnitExp pre u -> c (UnitExp pre u) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UnitExp pre u) # toConstr :: UnitExp pre u -> Constr # dataTypeOf :: UnitExp pre u -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (UnitExp pre u)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UnitExp pre u)) # gmapT :: (forall b. Data b => b -> b) -> UnitExp pre u -> UnitExp pre u # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnitExp pre u -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnitExp pre u -> r # gmapQ :: (forall d. Data d => d -> u0) -> UnitExp pre u -> [u0] # gmapQi :: Int -> (forall d. Data d => d -> u0) -> UnitExp pre u -> u0 # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnitExp pre u -> m (UnitExp pre u) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitExp pre u -> m (UnitExp pre u) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitExp pre u -> m (UnitExp pre u) # | |
| (Ord pre, Ord u) => Ord (UnitExp pre u) Source # | |
| Defined in Text.Parse.Units Methods compare :: UnitExp pre u -> UnitExp pre u -> Ordering # (<) :: UnitExp pre u -> UnitExp pre u -> Bool # (<=) :: UnitExp pre u -> UnitExp pre u -> Bool # (>) :: UnitExp pre u -> UnitExp pre u -> Bool # (>=) :: UnitExp pre u -> UnitExp pre u -> Bool # | |
| (Show pre, Show u) => Show (UnitExp pre u) Source # | |
| Generic (UnitExp pre u) Source # | |
| type Rep (UnitExp pre u) Source # | |
| Defined in Text.Parse.Units type Rep (UnitExp pre u) = D1 ('MetaData "UnitExp" "Text.Parse.Units" "units-parser-0.1.1.4-JzgMQA3GTHu2LCbluj7WLi" 'False) ((C1 ('MetaCons "Unity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe pre)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 u))) :+: (C1 ('MetaCons "Mult" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitExp pre u)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitExp pre u))) :+: (C1 ('MetaCons "Div" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitExp pre u)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitExp pre u))) :+: C1 ('MetaCons "Pow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitExp pre u)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) | |
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.
Symbol tables
data SymbolTable pre u Source #
A "symbol table" for the parser, mapping prefixes and units to their representations.
Constructors
| SymbolTable | |
| Fields 
 | |
Instances
| Generic (SymbolTable pre u) Source # | |
| Defined in Text.Parse.Units Associated Types type Rep (SymbolTable pre u) :: Type -> Type # Methods from :: SymbolTable pre u -> Rep (SymbolTable pre u) x # to :: Rep (SymbolTable pre u) x -> SymbolTable pre u # | |
| type Rep (SymbolTable pre u) Source # | |
| Defined in Text.Parse.Units type Rep (SymbolTable pre u) = D1 ('MetaData "SymbolTable" "Text.Parse.Units" "units-parser-0.1.1.4-JzgMQA3GTHu2LCbluj7WLi" 'False) (C1 ('MetaCons "SymbolTable" 'PrefixI 'True) (S1 ('MetaSel ('Just "prefixTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PrefixTable pre)) :*: S1 ('MetaSel ('Just "unitTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnitTable u)))) | |
type PrefixTable pre = Map String pre Source #
A finite mapping from prefix spellings to prefix identifiers (of
 unspecified type pre). All prefix spellings must be strictly alphabetic.
type UnitTable u = String -> Maybe u Source #
A mapping from unit spellings to unit identifiers (of unspecified type
 u). All unit spellings must be strictly alphabetic.
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.
unsafeMkSymbolTable :: PrefixTable pre -> UnitTable u -> SymbolTable pre u Source #
Make a symbol table without checking for ambiguity or non-purely alphabetic strings. The prefixes must be a (potentially empty) finite map, but the units mapping need not be finite. Note that this is unsafe in that the resulting parser may behave unpredictably. It surely won't launch the rockets, though.
universalSymbolTable :: SymbolTable a String Source #
A symbol table that accepts all unit strings, but supports no prefixes.