{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoStarIsType #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Type.Funspection.Decidable (
EnableIf,
Return(..),
ReturnOf,
CanReturn,
TaggedReturn,
TagReturn,
tagReturn,
UntaggedReturn,
UntagReturn,
untagReturn,
) where
import Data.Kind
import Data.Proxy
type family EnableIf (condition :: Bool) (a :: Type) :: Type where
EnableIf 'True a = a
newtype Return (a :: Type) where
Return :: { unReturn :: a } -> Return a
type family ReturnOf (f :: Type) :: Type where
ReturnOf (a -> b) = ReturnOf b
ReturnOf r = r
type family CanReturn (r :: Type) (f :: Type) :: Bool where
CanReturn r r = 'True
CanReturn r (a -> b) = CanReturn r b
CanReturn r r' = 'False
type family TaggedReturn (r :: Type) (f :: Type) :: Type where
TaggedReturn r r = Return r
TaggedReturn r (a -> b) = a -> TaggedReturn r b
class TagReturn' (f' :: Type) (f :: Type) where
tagReturn' :: Proxy f' -> f -> f'
instance (TagReturn' b' b) => TagReturn' (a -> b') (a -> b) where
tagReturn' ~Proxy f = tagReturn' (Proxy :: Proxy b') . f
instance TagReturn' (Return r) r where
tagReturn' ~Proxy = Return
type TagReturn (r :: Type) (f :: Type) = TagReturn' (TaggedReturn r f) f
tagReturn :: forall r f. (TagReturn r f) => Proxy r -> f -> TaggedReturn r f
tagReturn ~Proxy = tagReturn' (Proxy :: Proxy (TaggedReturn r f))
type family UntaggedReturn (f :: Type) :: Type where
UntaggedReturn (Return r) = r
UntaggedReturn (a -> b) = a -> UntaggedReturn b
class UntagReturn' (f :: Type) where
untagReturn' :: f -> UntaggedReturn f
instance (UntagReturn' b) => UntagReturn' (a -> b) where
untagReturn' f = untagReturn' . f
instance UntagReturn' (Return r) where
untagReturn' = unReturn
type UntagReturn (f :: Type) = UntagReturn' f
untagReturn :: (UntagReturn f) => f -> UntaggedReturn f
untagReturn = untagReturn'