{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Generics.MRSOP.Util
(
(&&&) , (***)
, (:->) , (<.>)
, (:*:)(..) , curry' , uncurry'
, Nat(..) , proxyUnsuc
, SNat(..) , snat2int
, IsNat(..) , getNat , getSNat'
, ListPrf(..) , IsList(..)
, L1 , L2 , L3 , L4
, (:++:) , appendIsListLemma
, Lkup , Idx , El(..) , getElSNat , into
, Eq1(..) , Show1(..)
) where
import Data.Proxy
import Data.Type.Equality
import GHC.TypeLits (TypeError , ErrorMessage(..))
import Control.Arrow ((***) , (&&&))
data (:*:) (f :: k -> *) (g :: k -> *) (x :: k)
= f x :*: g x
curry' :: ((f :*: g) x -> a) -> f x -> g x -> a
curry' f fx gx = f (fx :*: gx)
uncurry' :: (f x -> g x -> a) -> (f :*: g) x -> a
uncurry' f (fx :*: gx) = f fx gx
type f :-> g = forall n . f n -> g n
infixr 8 <.>
(<.>) :: (Monad m) => (b -> m c) -> (a -> m b) -> a -> m c
f <.> g = (>>= f) . g
data Nat = S Nat | Z
deriving (Eq , Show)
proxyUnsuc :: Proxy (S n) -> Proxy n
proxyUnsuc _ = Proxy
data SNat :: Nat -> * where
SZ :: SNat Z
SS :: SNat n -> SNat (S n)
snat2int :: SNat n -> Integer
snat2int SZ = 0
snat2int (SS n) = 1 + snat2int n
class IsNat (n :: Nat) where
getSNat :: Proxy n -> SNat n
instance IsNat Z where
getSNat p = SZ
instance IsNat n => IsNat (S n) where
getSNat p = SS (getSNat $ proxyUnsuc p)
getNat :: (IsNat n) => Proxy n -> Integer
getNat = snat2int . getSNat
getSNat' :: forall (n :: Nat). IsNat n => SNat n
getSNat' = getSNat (Proxy :: Proxy n)
instance TestEquality SNat where
testEquality SZ SZ = Just Refl
testEquality (SS n) (SS m)
= case testEquality n m of
Nothing -> Nothing
Just Refl -> Just Refl
testEquality _ _ = Nothing
type family Lkup (n :: Nat) (ks :: [k]) :: k where
Lkup Z (k : ks) = k
Lkup (S n) (k : ks) = Lkup n ks
Lkup _ '[] = TypeError (Text "Lkup index too big")
type family Idx (ty :: k) (xs :: [k]) :: Nat where
Idx x (x ': ys) = Z
Idx x (y ': ys) = S (Idx x ys)
Idx x '[] = TypeError (Text "Element not found")
data El :: [*] -> Nat -> * where
El :: IsNat ix => {unEl :: Lkup ix fam} -> El fam ix
getElSNat :: forall ix ls. El ls ix -> SNat ix
getElSNat (El _) = getSNat' @ix
into :: forall fam ty ix
. (ix ~ Idx ty fam , Lkup ix fam ~ ty , IsNat ix)
=> ty -> El fam ix
into = El
data ListPrf :: [k] -> * where
Nil :: ListPrf '[]
Cons :: ListPrf l -> ListPrf (x ': l)
class IsList (xs :: [k]) where
listPrf :: ListPrf xs
instance IsList '[] where
listPrf = Nil
instance IsList xs => IsList (x ': xs) where
listPrf = Cons listPrf
appendIsListLemma :: ListPrf xs -> ListPrf ys -> ListPrf (xs :++: ys)
appendIsListLemma Nil isys = isys
appendIsListLemma (Cons isxs) isys = Cons (appendIsListLemma isxs isys)
type family (:++:) (txs :: [k]) (tys :: [k]) :: [k] where
(:++:) '[] tys = tys
(:++:) (tx ': txs) tys = tx ': (txs :++: tys)
type L1 xs = (IsList xs)
type L2 xs ys = (IsList xs, IsList ys)
type L3 xs ys zs = (IsList xs, IsList ys, IsList zs)
type L4 xs ys zs as = (IsList xs, IsList ys, IsList zs, IsList as)
class Eq1 (f :: k -> *) where
eq1 :: forall k . f k -> f k -> Bool
class Show1 (f :: k -> *) where
show1 :: forall k . f k -> String