Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This package is used to create and manipulate physical quantities, which are a numerical value associated with a unit of measurement.
In this package, values with units are represented with the Quantity type. Included is an expression parser and a huge list of predefined quantities with which to parse strings into a Quantity datatype. Once created, a quantity can be converted to different units or queried for its dimensionality. A user can also operate on quantities arithmetically, and doing so uses automatic unit conversion and simplification.
Synopsis
- fromString :: String -> Either (QuantityError Double) (Quantity Double)
- unitsFromString :: String -> Either (QuantityError Double) CompoundUnit
- data Definitions
- data Quantity a
- magnitude :: Quantity a -> a
- units :: Quantity a -> CompoundUnit
- data CompoundUnit
- convert :: Fractional a => Quantity a -> CompoundUnit -> Either (QuantityError a) (Quantity a)
- convertBase :: Fractional a => Quantity a -> Quantity a
- dimensionality :: Quantity a -> CompoundUnit
- addQuants :: Fractional a => Quantity a -> Quantity a -> Either (QuantityError a) (Quantity a)
- subtractQuants :: Fractional a => Quantity a -> Quantity a -> Either (QuantityError a) (Quantity a)
- multiplyQuants :: Num a => Quantity a -> Quantity a -> Quantity a
- divideQuants :: Fractional a => Quantity a -> Quantity a -> Quantity a
- exptQuants :: (Real a, Floating a) => Quantity a -> a -> Quantity a
- fromString' :: Definitions -> String -> Either (QuantityError Double) (Quantity Double)
- readDefinitions :: String -> Either (QuantityError Double) Definitions
- defaultDefString :: String
- data QuantityError a
- type QuantityComputation a = Either (QuantityError a)
Constructors
Currently, one constructor is supported to create quantities: fromString
.
There is an included expression parser that can parse values and strings
corresponding to builtin units. To view defined unit types, look at the
source code for defaultDefString
.
fromString :: String -> Either (QuantityError Double) (Quantity Double) Source #
Create a Quantity by parsing a string. Uses an UndefinedUnitError
for
undefined units. Handles arithmetic expressions as well.
>>>
fromString "25 m/s"
Right 25.0 meter / second>>>
fromString "fakeunit"
Left (UndefinedUnitError "fakeunit")>>>
fromString "ft + 12in"
Right 2.0 foot
This function also supports unit conversions, by placing "=>" in between
two valid expressions. This behavior is undefined (and returns a
ScalingFactorError
) if the quantity to be converted to has a magnitude.
>>>
fromString "min => s"
Right 60.0 second>>>
fromString "2 ft + 6 in => ft"
Right 2.5 foot>>>
fromString "m => 3 ft"
Left (ScalingFactorError 3.0 foot)
Make sure not to use dimensional quantities in exponents.
>>>
fromString "m ** 2"
Right 1.0 meter ** 2>>>
fromString "m ** (2s)"
Left (ParserError "Used non-dimensionless exponent in ( Right 1.0 meter ) ** ( Right 2.0 second )")
unitsFromString :: String -> Either (QuantityError Double) CompoundUnit Source #
Parse units from a string. Equivalent to fmap units . fromString
>>>
unitsFromString "N * s"
Right newton second
data Definitions Source #
Holds information about defined units, prefixes, and bases. Used when parsing new units and performing units conversions.
Instances
Eq Definitions Source # | |
Defined in Data.Quantities.Data (==) :: Definitions -> Definitions -> Bool # (/=) :: Definitions -> Definitions -> Bool # | |
Ord Definitions Source # | |
Defined in Data.Quantities.Data compare :: Definitions -> Definitions -> Ordering # (<) :: Definitions -> Definitions -> Bool # (<=) :: Definitions -> Definitions -> Bool # (>) :: Definitions -> Definitions -> Bool # (>=) :: Definitions -> Definitions -> Bool # max :: Definitions -> Definitions -> Definitions # min :: Definitions -> Definitions -> Definitions # | |
Show Definitions Source # | |
Defined in Data.Quantities.Data showsPrec :: Int -> Definitions -> ShowS # show :: Definitions -> String # showList :: [Definitions] -> ShowS # |
Combination of magnitude and units.
Instances
Eq a => Eq (Quantity a) Source # | |
Ord a => Ord (Quantity a) Source # | |
Show a => Show (Quantity a) Source # | |
magnitude :: Quantity a -> a Source #
Numerical magnitude of quantity.
>>>
magnitude <$> fromString "100 N * m"
Right 100.0
units :: Quantity a -> CompoundUnit Source #
Units associated with quantity.
>>>
units <$> fromString "3.4 m/s^2"
Right meter / second ** 2
data CompoundUnit Source #
Data type to hold compound units, which are simple units multiplied together.
Instances
Eq CompoundUnit Source # | |
Defined in Data.Quantities.Data (==) :: CompoundUnit -> CompoundUnit -> Bool # (/=) :: CompoundUnit -> CompoundUnit -> Bool # | |
Ord CompoundUnit Source # | |
Defined in Data.Quantities.Data compare :: CompoundUnit -> CompoundUnit -> Ordering # (<) :: CompoundUnit -> CompoundUnit -> Bool # (<=) :: CompoundUnit -> CompoundUnit -> Bool # (>) :: CompoundUnit -> CompoundUnit -> Bool # (>=) :: CompoundUnit -> CompoundUnit -> Bool # max :: CompoundUnit -> CompoundUnit -> CompoundUnit # min :: CompoundUnit -> CompoundUnit -> CompoundUnit # | |
Show CompoundUnit Source # | |
Defined in Data.Quantities.Data showsPrec :: Int -> CompoundUnit -> ShowS # show :: CompoundUnit -> String # showList :: [CompoundUnit] -> ShowS # |
Conversion
These functions are used to convert quantities from one unit type to another.
convert :: Fractional a => Quantity a -> CompoundUnit -> Either (QuantityError a) (Quantity a) Source #
Convert quantity to given units.
>>>
convert <$> fromString "m" <*> unitsFromString "ft"
Right (Right 3.280839895013123 foot)
convertBase :: Fractional a => Quantity a -> Quantity a Source #
Convert a quantity to its base units.
>>>
convertBase <$> fromString "newton"
Right 1000.0 gram meter / second ** 2
dimensionality :: Quantity a -> CompoundUnit Source #
Computes dimensionality of quantity.
>>>
dimensionality <$> fromString "newton"
Right [length] [mass] / [time] ** 2
Quantity arithmetic
Once created, quantities can be manipulated using the included arithmetic functions.
>>>
let (Right x) = fromString "m/s"
>>>
let (Right y) = fromString "mile/hr"
>>>
x `multiplyQuants` y
1.0 meter mile / hour / second>>>
x `divideQuants` y
1.0 hour meter / mile / second>>>
x `addQuants` y
Right 1.4470399999999999 meter / second>>>
x `subtractQuants` y
Right 0.55296 meter / second>>>
x `exptQuants` 1.5
1.0 meter ** 1.5 / second ** 1.5
The functions multiplyQuants
, divideQuants
, and exptQuants
change
units, and the units of the result are reduced to simplest terms.
>>>
x `divideQuants` x
1.0>>>
fmap (multiplyQuants x) $ fromString "s"
Right 1.0 meter>>>
x `exptQuants` 0
1.0
addQuants :: Fractional a => Quantity a -> Quantity a -> Either (QuantityError a) (Quantity a) Source #
Adds two quantities. Second quantity is converted to units of first quantity.
subtractQuants :: Fractional a => Quantity a -> Quantity a -> Either (QuantityError a) (Quantity a) Source #
Subtract two quantities. Second quantity is converted to units of first quantity.
multiplyQuants :: Num a => Quantity a -> Quantity a -> Quantity a Source #
Multiplies two quantities.
divideQuants :: Fractional a => Quantity a -> Quantity a -> Quantity a Source #
Divides two quantities.
exptQuants :: (Real a, Floating a) => Quantity a -> a -> Quantity a Source #
Exponentiates a quantity with an integer
Custom definitions
You don't have to use the default definitions provided by
defaultDefString
. Here is an example of adding a new unit called
metric_foot
.
>>>
let myDefString = defaultDefString ++ "\n" ++ "metric_foot = 300mm"
>>>
let (Right d') = readDefinitions myDefString
>>>
let myFromString = fromString' d'
>>>
myFromString "metric_foot"
Right 1.0 metric_foot>>>
convertBase <$> myFromString "metric_foot"
Right 0.3 meter
It is usually much easier to copy the source code for defaultDefString
and
add your definitions in the appropriate spot (for example, put metric_foot
next to the other unit definitions). Then, use fromString'
to create your
Quantity constructor.
NOTE: It is very important not to perform conversions on two quantities from different Definitions. Most of the error checking for undefined units is done when a unit is created, and not when performing conversions. We try to catch when different definitions are used.
>>>
let (Right m) = fromString "m"
>>>
let (Right ft) = myFromString "ft"
>>>
convert m (units ft)
Left (DifferentDefinitionsError meter foot)
fromString' :: Definitions -> String -> Either (QuantityError Double) (Quantity Double) Source #
Create quantities with custom definitions.
>>>
let myDefString = defaultDefString ++ "\nmy_unit = 100 s"
>>>
let (Right d) = readDefinitions myDefString
>>>
let myFromString = fromString' d
>>>
myFromString "25 my_unit"
Right 25.0 my_unit
readDefinitions :: String -> Either (QuantityError Double) Definitions Source #
Convert string of definitions into Definitions
structure. See source
code for defaultDefString
for an example.
defaultDefString :: String Source #
View the source code for this declaration to see what units and prefixes are defined by default.
This string holds the definitions for units and prefixes. Base units are
defined by the name of the unit, the name of the base in brackets, and any
aliases for the unit after that, all separated by equal signs: meter =
[length] = m
. Prefixes are defined by placing a dash after all identifiers,
and providing a value for the prefix: milli- = 1e-3 = m-
. Other units are
defined by using previously defined units in an expression: minute = 60 *
second = min
.
The reason these definitions aren't placed in a text file is so you don't have to operate your whole program in the IO monad. Users can copy this file into their source and modify definitions, or simply add a few definitions to the end of this string.
These definitions are taken almost verbatim from the Pint unit conversion library for the Python programming language. Check them out on GitHub.
Error type
data QuantityError a Source #
Custom error type
UndefinedUnitError String | Used when trying to parse an undefined unit. |
DimensionalityError CompoundUnit CompoundUnit | Used when converting units that do not have the same dimensionality (example: convert meter to second). |
UnitAlreadyDefinedError String | Used internally when defining units and a unit is already defined. |
PrefixAlreadyDefinedError String | Used internally when defining units and a prefix is already defined. |
ParserError String | Used when a string cannot be parsed. |
DifferentDefinitionsError CompoundUnit CompoundUnit | Used when two quantities come from different Definitions. |
ScalingFactorError (Quantity a) | Used when a scaling factor is present in a unit conversion. |
Instances
Eq a => Eq (QuantityError a) Source # | |
Defined in Data.Quantities.Data (==) :: QuantityError a -> QuantityError a -> Bool # (/=) :: QuantityError a -> QuantityError a -> Bool # | |
Show a => Show (QuantityError a) Source # | |
Defined in Data.Quantities.Data showsPrec :: Int -> QuantityError a -> ShowS # show :: QuantityError a -> String # showList :: [QuantityError a] -> ShowS # |
type QuantityComputation a = Either (QuantityError a) Source #
Useful for monadic computations with QuantityError
s. Some examples:
computation :: QuantityComputation Quantity computation = do x <- fromString "mile/hr" y <- unitsFromString "m/s" convert x y
Returns Right 0.44704 meter / second
computation :: QuantityComputation Quantity computation = do x <- fromString "BADUNIT" convertBase x
Returns Left (UndefinedUnitError BADUNIT)