{-# LANGUAGE
GADTs
, LambdaCase
, PatternSynonyms
, PolyKinds
, QuantifiedConstraints
, RankNTypes
, StandaloneDeriving
#-}
module Control.Category.Free
( Path (..)
, pattern (:<<)
, FoldPath (..)
, CFree (..)
, toPath
, reversePath
, beforeAll
, afterAll
, Category (..)
) where
import Data.Quiver
import Data.Quiver.Functor
import Control.Category
import Control.Monad (join)
import Prelude hiding (id, (.))
data Path p x y where
Done :: Path p x x
(:>>) :: p x y -> Path p y z -> Path p x z
infixr 7 :>>
pattern (:<<) :: Path p y z -> p x y -> Path p x z
pattern ps :<< p = p :>> ps
infixl 7 :<<
deriving instance (forall x y. Show (p x y)) => Show (Path p x y)
instance x ~ y => Semigroup (Path p x y) where (<>) = (>>>)
instance x ~ y => Monoid (Path p x y) where mempty = Done
instance Category (Path p) where
id = Done
(.) path = \case
Done -> path
p :>> ps -> p :>> (ps >>> path)
instance QFunctor Path where
qmap _ Done = Done
qmap f (p :>> ps) = f p :>> qmap f ps
instance QFoldable Path where
qfoldMap _ Done = id
qfoldMap f (p :>> ps) = f p >>> qfoldMap f ps
qtoMonoid _ Done = mempty
qtoMonoid f (p :>> ps) = f p <> qtoMonoid f ps
qtoList _ Done = []
qtoList f (p :>> ps) = f p : qtoList f ps
qtraverse_ _ Done = pure id
qtraverse_ f (p :>> ps) = (>>>) <$> f p <*> qtraverse_ f ps
instance QTraversable Path where
qtraverse _ Done = pure Done
qtraverse f (p :>> ps) = (:>>) <$> f p <*> qtraverse f ps
instance QPointed Path where qsingle p = p :>> Done
instance QMonad Path where qjoin = qfold
instance CFree Path
newtype FoldPath p x y = FoldPath
{getFoldPath :: forall q. Category q
=> (forall x y. p x y -> q x y) -> q x y}
instance x ~ y => Semigroup (FoldPath p x y) where (<>) = (>>>)
instance x ~ y => Monoid (FoldPath p x y) where mempty = id
instance Category (FoldPath p) where
id = FoldPath $ \ _ -> id
FoldPath g . FoldPath f = FoldPath $ \ k -> g k . f k
instance QFunctor FoldPath where qmap f = qfoldMap (qsingle . f)
instance QFoldable FoldPath where qfoldMap k (FoldPath f) = f k
instance QTraversable FoldPath where
qtraverse f = getApQ . qfoldMap (ApQ . fmap qsingle . f)
instance QPointed FoldPath where qsingle p = FoldPath $ \ k -> k p
instance QMonad FoldPath where qjoin (FoldPath f) = f id
instance CFree FoldPath
class
( QPointed c
, QFoldable c
, forall p. Category (c p)
) => CFree c where
toPath :: (QFoldable c, CFree path) => c p x y -> path p x y
toPath = qfoldMap qsingle
reversePath :: (QFoldable c, CFree path) => c p x y -> path (OpQ p) y x
reversePath = getOpQ . qfoldMap (OpQ . qsingle . OpQ)
beforeAll
:: (QFoldable c, CFree path)
=> (forall x. p x x) -> c p x y -> path p x y
beforeAll sep = qfoldMap (\p -> qsingle sep >>> qsingle p)
afterAll
:: (QFoldable c, CFree path)
=> (forall x. p x x) -> c p x y -> path p x y
afterAll sep = qfoldMap (\p -> qsingle p >>> qsingle sep)