{-# LANGUAGE UndecidableInstances #-}
module WebGear.Core.Trait (
Trait (..),
TraitAbsence (..),
Get (..),
Gets,
Linked,
Set (..),
Sets,
linkzero,
linkminus,
unlink,
probe,
plant,
HasTrait (..),
HaveTraits,
pick,
MissingTrait,
) where
import Control.Arrow (Arrow (..))
import Data.Kind (Constraint, Type)
import Data.Tagged (Tagged (..), untag)
import GHC.TypeLits (ErrorMessage (..), TypeError)
class Trait (t :: Type) a where
type Attribute t a :: Type
class Trait t a => TraitAbsence t a where
type Absence t a :: Type
class (Arrow h, TraitAbsence t a) => Get h t a where
getTrait ::
t ->
h (Linked ts a) (Either (Absence t a) (Attribute t a))
class (Arrow h, Trait t a) => Set h (t :: Type) a where
setTrait ::
t ->
(Linked ts a -> a -> Attribute t a -> Linked (t : ts) a) ->
h (Linked ts a, Attribute t a) (Linked (t : ts) a)
type family Gets h ts a :: Constraint where
Gets h '[] a = ()
Gets h (t : ts) a = (Get h t a, Gets h ts a)
type family Sets h ts a :: Constraint where
Sets h '[] a = ()
Sets h (t : ts) a = (Set h t a, Sets h ts a)
data Linked (ts :: [Type]) a = Linked
{ Linked ts a -> LinkedAttributes ts a
linkAttribute :: !(LinkedAttributes ts a)
,
Linked ts a -> a
unlink :: !a
}
type family LinkedAttributes (ts :: [Type]) (a :: Type) where
LinkedAttributes '[] a = ()
LinkedAttributes (t : ts) a = (Attribute t a, LinkedAttributes ts a)
linkzero :: a -> Linked '[] a
linkzero :: a -> Linked '[] a
linkzero = LinkedAttributes '[] a -> a -> Linked '[] a
forall (ts :: [*]) a. LinkedAttributes ts a -> a -> Linked ts a
Linked ()
linkminus :: Linked (t : ts) a -> Linked ts a
linkminus :: Linked (t : ts) a -> Linked ts a
linkminus (Linked (_, rv) a
a) = LinkedAttributes ts a -> a -> Linked ts a
forall (ts :: [*]) a. LinkedAttributes ts a -> a -> Linked ts a
Linked LinkedAttributes ts a
rv a
a
probe ::
forall t ts h a.
Get h t a =>
t ->
h (Linked ts a) (Either (Absence t a) (Linked (t : ts) a))
probe :: t -> h (Linked ts a) (Either (Absence t a) (Linked (t : ts) a))
probe t
t = proc Linked ts a
l -> do
Either (Absence t a) (Attribute t a)
res <- t -> h (Linked ts a) (Either (Absence t a) (Attribute t a))
forall (h :: * -> * -> *) t a (ts :: [*]).
Get h t a =>
t -> h (Linked ts a) (Either (Absence t a) (Attribute t a))
getTrait t
t -< Linked ts a
l
((Linked ts a, Either (Absence t a) (Attribute t a))
-> Either (Absence t a) (Linked (t : ts) a))
-> h (Linked ts a, Either (Absence t a) (Attribute t a))
(Either (Absence t a) (Linked (t : ts) a))
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (Linked ts a, Either (Absence t a) (Attribute t a))
-> Either (Absence t a) (Linked (t : ts) a)
forall e.
(Linked ts a, Either e (Attribute t a))
-> Either e (Linked (t : ts) a)
link -< (Linked ts a
l, Either (Absence t a) (Attribute t a)
res)
where
link :: (Linked ts a, Either e (Attribute t a)) -> Either e (Linked (t : ts) a)
link :: (Linked ts a, Either e (Attribute t a))
-> Either e (Linked (t : ts) a)
link (Linked ts a
_, Left e
e) = e -> Either e (Linked (t : ts) a)
forall a b. a -> Either a b
Left e
e
link (Linked{a
LinkedAttributes ts a
unlink :: a
linkAttribute :: LinkedAttributes ts a
linkAttribute :: forall (ts :: [*]) a. Linked ts a -> LinkedAttributes ts a
unlink :: forall (ts :: [*]) a. Linked ts a -> a
..}, Right Attribute t a
attr) = Linked (t : ts) a -> Either e (Linked (t : ts) a)
forall a b. b -> Either a b
Right (Linked (t : ts) a -> Either e (Linked (t : ts) a))
-> Linked (t : ts) a -> Either e (Linked (t : ts) a)
forall a b. (a -> b) -> a -> b
$ Linked :: forall (ts :: [*]) a. LinkedAttributes ts a -> a -> Linked ts a
Linked{linkAttribute :: LinkedAttributes (t : ts) a
linkAttribute = (Attribute t a
attr, LinkedAttributes ts a
linkAttribute), a
unlink :: a
unlink :: a
..}
plant :: forall t ts h a. Set h t a => t -> h (Linked ts a, Attribute t a) (Linked (t : ts) a)
plant :: t -> h (Linked ts a, Attribute t a) (Linked (t : ts) a)
plant t
t = proc (Linked ts a
l, Attribute t a
attr) -> do
t
-> (Linked ts a -> a -> Attribute t a -> Linked (t : ts) a)
-> h (Linked ts a, Attribute t a) (Linked (t : ts) a)
forall (h :: * -> * -> *) t a (ts :: [*]).
Set h t a =>
t
-> (Linked ts a -> a -> Attribute t a -> Linked (t : ts) a)
-> h (Linked ts a, Attribute t a) (Linked (t : ts) a)
setTrait t
t Linked ts a -> a -> Attribute t a -> Linked (t : ts) a
link -< (Linked ts a
l, Attribute t a
attr)
where
link :: Linked ts a -> a -> Attribute t a -> Linked (t : ts) a
link :: Linked ts a -> a -> Attribute t a -> Linked (t : ts) a
link Linked{a
LinkedAttributes ts a
unlink :: a
linkAttribute :: LinkedAttributes ts a
linkAttribute :: forall (ts :: [*]) a. Linked ts a -> LinkedAttributes ts a
unlink :: forall (ts :: [*]) a. Linked ts a -> a
..} a
a' Attribute t a
attr = Linked :: forall (ts :: [*]) a. LinkedAttributes ts a -> a -> Linked ts a
Linked{linkAttribute :: LinkedAttributes (t : ts) a
linkAttribute = (Attribute t a
attr, LinkedAttributes ts a
linkAttribute), unlink :: a
unlink = a
a'}
class HasTrait t ts where
from :: Linked ts a -> Tagged t (Attribute t a)
instance HasTrait t (t : ts) where
from :: Linked (t : ts) a -> Tagged t (Attribute t a)
from :: Linked (t : ts) a -> Tagged t (Attribute t a)
from (Linked (lv, _) a
_) = Attribute t a -> Tagged t (Attribute t a)
forall k (s :: k) b. b -> Tagged s b
Tagged Attribute t a
lv
instance {-# OVERLAPPABLE #-} HasTrait t ts => HasTrait t (t' : ts) where
from :: Linked (t' : ts) a -> Tagged t (Attribute t a)
from :: Linked (t' : ts) a -> Tagged t (Attribute t a)
from Linked (t' : ts) a
l = Linked ts a -> Tagged t (Attribute t a)
forall t (ts :: [*]) a.
HasTrait t ts =>
Linked ts a -> Tagged t (Attribute t a)
from (Linked ts a -> Tagged t (Attribute t a))
-> Linked ts a -> Tagged t (Attribute t a)
forall a b. (a -> b) -> a -> b
$ Linked (t' : ts) a -> Linked ts a
forall t (ts :: [*]) a. Linked (t : ts) a -> Linked ts a
linkminus Linked (t' : ts) a
l
pick :: Tagged t a -> a
pick :: Tagged t a -> a
pick = Tagged t a -> a
forall k (s :: k) b. Tagged s b -> b
untag
instance TypeError (MissingTrait t) => HasTrait t '[] where
from :: Linked '[] a -> Tagged t (Attribute t a)
from = Linked '[] a -> Tagged t (Attribute t a)
forall a. HasCallStack => a
undefined
type MissingTrait t =
Text "The request doesn't have the trait ‘" :<>: ShowType t :<>: Text "’."
:$$: Text ""
:$$: Text "Did you use a wrong trait type?"
:$$: Text "For e.g., ‘QueryParam \"foo\" Int’ instead of ‘QueryParam \"foo\" String’?"
:$$: Text ""
:$$: Text "Or did you forget to apply an appropriate middleware?"
:$$: Text "For e.g. The trait ‘JSONBody t’ can be used with ‘jsonRequestBody @t’ middleware."
:$$: Text ""
type family HaveTraits ts qs :: Constraint where
HaveTraits '[] qs = ()
HaveTraits (t : ts) qs = (HasTrait t qs, HaveTraits ts qs)