{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.API.UVerb.Union
( IsMember
, Unique
, Union
, inject
, eject
, foldMapUnion
, matchUnion
)
where
import Data.Proxy (Proxy)
import Data.SOP.BasicFunctors (I, unI)
import Data.SOP.Constraint
import Data.SOP.NS
import Data.Type.Bool (If)
import Data.Type.Equality (type (==))
import GHC.TypeLits
type Union = NS I
foldMapUnion ::
forall (c :: * -> Constraint) (a :: *) (as :: [*]).
All c as =>
Proxy c ->
(forall x. c x => x -> a) ->
Union as ->
a
foldMapUnion :: forall (c :: * -> Constraint) a (as :: [*]).
All c as =>
Proxy c -> (forall x. c x => x -> a) -> Union as -> a
foldMapUnion Proxy c
proxy forall x. c x => x -> a
go = forall {k} (c :: k -> Constraint) (proxy :: (k -> Constraint) -> *)
(f :: k -> *) (xs :: [k]) m.
All c xs =>
proxy c -> (forall (a :: k). c a => f a -> m) -> NS f xs -> m
cfoldMap_NS Proxy c
proxy (forall x. c x => x -> a
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. I a -> a
unI)
matchUnion :: forall (a :: *) (as :: [*]). (IsMember a as) => Union as -> Maybe a
matchUnion :: forall a (as :: [*]). IsMember a as => Union as -> Maybe a
matchUnion = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. I a -> a
unI forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (x :: k) (xs :: [k]) (f :: k -> *).
UElem x xs =>
NS f xs -> Maybe (f x)
eject
type IsMember (a :: u) (as :: [u]) = (Unique as, CheckElemIsMember a as, UElem a as)
class UElem x xs where
inject :: f x -> NS f xs
eject :: NS f xs -> Maybe (f x)
instance {-# OVERLAPPING #-} UElem x (x ': xs) where
inject :: forall (f :: a -> *). f x -> NS f (x : xs)
inject = forall {k} (a :: k -> *) (x :: k) (xs :: [k]). a x -> NS a (x : xs)
Z
eject :: forall (f :: a -> *). NS f (x : xs) -> Maybe (f x)
eject (Z f x
x) = forall a. a -> Maybe a
Just f x
x
eject NS f (x : xs)
_ = forall a. Maybe a
Nothing
instance {-# OVERLAPPING #-} UElem x xs => UElem x (x' ': xs) where
inject :: forall (f :: a -> *). f x -> NS f (x' : xs)
inject = forall {k} (a :: k -> *) (xs :: [k]) (x :: k).
NS a xs -> NS a (x : xs)
S forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (x :: k) (xs :: [k]) (f :: k -> *).
UElem x xs =>
f x -> NS f xs
inject
eject :: forall (f :: a -> *). NS f (x' : xs) -> Maybe (f x)
eject (Z f x
_) = forall a. Maybe a
Nothing
eject (S NS f xs
ns) = forall {k} (x :: k) (xs :: [k]) (f :: k -> *).
UElem x xs =>
NS f xs -> Maybe (f x)
eject NS f xs
ns
type family CheckElemIsMember (a :: k) (as :: [k]) :: Constraint where
CheckElemIsMember a as =
If (Elem a as) (() :: Constraint) (TypeError (NoElementError a as))
type NoElementError (r :: k) (rs :: [k]) =
'Text "Expected one of:"
':$$: 'Text " " ':<>: 'ShowType rs
':$$: 'Text "But got:"
':$$: 'Text " " ':<>: 'ShowType r
type DuplicateElementError (rs :: [k]) =
'Text "Duplicate element in list:"
':$$: 'Text " " ':<>: 'ShowType rs
type family Elem (x :: k) (xs :: [k]) :: Bool where
Elem _ '[] = 'False
Elem x (x' ': xs) =
If (x == x') 'True (Elem x xs)
type family Unique xs :: Constraint where
Unique xs = If (Nubbed xs == 'True) (() :: Constraint) (TypeError (DuplicateElementError xs))
type family Nubbed xs :: Bool where
Nubbed '[] = 'True
Nubbed (x ': xs) = If (Elem x xs) 'False (Nubbed xs)
_testNubbed :: ( ( Nubbed '[Bool, Int, Int] ~ 'False
, Nubbed '[Int, Int, Bool] ~ 'False
, Nubbed '[Int, Bool] ~ 'True
)
=> a) -> a
_testNubbed :: forall a.
((Nubbed '[Bool, Int, Int] ~ 'False,
Nubbed '[Int, Int, Bool] ~ 'False, Nubbed '[Int, Bool] ~ 'True) =>
a)
-> a
_testNubbed (Nubbed '[Bool, Int, Int] ~ 'False,
Nubbed '[Int, Int, Bool] ~ 'False, Nubbed '[Int, Bool] ~ 'True) =>
a
a = (Nubbed '[Bool, Int, Int] ~ 'False,
Nubbed '[Int, Int, Bool] ~ 'False, Nubbed '[Int, Bool] ~ 'True) =>
a
a