Thanks for sharing! I especially like the trick of writing the actions polymorphically and instantiate later.
Reminds me of provenience, in particular the data flow graph. That is what you mean by statically inspect the resulting structure, right? For my use case I needed the graph to hold all intermediate data, not only the labels, so I opted for mapping everything to pandoc.
But provenience definitely shares the pattern of returning Action (Value a). I should try to re-structure the library as a free monad!
Nice! Yeah, being able to render a graph of the network before running it, exactly.
I used this pattern for a Shake-like build system at one job, it had a ‘plan’ mode that would print a plan like Terraform. It could cache some things that were already ran, similar to Make/Shake.
Used the same pattern at another job for a network of Mealy machines which represented economics games like auctions, markets or so, which had a little web app and showed a literal graph with how many people were playing each game and what data was flowing between the games.
For the build system one, I did end up using a free monad and a free applicative, but that was mostly for the fun, I wouldn’t say it’s essential or necessary, though.
That crucially relies on parametricity, I suppose?
Further I noticed that the Value GADT in your post looks like the free Applicative over the Either String functor, which suggests that attaching labels to actions is optional. So does that give the same functionality as sprinkling cost centre annotations in source code?
I believe that the Key constructor isn’t usually constructed but every Action requires a String to act as the label. The Key is used in the graph creation though.
Possibly, which type parameter do you have in mind?
Yeah, I have rewritten the Value type using a free applicative over Key (which has a vacuous Functor). I’m not sure about the Either String functor’s role in this context.
Attaching labels to actions is entirely optional in the sense that the interpretation of the monad could generate unique names on the fly like a compiler does, then the graph would be a1, a2, etc. I can make an example of this, if helpful. (I put names in Action as I thought it’d be easier to digest.)
The example has type forall f. Applicative f => Action f IO something and specializing f = Value makes it possible to extract the graph. In a production environment one could set f = Identity.
Consider
flip Ap . either Key Pure
:: Either String a -> Value (a -> b) -> Value b
This plays the role of Control.Applicative.Free.Ap
EDIT: But you are right: The term
flip Ap . Key . getConst
:: Const String a -> Value (a -> b) -> Value b
works just as well, so Value is more likely the free Applicative over Const.
Right, that is crucial for the example I did. But you can pack both the real running and the graphing into one like this:
So I do think the higher order bit is the having all actions in the API returning and accepting an applicative of some name, like Value a or similar, which unlocks the structure being visible.
The parametrising of the given applicative f I think was an incidental choice. Maybe I should add this to the blog post?
EDIT: though, the graph function builds a gimmie in that example would repeat side effects, due to each action running the inputs it needs, so one would have to be careful not to use it. Perhaps the parametrising is a little cleaner to avoid subtle issues like that.
I’ve enjoyed (something similar to) this too! I wonder if there’s some relationship with Relative Monads, though I suspect they are differently capable.
Also, given that f necessarily has an Applicative instance, Spec could be redefined as:
data Spec f m a where
- Spec :: String -> f i -> (i -> m a) -> Spec f m (f a)
+ Spec :: String -> f (m a) -> Spec f m (f a)
Effectively eliminating the inlined Coyoneda f.
Cascading the changes…
-act :: String -> f i -> (i -> m a) -> Action f m (f a)
-act l i f = Action $ liftF $ liftAp $ Spec l i f
+act :: String -> f (m a) -> Action f m (f a)
+act l fma = Action $ liftF $ liftAp $ Spec l fma
example :: Applicative f => Action f IO (f (ByteString, ByteString))
example = do
- file1 <- act "read_file_1" (pure ()) $ const $ S.readFile "file1.txt"
+ file1 <- act "read_file_1" (pure $ S.readFile "file1.txt")
- file2 <- act "read_file_2" file1 $ S.readFile . unwords . words . S8.unpack
+ file2 <- act "read_file_2" (S.readFile . unwords . words . S8.unpack <$> file1)
pure $ (,) <$> file1 <*> file2
runIO :: Action Identity IO a -> IO a
runIO = foldFree (runAp io) . runAction where
io :: Spec Identity IO x -> IO x
io = \case
- Spec name input act' -> do
+ Spec name input -> do
putStrLn $ "Running " ++ name
- out <- act' $ runIdentity input
+ out <- runIdentity input
pure $ Identity out
An alternative cascade would be to keep the type of act mostly as it was but require Functor f and do an explicit fmap. However the file1 example becomes a bit nicer with act fully altered. ( Note that you could have this version of act even without eliminating the Coyoneda just by passing id for i → m a. )