module Data.HSet.Get
( HGet(..)
, HGettable
, AllHGettable
, hgetTagged
) where
import Data.HSet.Type
import Data.Tagged
import GHC.Exts
import TypeFun.Data.List
import TypeFun.Data.Peano
#if !(MIN_VERSION_base(4, 8, 0))
import Control.Applicative
#endif
class (i ~ (IndexOf e els)) => HGet els e i | els i -> e where
hget :: HSet els -> e
instance HGet (e ': els) e 'Z where
hget (HSCons e _) = e
instance (('S i) ~ (IndexOf e (e1 ': els)), HGet els e i)
=> HGet (e1 ': els) e ('S i) where
hget (HSCons _ els) = hget els
type HGettable els e = HGet els e (IndexOf e els)
type family AllHGettable (els :: [k]) (subels :: [k]) :: Constraint where
AllHGettable els '[] = ()
AllHGettable els (e ': subels) = (HGettable els e, AllHGettable els subels)
hgetTagged :: forall proxy label e els
. (HGettable els (Tagged label e))
=> proxy label
-> HSet els
-> e
hgetTagged _ hset =
let x = hget hset
in unTagged (x :: Tagged label e)