{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
module Haskus.Utils.EGADT where
import Unsafe.Coerce
import Haskus.Utils.Monad
import Haskus.Utils.Variant
import Haskus.Utils.VariantF
import Haskus.Utils.Types
newtype EGADT fs t = EGADT (HVariantF fs (EGADT fs) t)
newtype HVariantF (fs :: [ (k -> Type) -> ( k -> Type) ]) (ast :: k -> Type) (t :: k)
= HVariantF (VariantF (ApplyAll ast fs) t)
toHVariantAt
:: forall i fs ast a
. KnownNat i
=> (Index i fs) ast a -> VariantF (ApplyAll ast fs) a
{-# INLINABLE toHVariantAt #-}
toHVariantAt a = VariantF (Variant (natValue' @i) (unsafeCoerce a))
fromHVariantAt
:: forall i fs ast a
. KnownNat i
=> VariantF (ApplyAll ast fs) a -> Maybe ((Index i fs) ast a)
{-# INLINABLE fromHVariantAt #-}
fromHVariantAt (VariantF (Variant t a)) = do
guard (t == natValue' @i)
return (unsafeCoerce a)
type instance HBase (EGADT xs) = HVariantF xs
instance HFunctor (HVariantF xs) => HRecursive (EGADT xs) where
hproject (EGADT a) = a
instance HFunctor (HVariantF xs) => HCorecursive (EGADT xs) where
hembed = EGADT
type family f :<! fs :: Constraint where
f :<! fs = ( MemberAtIndex (IndexOf f fs) f fs )
type family MemberAtIndex (i :: Nat) f fs :: Constraint where
MemberAtIndex i f fs = ( KnownNat i, Index i fs ~ f )
type family (:<<!) xs ys :: Constraint where
'[] :<<! ys = ()
(x ': xs) :<<! ys = (x :<! ys, xs :<<! ys)
pattern VF :: forall e a f fs.
( e ~ EGADT fs a
, f :<! fs
) => f (EGADT fs) a -> EGADT fs a
pattern VF x <- ( ( \ ( EGADT (HVariantF v) ) -> fromHVariantAt @(IndexOf f fs) @fs v ) -> Just x )
where
VF x = EGADT (HVariantF (toHVariantAt @(IndexOf f fs) @fs x))