Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Base module for all data structures.
Synopsis
- type Symbol = String
- data SimpleUnit = SimpleUnit {}
- data CompoundUnit = CompoundUnit {
- defs :: Definitions
- sUnits :: [SimpleUnit]
- showCompUnit' :: SimpleUnit -> String
- showPower :: Double -> String
- showPrettyNum :: (Show a, Num a) => a -> String
- data Quantity a = Quantity {
- magnitude :: a
- units :: CompoundUnit
- units' :: Quantity a -> [SimpleUnit]
- defs' :: Quantity a -> Definitions
- baseQuant :: a -> [SimpleUnit] -> Quantity a
- showSort :: [SimpleUnit] -> [SimpleUnit]
- data QuantityError a
- type QuantityComputation a = Either (QuantityError a)
- reduceUnits :: Quantity a -> Quantity a
- reduceUnits' :: [SimpleUnit] -> [SimpleUnit]
- removeZeros :: [SimpleUnit] -> [SimpleUnit]
- invertUnits :: [SimpleUnit] -> [SimpleUnit]
- invertSimpleUnit :: SimpleUnit -> SimpleUnit
- 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
- data Definition
- = PrefixDefinition { }
- | BaseDefinition { }
- | UnitDefinition { }
- data Definitions = Definitions {}
- emptyDefinitions :: Definitions
- unionDefinitions :: Definitions -> Definitions -> Definitions
Documentation
>>>
import Control.Applicative
>>>
import Data.Quantities
data SimpleUnit Source #
Representation of single unit. For example: "mm^2" is represented as
SimpleUnit { symbol = "meter", prefix = "milli", power = 2.0 }
Instances
Eq SimpleUnit Source # | |
Defined in Data.Quantities.Data (==) :: SimpleUnit -> SimpleUnit -> Bool # (/=) :: SimpleUnit -> SimpleUnit -> Bool # | |
Ord SimpleUnit Source # | |
Defined in Data.Quantities.Data compare :: SimpleUnit -> SimpleUnit -> Ordering # (<) :: SimpleUnit -> SimpleUnit -> Bool # (<=) :: SimpleUnit -> SimpleUnit -> Bool # (>) :: SimpleUnit -> SimpleUnit -> Bool # (>=) :: SimpleUnit -> SimpleUnit -> Bool # max :: SimpleUnit -> SimpleUnit -> SimpleUnit # min :: SimpleUnit -> SimpleUnit -> SimpleUnit # | |
Show SimpleUnit Source # | |
Defined in Data.Quantities.Data showsPrec :: Int -> SimpleUnit -> ShowS # show :: SimpleUnit -> String # showList :: [SimpleUnit] -> ShowS # |
data CompoundUnit Source #
Data type to hold compound units, which are simple units multiplied together.
CompoundUnit | |
|
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 # |
showCompUnit' :: SimpleUnit -> String Source #
Show a single unit, but prepend with /
if negative
showPrettyNum :: (Show a, Num a) => a -> String Source #
Will be used when we allow pretty printing of fractional units.
Combination of magnitude and units.
Quantity | |
|
Instances
Eq a => Eq (Quantity a) Source # | |
Ord a => Ord (Quantity a) Source # | |
Show a => Show (Quantity a) Source # | |
units' :: Quantity a -> [SimpleUnit] Source #
Convenience function to extract SimpleUnit collection from Quantity's CompoundUnit.
defs' :: Quantity a -> Definitions Source #
Convenience function to extract Definitions from Quantity's CompoundUnit.
baseQuant :: a -> [SimpleUnit] -> Quantity a Source #
Convenience function to make quantity with no definitions.
showSort :: [SimpleUnit] -> [SimpleUnit] Source #
Sort units but put negative units at end.
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)
reduceUnits :: Quantity a -> Quantity a Source #
Combines equivalent units and removes units with powers of zero.
reduceUnits' :: [SimpleUnit] -> [SimpleUnit] Source #
Helper function for reduceUnits.
removeZeros :: [SimpleUnit] -> [SimpleUnit] Source #
Removes units with powers of zero that are left over from other computations.
invertUnits :: [SimpleUnit] -> [SimpleUnit] Source #
Negate the powers of a list of SimpleUnits.
invertSimpleUnit :: SimpleUnit -> SimpleUnit Source #
Inverts unit by negating the power field.
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
data Definition Source #
Data type for the three definition types. Used to hold definitions information when parsing.
Instances
Eq Definition Source # | |
Defined in Data.Quantities.Data (==) :: Definition -> Definition -> Bool # (/=) :: Definition -> Definition -> Bool # | |
Ord Definition Source # | |
Defined in Data.Quantities.Data compare :: Definition -> Definition -> Ordering # (<) :: Definition -> Definition -> Bool # (<=) :: Definition -> Definition -> Bool # (>) :: Definition -> Definition -> Bool # (>=) :: Definition -> Definition -> Bool # max :: Definition -> Definition -> Definition # min :: Definition -> Definition -> Definition # | |
Show Definition Source # | |
Defined in Data.Quantities.Data showsPrec :: Int -> Definition -> ShowS # show :: Definition -> String # showList :: [Definition] -> ShowS # |
data Definitions Source #
Holds information about defined units, prefixes, and bases. Used when parsing new units and performing units conversions.
Definitions | |
|
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 # |
emptyDefinitions :: Definitions Source #
Default, empty set of definitions.
unionDefinitions :: Definitions -> Definitions -> Definitions Source #
Combine two Definitions structures