We know free monads are useful, and packages like Operational make it easy to define new monads by only caring about the application-specific effects, not the monadic structure itself.
We can easily define "free arrows" analogous to how free monads are defined:
{-# LANGUAGE GADTs #-}
module FreeA
( FreeA, effect
) where
import Prelude hiding ((.), id)
import Control.Category
import Control.Arrow
import Control.Applicative
import Data.Monoid
data FreeA eff a b where
Pure :: (a -> b) -> FreeA eff a b
Effect :: eff a b -> FreeA eff a b
Seq :: FreeA eff a b -> FreeA eff b c -> FreeA eff a c
Par :: FreeA eff a₁ b₁ -> FreeA eff a₂ b₂ -> FreeA eff (a₁, a₂) (b₁, b₂)
effect :: eff a b -> FreeA eff a b
effect = Effect
instance Category (FreeA eff) where
id = Pure id
(.) = flip Seq
instance Arrow (FreeA eff) where
arr = Pure
first f = Par f id
second f = Par id f
(***) = Par
My question is, what would be the most useful generic operations on free arrows? For my particular application, I needed special cases of these two:
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
analyze :: forall f eff a₀ b₀ r. (Applicative f, Monoid r)
=> (forall a b. eff a b -> f r)
-> FreeA eff a₀ b₀ -> f r
analyze visit = go
where
go :: forall a b. FreeA eff a b -> f r
go arr = case arr of
Pure _ -> pure mempty
Seq f₁ f₂ -> mappend <$> go f₁ <*> go f₂
Par f₁ f₂ -> mappend <$> go f₁ <*> go f₂
Effect eff -> visit eff
evalA :: forall eff arr a₀ b₀. (Arrow arr) => (forall a b. eff a b -> arr a b) -> FreeA eff a₀ b₀ -> arr a₀ b₀
evalA exec = go
where
go :: forall a b. FreeA eff a b -> arr a b
go freeA = case freeA of
Pure f -> arr f
Seq f₁ f₂ -> go f₂ . go f₁
Par f₁ f₂ -> go f₁ *** go f₂
Effect eff -> exec eff
but I don't have any theoretical arguments on why these (and not others) would be the useful ones.
arr id
is justid
– Justin L.first
andsecond
. – Justin L.