{-# OPTIONS_HADDOCK show-extensions #-}
{-# OPTIONS_GHC -Wwarn #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
#if __GLASGOW_HASKELL__ < 710 || FORCE_OU51
{-# LANGUAGE OverlappingInstances #-}
#endif
{-# LANGUAGE FunctionalDependencies, UndecidableInstances #-}
module Data.OpenUnion ( Union
, inj
, prj
, decomp
, Member
, SetMember
, type(<::)
, weaken
) where
import Unsafe.Coerce(unsafeCoerce)
#if __GLASGOW_HASKELL__ > 800
import Data.Kind (Constraint)
import GHC.TypeLits
#else
import GHC.Exts (Constraint)
#endif
data Union (r :: [ * -> * ]) v where
Union :: {-# UNPACK #-} !Int -> t v -> Union r v
{-# INLINE prj' #-}
{-# INLINE inj' #-}
inj' :: Int -> t v -> Union r v
inj' = Union
prj' :: Int -> Union r v -> Maybe (t v)
prj' n (Union n' x) | n == n' = Just (unsafeCoerce x)
| otherwise = Nothing
newtype P t r = P{unP :: Int}
class (FindElem t r) => Member (t :: * -> *) r where
inj :: t v -> Union r v
prj :: Union r v -> Maybe (t v)
#if __GLASGOW_HASKELL__ < 710 || FORCE_OU51
instance (FindElem t r) => Member t r where
{-# INLINE inj #-}
{-# INLINE prj #-}
inj = inj' (unP $ (elemNo :: P t r))
prj = prj' (unP $ (elemNo :: P t r))
#else
instance {-# OVERLAPPING #-} t ~ s => Member t '[s] where
{-# INLINE inj #-}
{-# INLINE prj #-}
inj x = Union 0 x
prj (Union _ x) = Just (unsafeCoerce x)
instance {-# INCOHERENT #-} (FindElem t r) => Member t r where
{-# INLINE inj #-}
{-# INLINE prj #-}
inj = inj' (unP $ (elemNo :: P t r))
prj = prj' (unP $ (elemNo :: P t r))
#endif
type family (<::) (ms :: [* -> *]) r where
(<::) '[] r = (() :: Constraint)
(<::) (m ': ms) r = (Member m r, (<::) ms r)
{-# INLINE [2] decomp #-}
decomp :: Union (t ': r) v -> Either (Union r v) (t v)
decomp (Union 0 v) = Right $ unsafeCoerce v
decomp (Union n v) = Left $ Union (n-1) v
{-# RULES "decomp/singleton" decomp = decomp0 #-}
{-# INLINE decomp0 #-}
decomp0 :: Union '[t] v -> Either (Union '[] v) (t v)
decomp0 (Union _ v) = Right $ unsafeCoerce v
weaken :: Union r w -> Union (any ': r) w
weaken (Union n v) = Union (n+1) v
class FindElem (t :: * -> *) r where
elemNo :: P t r
instance FindElem t (t ': r) where
elemNo = P 0
#if __GLASGOW_HASKELL__ < 710 || FORCE_OU51
instance FindElem t r => FindElem t (t' ': r) where
#else
instance {-# OVERLAPPABLE #-} FindElem t r => FindElem t (t' ': r) where
#endif
elemNo = P $ 1 + (unP $ (elemNo :: P t r))
#if __GLASGOW_HASKELL__ > 800
instance TypeError ('Text "Cannot unify effect types." ':$$:
'Text "Unhandled effect: " ':<>: 'ShowType t ':$$:
'Text "Perhaps check the type of effectful computation and the sequence of handlers for concordance?")
=> FindElem t '[] where
elemNo = error "unreachable"
#endif
class EQU (a :: k) (b :: k) p | a b -> p
instance EQU a a 'True
#if __GLASGOW_HASKELL__ < 710 || FORCE_OU51
instance (p ~ 'False) => EQU a b p
#else
instance {-# OVERLAPPABLE #-} (p ~ 'False) => EQU a b p
#endif
class Member t r => SetMember (tag :: k -> * -> *) (t :: * -> *) r | tag r -> t
instance (EQU t1 t2 p, MemberU' p tag t1 (t2 ': r)) => SetMember tag t1 (t2 ': r)
class Member t r =>
MemberU' (f::Bool) (tag :: k -> * -> *) (t :: * -> *) r | tag r -> t
instance MemberU' 'True tag (tag e) (tag e ': r)
instance (Member t (t' ': r), SetMember tag t r) =>
MemberU' 'False tag t (t' ': r)