{-# LANGUAGE FunctionalDependencies #-}
module Data.Row.Switch
  (
    Switch(..)
  )
where
import Data.Row.Internal
import Data.Row.Records
import Data.Row.Variants
class Switch (v :: Row *) (r :: Row *) x | v x -> r, r x -> v where
  {-# MINIMAL switch | caseon #-}
  
  
  
  switch :: Var v -> Rec r -> x
  switch = flip caseon
  
  caseon :: Rec r -> Var v -> x
  caseon = flip switch
instance Switch (R '[]) (R '[]) x where
  switch = const . impossible
instance (KnownSymbol l, Switch (R v) (R r) b)
      => Switch (R (l :-> a ': v)) (R (l :-> (a -> b) ': r)) b where
  switch v r = case trial v l of
    Left x  -> (r .! l) x
    Right v -> switch v (unsafeRemove l r)
    where l = Label @l