{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
#if __GLASGOW_HASKELL__ >= 810
{-# LANGUAGE UndecidableInstances #-}
#endif
module Data.Vinyl.TypeLevel where
#if __GLASGOW_HASKELL__ < 806
import Data.Kind
#else
import GHC.Exts
#endif
import GHC.Types (Type)
data Nat = Z | S !Nat
class NatToInt (n :: Nat) where
natToInt :: Int
instance NatToInt 'Z where
natToInt = 0
{-# INLINE natToInt #-}
instance NatToInt n => NatToInt ('S n) where
natToInt = 1 + natToInt @n
{-# INLINE natToInt #-}
class IndexWitnesses (is :: [Nat]) where
indexWitnesses :: [Int]
instance IndexWitnesses '[] where
indexWitnesses = []
{-# INLINE indexWitnesses #-}
instance (IndexWitnesses is, NatToInt i) => IndexWitnesses (i ': is) where
indexWitnesses = natToInt @i : indexWitnesses @is
{-# INLINE indexWitnesses #-}
type family Fst (a :: (k1,k2)) where Fst '(x,y) = x
type family Snd (a :: (k1,k2)) where Snd '(x,y) = y
type family RLength xs where
RLength '[] = 'Z
RLength (x ': xs) = 'S (RLength xs)
type family RIndex (r :: k) (rs :: [k]) :: Nat where
RIndex r (r ': rs) = 'Z
RIndex r (s ': rs) = 'S (RIndex r rs)
type family RImage (rs :: [k]) (ss :: [k]) :: [Nat] where
RImage '[] ss = '[]
RImage (r ': rs) ss = RIndex r ss ': RImage rs ss
type family RDelete r rs where
RDelete r (r ': rs) = rs
RDelete r (s ': rs) = s ': RDelete r rs
type family RecAll (f :: u -> *) (rs :: [u]) (c :: * -> Constraint) :: Constraint where
RecAll f '[] c = ()
RecAll f (r ': rs) c = (c (f r), RecAll f rs c)
type family (as :: [k]) ++ (bs :: [k]) :: [k] where
'[] ++ bs = bs
(a ': as) ++ bs = a ': (as ++ bs)
type family AllConstrained (c :: u -> Constraint) (ts :: [u]) :: Constraint where
AllConstrained c '[] = ()
AllConstrained c (t ': ts) = (c t, AllConstrained c ts)
class AllSatisfied cs t where
instance AllSatisfied '[] t where
instance (c t, AllSatisfied cs t) => AllSatisfied (c ': cs) t where
type family AllAllSat cs ts :: Constraint where
AllAllSat cs '[] = ()
AllAllSat cs (t ': ts) = (AllSatisfied cs t, AllAllSat cs ts)
type family ApplyToField (t :: Type -> Type) (a :: k1) = (r :: k1) | r -> t a where
ApplyToField t '(s,x) = '(s, t x)
ApplyToField t x = t x
type family MapTyCon t xs = r | r -> xs where
MapTyCon t '[] = '[]
MapTyCon t (x ': xs) = ApplyToField t x ': MapTyCon t xs