Copyright | Copyright (C) 2006-2018 Bjorn Buckwalter |
---|---|
License | BSD3 |
Maintainer | bjorn@buckwalter.se |
Stability | Experimental |
Portability | GHC only? |
Safe Haskell | None |
Language | Haskell2010 |
Numeric.Units.Dimensional.Coercion
Description
Re-exports the raw Quantity
constructor from the Numeric.Units.Dimensional.Internal module, along with coerce
,
for convenience in converting between raw representations and dimensional values.
Note that use of these constructs requires the user to verify the dimensional safety of the conversion,
because the coercion doesn't explicitly mention the unit of the representation. Note also that the
Quantity
constructor constructs a SQuantity
which may have a scale factor
other than One
.
Note that the haddock documentation doesn't mention the Quantity
constructor because it is a part of the
Dimensional
associated data family, but it is exported by this module.
Synopsis
- coerce :: Coercible a b => a -> b
- data family Dimensional v :: Dimension -> Type -> Type
- unQuantity :: SQuantity s d a -> a
Documentation
data family Dimensional v :: Dimension -> Type -> Type Source #
A dimensional value, either a Quantity
or a Unit
, parameterized by its Dimension
and representation.
Instances
Vector Vector a => Vector Vector (SQuantity s d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (SQuantity s d a) -> m (Vector (SQuantity s d a)) Source # basicUnsafeThaw :: PrimMonad m => Vector (SQuantity s d a) -> m (Mutable Vector (PrimState m) (SQuantity s d a)) Source # basicLength :: Vector (SQuantity s d a) -> Int Source # basicUnsafeSlice :: Int -> Int -> Vector (SQuantity s d a) -> Vector (SQuantity s d a) Source # basicUnsafeIndexM :: Monad m => Vector (SQuantity s d a) -> Int -> m (SQuantity s d a) Source # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (SQuantity s d a) -> Vector (SQuantity s d a) -> m () Source # elemseq :: Vector (SQuantity s d a) -> SQuantity s d a -> b -> b Source # | |
MVector MVector a => MVector MVector (SQuantity s d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods basicLength :: MVector s0 (SQuantity s d a) -> Int Source # basicUnsafeSlice :: Int -> Int -> MVector s0 (SQuantity s d a) -> MVector s0 (SQuantity s d a) Source # basicOverlaps :: MVector s0 (SQuantity s d a) -> MVector s0 (SQuantity s d a) -> Bool Source # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (SQuantity s d a)) Source # basicInitialize :: PrimMonad m => MVector (PrimState m) (SQuantity s d a) -> m () Source # basicUnsafeReplicate :: PrimMonad m => Int -> SQuantity s d a -> m (MVector (PrimState m) (SQuantity s d a)) Source # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (SQuantity s d a) -> Int -> m (SQuantity s d a) Source # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (SQuantity s d a) -> Int -> SQuantity s d a -> m () Source # basicClear :: PrimMonad m => MVector (PrimState m) (SQuantity s d a) -> m () Source # basicSet :: PrimMonad m => MVector (PrimState m) (SQuantity s d a) -> SQuantity s d a -> m () Source # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (SQuantity s d a) -> MVector (PrimState m) (SQuantity s d a) -> m () Source # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (SQuantity s d a) -> MVector (PrimState m) (SQuantity s d a) -> m () Source # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (SQuantity s d a) -> Int -> m (MVector (PrimState m) (SQuantity s d a)) Source # | |
KnownDimension d => Demotable (Quantity d) Source # | |
Defined in Numeric.Units.Dimensional.Dynamic Methods demotableOut :: Quantity d a -> AnyQuantity a | |
Generic1 (Dimensional ('DQuantity s) d :: Type -> Type) Source # | |
Defined in Numeric.Units.Dimensional.Internal Associated Types type Rep1 (Dimensional ('DQuantity s) d) :: k -> Type Methods from1 :: forall (a :: k). Dimensional ('DQuantity s) d a -> Rep1 (Dimensional ('DQuantity s) d) a to1 :: forall (a :: k). Rep1 (Dimensional ('DQuantity s) d) a -> Dimensional ('DQuantity s) d a | |
Generic1 (Dimensional ('DUnit m) d :: Type -> Type) Source # | |
Defined in Numeric.Units.Dimensional.Internal Associated Types type Rep1 (Dimensional ('DUnit m) d) :: k -> Type Methods from1 :: forall (a :: k). Dimensional ('DUnit m) d a -> Rep1 (Dimensional ('DUnit m) d) a to1 :: forall (a :: k). Rep1 (Dimensional ('DUnit m) d) a -> Dimensional ('DUnit m) d a | |
KnownVariant v => Functor (Dimensional v d) Source # | A Note that this instance is dubious, because it allows you to break the dimensional abstraction. See Note that, while this instance overlaps with that given for Note that this is an orphan instance. |
Defined in Numeric.Units.Dimensional.Functor Methods fmap :: (a -> b) -> Dimensional v d a -> Dimensional v d b # (<$) :: a -> Dimensional v d b -> Dimensional v d a # | |
Functor (SQuantity s DOne) Source # | |
NFData a => NFData (Quantity d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal | |
Eq1 (SQuantity s d) Source # | |
Ord1 (SQuantity s d) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods liftCompare :: (a -> b -> Ordering) -> SQuantity s d a -> SQuantity s d b -> Ordering | |
Bounded a => Bounded (SQuantity s d a) Source # | |
Eq a => Eq (Dimensional ('DQuantity s) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods (==) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool # (/=) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool # | |
(Typeable s, Typeable d, Data a) => Data (Dimensional ('DQuantity s) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods gfoldl :: (forall d0 b. Data d0 => c (d0 -> b) -> d0 -> c b) -> (forall g. g -> c g) -> Dimensional ('DQuantity s) d a -> c (Dimensional ('DQuantity s) d a) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dimensional ('DQuantity s) d a) toConstr :: Dimensional ('DQuantity s) d a -> Constr dataTypeOf :: Dimensional ('DQuantity s) d a -> DataType dataCast1 :: Typeable t => (forall d0. Data d0 => c (t d0)) -> Maybe (c (Dimensional ('DQuantity s) d a)) dataCast2 :: Typeable t => (forall d0 e. (Data d0, Data e) => c (t d0 e)) -> Maybe (c (Dimensional ('DQuantity s) d a)) gmapT :: (forall b. Data b => b -> b) -> Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> Dimensional ('DQuantity s) d a -> r gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> Dimensional ('DQuantity s) d a -> r gmapQ :: (forall d0. Data d0 => d0 -> u) -> Dimensional ('DQuantity s) d a -> [u] gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> Dimensional ('DQuantity s) d a -> u gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> Dimensional ('DQuantity s) d a -> m (Dimensional ('DQuantity s) d a) gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> Dimensional ('DQuantity s) d a -> m (Dimensional ('DQuantity s) d a) gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> Dimensional ('DQuantity s) d a -> m (Dimensional ('DQuantity s) d a) | |
Ord a => Ord (Dimensional ('DQuantity s) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods compare :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Ordering # (<) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool # (<=) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool # (>) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool # (>=) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool # max :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a # min :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a # | |
(KnownDimension d, KnownExactPi s, Show a, Real a) => Show (SQuantity s d a) Source # | Uses non-breaking spaces between the value and the unit, and within the unit name. |
Show a => Show (Unit m d a) Source # | Unit names are shown with non-breaking spaces. |
Generic (Dimensional ('DQuantity s) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Associated Types type Rep (Dimensional ('DQuantity s) d a) :: Type -> Type Methods from :: Dimensional ('DQuantity s) d a -> Rep (Dimensional ('DQuantity s) d a) x to :: Rep (Dimensional ('DQuantity s) d a) x -> Dimensional ('DQuantity s) d a | |
Generic (Dimensional ('DUnit m) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Associated Types type Rep (Dimensional ('DUnit m) d a) :: Type -> Type Methods from :: Dimensional ('DUnit m) d a -> Rep (Dimensional ('DUnit m) d a) x to :: Rep (Dimensional ('DUnit m) d a) x -> Dimensional ('DUnit m) d a | |
Num a => Semigroup (SQuantity s d a) Source # |
|
Num a => Monoid (SQuantity s d a) Source # |
|
AEq a => AEq (Dimensional ('DQuantity s) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods (===) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool Source # (~==) :: Dimensional ('DQuantity s) d a -> Dimensional ('DQuantity s) d a -> Bool Source # | |
Unbox a => Unbox (SQuantity s d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal | |
Storable a => Storable (SQuantity s d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods sizeOf :: SQuantity s d a -> Int alignment :: SQuantity s d a -> Int peekElemOff :: Ptr (SQuantity s d a) -> Int -> IO (SQuantity s d a) pokeElemOff :: Ptr (SQuantity s d a) -> Int -> SQuantity s d a -> IO () peekByteOff :: Ptr b -> Int -> IO (SQuantity s d a) pokeByteOff :: Ptr b -> Int -> SQuantity s d a -> IO () | |
KnownDimension d => HasDimension (Dimensional v d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods dimension :: Dimensional v d a -> Dimension' Source # | |
KnownDimension d => HasDynamicDimension (Dimensional v d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods dynamicDimension :: Dimensional v d a -> DynamicDimension Source # | |
HasInterchangeName (Unit m d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal Methods interchangeName :: Unit m d a -> InterchangeName Source # | |
newtype MVector v (SQuantity s d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal | |
newtype Dimensional ('DQuantity s) d a Source # | |
Defined in Numeric.Units.Dimensional.Internal | |
data Dimensional ('DUnit m) d a Source # | |
Defined in Numeric.Units.Dimensional.Internal | |
type Rep1 (Dimensional ('DQuantity s) d :: Type -> Type) Source # | |
Defined in Numeric.Units.Dimensional.Internal type Rep1 (Dimensional ('DQuantity s) d :: Type -> Type) = D1 ('MetaData "Dimensional" "Numeric.Units.Dimensional.Internal" "dimensional-1.3-C8v0k83E9Py18UKTdF1oLh" 'True) (C1 ('MetaCons "Quantity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |
type Rep1 (Dimensional ('DUnit m) d :: Type -> Type) Source # | |
Defined in Numeric.Units.Dimensional.Internal type Rep1 (Dimensional ('DUnit m) d :: Type -> Type) = D1 ('MetaData "Dimensional" "Numeric.Units.Dimensional.Internal" "dimensional-1.3-C8v0k83E9Py18UKTdF1oLh" 'False) (C1 ('MetaCons "Unit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (UnitName m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ExactPi) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))) | |
type Rep (Dimensional ('DQuantity s) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal type Rep (Dimensional ('DQuantity s) d a) = D1 ('MetaData "Dimensional" "Numeric.Units.Dimensional.Internal" "dimensional-1.3-C8v0k83E9Py18UKTdF1oLh" 'True) (C1 ('MetaCons "Quantity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |
type Rep (Dimensional ('DUnit m) d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal type Rep (Dimensional ('DUnit m) d a) = D1 ('MetaData "Dimensional" "Numeric.Units.Dimensional.Internal" "dimensional-1.3-C8v0k83E9Py18UKTdF1oLh" 'False) (C1 ('MetaCons "Unit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (UnitName m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ExactPi) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))) | |
newtype Vector (SQuantity s d a) Source # | |
Defined in Numeric.Units.Dimensional.Internal |