{-# LANGUAGE CPP #-}
{-# LANGUAGE MonoLocalBinds #-}
#if __GLASGOW_HASKELL__ == 902
{-# LANGUAGE GADTs #-}
#endif
{-# LANGUAGE Safe #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Clash.Class.Resize
( Resize(..)
, checkedResize
, checkedFromIntegral
, checkedTruncateB
, maybeResize
, maybeTruncateB
) where
import Data.Kind (Type)
import Data.Proxy (Proxy(Proxy))
import GHC.Stack (HasCallStack)
import GHC.TypeLits (Nat, KnownNat, type (+))
import Clash.Sized.Internal (formatRange)
#if MIN_VERSION_base(4,16,0)
import GHC.TypeLits (OrderingI(EQI, GTI), cmpNat)
#else
import Clash.Promoted.Nat (natToNatural)
#endif
class Resize (f :: Nat -> Type) where
resize :: (KnownNat a, KnownNat b) => f a -> f b
extend :: (KnownNat a, KnownNat b) => f a -> f (b + a)
extend = resize
zeroExtend :: (KnownNat a, KnownNat b) => f a -> f (b + a)
signExtend :: (KnownNat a, KnownNat b) => f a -> f (b + a)
signExtend = resize
truncateB :: KnownNat a => f (a + b) -> f a
checkIntegral ::
forall a b.
HasCallStack =>
(Integral a, Integral b, Bounded b) =>
Proxy b ->
a -> ()
checkIntegral Proxy v =
if toInteger v > toInteger (maxBound @b)
|| toInteger v < toInteger (minBound @b) then
error $ "Given integral " <> show (toInteger v) <> " is out of bounds for" <>
" target type. Bounds of target type are: " <>
formatRange (toInteger (minBound @b)) (toInteger (maxBound @b)) <> "."
else
()
checkedFromIntegral ::
forall a b.
HasCallStack =>
(Integral a, Integral b, Bounded b) =>
a -> b
checkedFromIntegral v =
checkIntegral (Proxy @b) v `seq` fromIntegral v
checkedResize ::
forall a b f.
( HasCallStack
, Resize f
, KnownNat a, Integral (f a)
, KnownNat b, Integral (f b), Bounded (f b) ) =>
f a -> f b
checkedResize v =
checkIntegral (Proxy @(f b)) v `seq` resize v
checkedTruncateB ::
forall a b f.
( HasCallStack
, Resize f
, KnownNat b, Integral (f (a + b))
, KnownNat a, Integral (f a), Bounded (f a) ) =>
f (a + b) -> f a
checkedTruncateB v =
checkIntegral (Proxy @(f a)) v `seq` truncateB v
maybeResize ::
forall a b f.
( Resize f
, KnownNat a, Integral (f a)
, KnownNat b, Integral (f b), Bounded (f b) ) =>
f a -> Maybe (f b)
maybeResize v =
#if MIN_VERSION_base(4,16,0)
case Proxy @a `cmpNat` Proxy @b of
GTI | v > resize (maxBound @(f b)) -> Nothing
GTI | v < resize (minBound @(f b)) -> Nothing
EQI -> Just v
_ -> Just (resize v)
#else
case natToNatural @a `compare` natToNatural @b of
GT | v > resize (maxBound @(f b)) -> Nothing
GT | v < resize (minBound @(f b)) -> Nothing
_ -> Just (resize v)
#endif
maybeTruncateB ::
forall a b f.
( Resize f
, KnownNat b, Integral (f (a + b))
, KnownNat a, Integral (f a), Bounded (f a) ) =>
f (a + b) -> Maybe (f a)
maybeTruncateB v
| v > resize (maxBound @(f a)) = Nothing
| v < resize (minBound @(f a)) = Nothing
| otherwise = Just (truncateB v)