module Numeric.Units.Dimensional.Internal
(
KnownVariant(..),
Dimensional(..),
type Unit, type Quantity,
siUnit, showIn,
liftD, liftD2,
liftQ, liftQ2
)
where
import Control.Applicative
import Control.DeepSeq
import Control.Monad (liftM)
import Data.Coerce (coerce)
import Data.Data
import Data.ExactPi
import Data.Monoid (Monoid(..))
import Foreign.Ptr (Ptr, castPtr)
import Foreign.Storable (Storable(..))
import GHC.Generics
import Numeric.Units.Dimensional.Dimensions
import Numeric.Units.Dimensional.Variants hiding (type (*))
import qualified Numeric.Units.Dimensional.Variants as V
import Numeric.Units.Dimensional.UnitNames hiding ((*), (/), (^), weaken, strengthen)
import qualified Numeric.Units.Dimensional.UnitNames.Internal as Name
import Numeric.Units.Dimensional.UnitNames.InterchangeNames (HasInterchangeName(..))
import qualified Data.Vector.Generic.Mutable as M
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Unboxed.Base as U
import Prelude
( Show, Eq(..), Ord, Bounded(..), Num, Fractional, Functor
, String, Maybe(..)
, (.), ($), (++), (+), (/)
, show, otherwise, undefined, error, fmap
)
type Unit (m :: Metricality) = Dimensional ('DUnit m)
type Quantity = Dimensional 'DQuantity
class KnownVariant (v :: Variant) where
data Dimensional v :: Dimension -> * -> *
extractValue :: Dimensional v d a -> (a, Maybe ExactPi)
extractName :: Dimensional v d a -> Maybe (UnitName 'NonMetric)
injectValue :: (Maybe (UnitName 'NonMetric)) -> (a, Maybe ExactPi) -> Dimensional v d a
dmap :: (a1 -> a2) -> Dimensional v d a1 -> Dimensional v d a2
deriving instance Typeable Dimensional
instance KnownVariant 'DQuantity where
newtype Dimensional 'DQuantity d a = Quantity a
deriving (Eq, Ord, Data, Generic, Generic1
#if MIN_VERSION_base(4,8,0)
, Typeable
#endif
)
extractValue (Quantity x) = (x, Nothing)
extractName _ = Nothing
injectValue _ (x, _) = Quantity x
dmap = coerce
instance (Typeable m) => KnownVariant ('DUnit m) where
data Dimensional ('DUnit m) d a = Unit !(UnitName m) !ExactPi !a
deriving (Generic, Generic1
#if MIN_VERSION_base(4,8,0)
, Typeable
#endif
)
extractValue (Unit _ e x) = (x, Just e)
extractName (Unit n _ _) = Just . Name.weaken $ n
injectValue (Just n) (x, Just e) | Just n' <- relax n = Unit n' e x
| otherwise = error "Shouldn't be reachable. Needed a metric name but got a non-metric one."
injectValue _ _ = error "Shouldn't be reachable. Needed to name a quantity."
dmap f (Unit n e x) = Unit n e (f x)
instance (Bounded a) => Bounded (Quantity d a) where
minBound = Quantity minBound
maxBound = Quantity maxBound
instance HasInterchangeName (Unit m d a) where
interchangeName (Unit n _ _) = interchangeName n
instance (Num a) => Monoid (Quantity d a) where
mempty = Quantity 0
mappend = liftQ2 (+)
instance Functor (Quantity DOne) where
fmap = dmap
instance (KnownDimension d) => HasDimension (Dimensional v d a) where
dimension _ = dimension (Proxy :: Proxy d)
siUnit :: forall d a.(KnownDimension d, Num a) => Unit 'NonMetric d a
siUnit = Unit (baseUnitName $ dimension (Proxy :: Proxy d)) 1 1
instance NFData a => NFData (Quantity d a)
instance Storable a => Storable (Quantity d a) where
sizeOf _ = sizeOf (undefined::a)
alignment _ = alignment (undefined::a)
poke ptr = poke (castPtr ptr :: Ptr a) . coerce
peek ptr = liftM Quantity (peek (castPtr ptr :: Ptr a))
newtype instance U.Vector (Quantity d a) = V_Quantity {unVQ :: U.Vector a}
newtype instance U.MVector s (Quantity d a) = MV_Quantity {unMVQ :: U.MVector s a}
instance U.Unbox a => U.Unbox (Quantity d a)
instance (M.MVector U.MVector a) => M.MVector U.MVector (Quantity d a) where
basicLength = M.basicLength . unMVQ
basicUnsafeSlice m n = MV_Quantity . M.basicUnsafeSlice m n . unMVQ
basicOverlaps u v = M.basicOverlaps (unMVQ u) (unMVQ v)
basicUnsafeNew = liftM MV_Quantity . M.basicUnsafeNew
basicUnsafeRead v = liftM Quantity . M.basicUnsafeRead (unMVQ v)
basicUnsafeWrite v i = M.basicUnsafeWrite (unMVQ v) i . coerce
#if MIN_VERSION_vector(0,11,0)
basicInitialize = M.basicInitialize . unMVQ
#endif
instance (G.Vector U.Vector a) => G.Vector U.Vector (Quantity d a) where
basicUnsafeFreeze = liftM V_Quantity . G.basicUnsafeFreeze . unMVQ
basicUnsafeThaw = liftM MV_Quantity . G.basicUnsafeThaw . unVQ
basicLength = G.basicLength . unVQ
basicUnsafeSlice m n = V_Quantity . G.basicUnsafeSlice m n . unVQ
basicUnsafeIndexM v = liftM Quantity . G.basicUnsafeIndexM (unVQ v)
instance (KnownDimension d, Show a, Fractional a) => Show (Quantity d a) where
show = showIn siUnit
showIn :: (KnownDimension d, Show a, Fractional a) => Unit m d a -> Quantity d a -> String
showIn (Unit n _ y) (Quantity x) | Name.weaken n == nOne = show (x / y)
| otherwise = (show (x / y)) ++ " " ++ (show n)
instance (KnownDimension d, Show a) => Show (Unit m d a) where
show (Unit n e x) = "The unit " ++ show n ++ ", with value " ++ show e ++ " (or " ++ show x ++ ")"
liftD :: (KnownVariant v1, KnownVariant v2) => (ExactPi -> ExactPi) -> (a -> b) -> UnitNameTransformer -> (Dimensional v1 d1 a) -> (Dimensional v2 d2 b)
liftD fe f nt x = let (x', e') = extractValue x
n = extractName x
n' = (liftA nt) n
in injectValue n' (f x', fmap fe e')
liftQ :: (a -> a) -> Quantity d1 a -> Quantity d2 a
liftQ = coerce
liftD2 :: (KnownVariant v1, KnownVariant v2, KnownVariant (v1 V.* v2)) => (ExactPi -> ExactPi -> ExactPi) -> (a -> a -> a) -> UnitNameTransformer2 -> Dimensional v1 d1 a -> Dimensional v2 d2 a -> Dimensional (v1 V.* v2) d3 a
liftD2 fe f nt x1 x2 = let (x1', e1') = extractValue x1
(x2', e2') = extractValue x2
n1 = extractName x1
n2 = extractName x2
n' = (liftA2 nt) n1 n2
in injectValue n' (f x1' x2', fe <$> e1' <*> e2')
liftQ2 :: (a -> a -> a) -> Quantity d1 a -> Quantity d2 a -> Quantity d3 a
liftQ2 = coerce