{-# LANGUAGE KindSignatures, DataKinds, FlexibleInstances, FlexibleContexts,
FunctionalDependencies, TypeFamilies, TypeOperators,
PatternSynonyms, UndecidableInstances, ConstraintKinds,
TypeApplications, ScopedTypeVariables, CPP,
AllowAmbiguousTypes #-}
module Named.Internal where
import Prelude (id, Maybe(..))
import Data.Maybe (fromMaybe)
import Data.Functor.Identity (Identity(..))
import Data.Kind (Type)
import GHC.TypeLits (Symbol, TypeError, ErrorMessage(..))
import GHC.OverloadedLabels (IsLabel(..))
newtype NamedF f (a :: Type) (name :: Symbol) =
ArgF (f a)
pattern Arg :: a -> name :! a
pattern Arg a = ArgF (Identity a)
#if MIN_VERSION_base(4,10,0)
{-# COMPLETE Arg #-}
#endif
type name :! a = NamedF Identity a name
type name :? a = NamedF Maybe a name
class InjValue f where
injValue :: a -> f a
instance InjValue Identity where
injValue = Identity
instance InjValue Maybe where
injValue = Just
instance (name ~ name', a ~ a', InjValue f) => IsLabel name (a -> NamedF f a' name') where
#if MIN_VERSION_base(4,10,0)
fromLabel a = ArgF (injValue a)
#else
fromLabel _ a = ArgF (injValue a)
#endif
{-# INLINE fromLabel #-}
newtype Param p = Param p
instance (p ~ NamedF f a name, InjValue f) => IsLabel name (a -> Param p) where
#if MIN_VERSION_base(4,10,0)
fromLabel a = Param (fromLabel @name a)
#else
fromLabel pName a = Param (fromLabel pName a)
#endif
{-# INLINE fromLabel #-}
(!) :: forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
fn ! p = with p fn
{-# INLINE (!) #-}
infixl 9 !
class WithParam p fn fn' | p fn -> fn' where
with :: Param p -> fn -> fn'
instance WithParam' (Decide p fn) p fn fn' => WithParam p fn fn' where
with (Param p) fn = withParam @(Decide p fn) p fn
{-# INLINE with #-}
data Defaults = Defaults
defaults :: Param Defaults
defaults = Param Defaults
data Name (name :: Symbol) = Name
instance name ~ name' => IsLabel name' (Name name) where
#if MIN_VERSION_base(4,10,0)
fromLabel = Name
#else
fromLabel _ = Name
#endif
{-# INLINE fromLabel #-}
arg :: Name name -> name :! a -> a
arg _ (ArgF (Identity a)) = a
{-# INLINE arg #-}
argF :: Name name -> NamedF f a name -> f a
argF _ (ArgF fa) = fa
{-# INLINE argF #-}
argDef :: Name name -> a -> name :? a -> a
argDef _ d (ArgF fa) = fromMaybe d fa
data DApply
data DFill
data DPass
type family Decide (p :: Type) (fn :: Type) :: [Type] where
Decide (NamedF f' a' name) (NamedF f a name -> r) = '[DApply]
Decide Defaults (NamedF Maybe a name -> r) = DFill : Decide Defaults r
Decide p (x -> r) = DPass : Decide p r
Decide (NamedF f' a' name) t =
TypeError (Text "Named parameter '" :<>: Text name :<>:
Text "' was supplied, but not expected")
Decide Defaults t = '[]
class WithParam' (ds :: [Type]) p fn fn' | ds p fn -> fn' where
withParam :: p -> fn -> fn'
instance fn ~ fn' => WithParam' '[] p fn fn' where
withParam _ = id
{-# INLINE withParam #-}
instance
( WithParam' ds p r r',
fn ~ (p -> r),
fn' ~ r'
) => WithParam' (DApply : ds) p fn fn'
where
withParam p fn = withParam @ds p (fn p)
{-# INLINE withParam #-}
instance
( WithParam' ds p r r',
fn ~ (x -> r),
fn' ~ (x -> r')
) => WithParam' (DPass : ds) p fn fn'
where
withParam a fn = \x -> withParam @ds a (fn x)
{-# INLINE withParam #-}
instance
( WithParam' ds p r r',
fn ~ (NamedF f x name -> r),
fn' ~ r',
f ~ Maybe
) => WithParam' (DFill : ds) p fn fn'
where
withParam p fn = withParam @ds p (fn (ArgF Nothing))
{-# INLINE withParam #-}