{-# LANGUAGE PolyKinds, DataKinds, KindSignatures, ScopedTypeVariables,
ExistentialQuantification, Rank2Types #-}
module Math.Combinat.TypeLevel
(
Proxy(..)
, proxyUndef
, proxyOf
, proxyOf1
, proxyOf2
, asProxyTypeOf
, asProxyTypeOf1
, typeArg
, iTypeArg
, Some (..)
, withSome , withSomeM
, selectSome , selectSomeM
, withSelected , withSelectedM
)
where
import Data.Proxy ( Proxy(..) , asProxyTypeOf )
import GHC.TypeLits
import Math.Combinat.Numbers.Primes ( isProbablyPrime )
proxyUndef :: Proxy a -> a
proxyUndef _ = error "proxyUndef"
proxyOf :: a -> Proxy a
proxyOf _ = Proxy
proxyOf1 :: f a -> Proxy a
proxyOf1 _ = Proxy
proxyOf2 :: g (f a) -> Proxy a
proxyOf2 _ = Proxy
asProxyTypeOf1 :: f a -> Proxy a -> f a
asProxyTypeOf1 y _ = y
typeArg :: KnownNat n => f (n :: Nat) -> Integer
typeArg = natVal . proxyOf1
iTypeArg :: KnownNat n => f (n :: Nat) -> Int
iTypeArg = fromIntegral . typeArg
data Some f = forall n. KnownNat n => Some (f n)
withSome :: Some f -> (forall n. KnownNat n => f n -> a) -> a
withSome some polyFun = case some of { Some stuff -> polyFun stuff }
withSomeM :: Monad m => Some f -> (forall n. KnownNat n => f n -> m a) -> m a
withSomeM some polyAct = case some of { Some stuff -> polyAct stuff }
selectSome :: Integral int => (forall n. KnownNat n => f n) -> int -> Some f
selectSome poly n = case someNatVal (fromIntegral n :: Integer) of
Nothing -> error "selectSome: not a natural number"
Just snat -> case snat of
SomeNat pxy -> Some (asProxyTypeOf1 poly pxy)
selectSomeM :: forall m f int. (Integral int, Monad m) => (forall n. KnownNat n => m (f n)) -> int -> m (Some f)
selectSomeM runPoly n = case someNatVal (fromIntegral n :: Integer) of
Nothing -> error "selectSomeM: not a natural number"
Just snat -> case snat of
SomeNat pxy -> do
poly <- runPoly
return $ Some (asProxyTypeOf1 poly pxy)
withSelected
:: Integral int
=> (forall n. KnownNat n => f n -> a)
-> (forall n. KnownNat n => f n)
-> int
-> a
withSelected f x n = withSome (selectSome x n) f
withSelectedM
:: forall m f int a. (Integral int, Monad m)
=> (forall n. KnownNat n => f n -> a)
-> (forall n. KnownNat n => m (f n))
-> int
-> m a
withSelectedM f mx n = do
s <- selectSomeM mx n
return (withSome s f)