Copyright | (C) 2013 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (rae@cs.brynmawr.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Data.Metrology.Unsafe
Contents
Description
This module exports the constructor of the Qu
type. This allows you
to write code that takes creates and reads quantities at will,
which may lead to dimension unsafety. Use at your peril.
This module also exports UnsafeQu
, which is a simple wrapper around
Qu
that has Functor
, etc., instances. The reason Qu
itself doesn't
have a Functor
instance is that it would be unit-unsafe, allowing you,
say, to add 1 to a quantity.... but 1 what? That's the problem. However,
a Functor
instance is likely useful, hence UnsafeQu
.
The Qu
type
newtype Qu (a :: [Factor *]) (lcsu :: LCSU *) (n :: *) Source #
Qu
adds a dimensional annotation to its numerical value type
n
. This is the representation for all quantities.
Constructors
Qu n |
Instances
Eq n => Eq (Qu d l n) Source # | |
(d ~ ('[] :: [Factor Type]), Floating n) => Floating (Qu d l n) Source # | |
Defined in Data.Metrology.Qu Methods sqrt :: Qu d l n -> Qu d l n # (**) :: Qu d l n -> Qu d l n -> Qu d l n # logBase :: Qu d l n -> Qu d l n -> Qu d l n # asin :: Qu d l n -> Qu d l n # acos :: Qu d l n -> Qu d l n # atan :: Qu d l n -> Qu d l n # sinh :: Qu d l n -> Qu d l n # cosh :: Qu d l n -> Qu d l n # tanh :: Qu d l n -> Qu d l n # asinh :: Qu d l n -> Qu d l n # acosh :: Qu d l n -> Qu d l n # atanh :: Qu d l n -> Qu d l n # log1p :: Qu d l n -> Qu d l n # expm1 :: Qu d l n -> Qu d l n # | |
(d ~ ('[] :: [Factor Type]), Fractional n) => Fractional (Qu d l n) Source # | |
(d ~ ('[] :: [Factor Type]), Num n) => Num (Qu d l n) Source # | |
Ord n => Ord (Qu d l n) Source # | |
Defined in Data.Metrology.Qu | |
Read n => Read (Qu ('[] :: [Factor Type]) l n) Source # | |
(d ~ ('[] :: [Factor Type]), Real n) => Real (Qu d l n) Source # | |
Defined in Data.Metrology.Qu Methods toRational :: Qu d l n -> Rational # | |
(d ~ ('[] :: [Factor Type]), RealFloat n) => RealFloat (Qu d l n) Source # | |
Defined in Data.Metrology.Qu Methods floatRadix :: Qu d l n -> Integer # floatDigits :: Qu d l n -> Int # floatRange :: Qu d l n -> (Int, Int) # decodeFloat :: Qu d l n -> (Integer, Int) # encodeFloat :: Integer -> Int -> Qu d l n # significand :: Qu d l n -> Qu d l n # scaleFloat :: Int -> Qu d l n -> Qu d l n # isInfinite :: Qu d l n -> Bool # isDenormalized :: Qu d l n -> Bool # isNegativeZero :: Qu d l n -> Bool # | |
(d ~ ('[] :: [Factor Type]), RealFrac n) => RealFrac (Qu d l n) Source # | |
Show n => Show (Qu ('[] :: [Factor Type]) l n) Source # | |
(ShowUnitFactor (LookupList dims lcsu), Show n) => Show (Qu dims lcsu n) Source # | |
NFData n => NFData (Qu d l n) Source # | |
Defined in Data.Metrology.Qu | |
VectorSpace n => VectorSpace (Qu d l n) Source # | |
AdditiveGroup n => AdditiveGroup (Qu d l n) Source # | |
ValidDL d l => Quantity (Qu d l n) Source # | |
Defined in Data.Metrology.Quantity Associated Types type QuantityUnit (Qu d l n) Source # type QuantityLCSU (Qu d l n) :: LCSU Type Source # type QuantityRep (Qu d l n) Source # Methods fromQuantity :: QuantityQu (Qu d l n) -> Qu d l n Source # toQuantity :: Qu d l n -> QuantityQu (Qu d l n) Source # | |
type Scalar (Qu d l n) Source # | |
Defined in Data.Metrology.Qu | |
type QuantityUnit (Qu d l n) Source # | |
Defined in Data.Metrology.Quantity | |
type QuantityLCSU (Qu d l n) Source # | |
Defined in Data.Metrology.Quantity | |
type QuantityRep (Qu d l n) Source # | |
Defined in Data.Metrology.Quantity | |
type (Qu d l n) %^ z Source # | |
Defined in Data.Metrology.Qu | |
type (Qu d1 l n) %/ (Qu d2 l n) Source # | |
type (Qu d1 l n) %* (Qu d2 l n) Source # | |
UnsafeQu
newtype UnsafeQu d l n Source #
A basic wrapper around Qu
that has more instances.
Instances
Functor (UnsafeQu d l) Source # | |
Applicative (UnsafeQu d l) Source # | |
Defined in Data.Metrology.Unsafe | |
Foldable (UnsafeQu d l) Source # | |
Defined in Data.Metrology.Unsafe Methods fold :: Monoid m => UnsafeQu d l m -> m # foldMap :: Monoid m => (a -> m) -> UnsafeQu d l a -> m # foldMap' :: Monoid m => (a -> m) -> UnsafeQu d l a -> m # foldr :: (a -> b -> b) -> b -> UnsafeQu d l a -> b # foldr' :: (a -> b -> b) -> b -> UnsafeQu d l a -> b # foldl :: (b -> a -> b) -> b -> UnsafeQu d l a -> b # foldl' :: (b -> a -> b) -> b -> UnsafeQu d l a -> b # foldr1 :: (a -> a -> a) -> UnsafeQu d l a -> a # foldl1 :: (a -> a -> a) -> UnsafeQu d l a -> a # toList :: UnsafeQu d l a -> [a] # null :: UnsafeQu d l a -> Bool # length :: UnsafeQu d l a -> Int # elem :: Eq a => a -> UnsafeQu d l a -> Bool # maximum :: Ord a => UnsafeQu d l a -> a # minimum :: Ord a => UnsafeQu d l a -> a # | |
Traversable (UnsafeQu d l) Source # | |
Defined in Data.Metrology.Unsafe |