module Control.DotDotDot
( DotDotDot((...))
, (…)
, IsFun
, Return
, Replace
)
where
import Data.Bool
( Bool(True, False)
)
import Prelude ()
type family IsFun (a :: *) :: Bool where
IsFun (_ -> _) = 'True
IsFun _ = 'False
class b ~ IsFun f => DotDotDot f (b :: Bool) where
type Return (f :: *) (b :: Bool) :: *
type Replace (f :: *) (r :: *) (b :: Bool) :: *
(...) :: (Return f b -> r) -> f -> Replace f r b
infixr 9 ...
instance DotDotDot b (IsFun b) => DotDotDot (a -> b) 'True where
type Return (a -> b) 'True = Return b (IsFun b)
type Replace (a -> b) r 'True = a -> Replace b r (IsFun b)
(...) g f x = g ... f x
instance 'False ~ IsFun a => DotDotDot a 'False where
type Return a 'False = a
type Replace a r 'False = r
(...) f x = f x
(…) ::
(b ~ IsFun f, DotDotDot f b) =>
(Return f b -> r) -> f -> Replace f r b
(…) = (...)
infixr 9 …