Porting Heist to Polysemy (just as an exercise) - Polysemy

Welcome to the Functional Programming Zulip Chat Archive. You can join the chat here.

Kari Pahula

Hi, they suggested on IRC that I'd ask here. I'm trying to make a port of Heist to use Polysemy. Just as an exercise at this point. Heist is an HTML template library which works in two stages and the monad transformer it uses has two type parameters, one for the initialization stage and a second one for the run time type. I'm trying to replicate that by making a data Heist s r a which gets interpreted with Polysemy twice, first for r and then for s.

{-# LANGUAGE TemplateHaskell, OverloadedStrings, BlockArguments #-}
-- Polysemy has a long list of default GHC extensions, I'm omitting them from this

import Data.ByteString (ByteString)
import Data.Map.Strict (Map)
import Polysemy
import Polysemy.State
-- Replace Node with just a String if you'd like to build my code and avoid downloading it
import Xeno.DOM

-- Heist's initialization stage works by making a list of runtime actions and pure bytestring chunks
data Chunk s = Pure ByteString
             | RuntimeString (Sem s ByteString)

-- Heist replaces tags in XML/HTML documents with chunks. That's what "splices" is about.
-- "s" is the runtime type that I've pretty much left up in the air as of yet. "r" is the initialization stage type.
data HeistState s r = HeistState
  { paramNode :: Node
  , splices :: Map ByteString (Sem r [Chunk s])
  }

-- Just a few operations defined at this point
data (Heist s) r a where
  WithLocalSplices :: Map ByteString (r [Chunk s]) -> r a -> (Heist s) r a
  GetParamNode :: (Heist s) r Node
  RunNode :: Node -> (Heist s) r [Chunk s]

makeSem ''Heist

I'm having difficulty writing a runHeist function. What I have so far is this:

runHeist
  :: Member (State (HeistState s r)) r
  => Sem ((Heist s) ': r) a
  -> Sem r a
runHeist = interpretH \case
  WithLocalSplices ss f -> runT $ modify id
  GetParamNode -> undefined
  RunNode n -> undefined

If I use undefined for theWithLocalSplices case then it compiles. But I'm having trouble with making the types fit if I do anything State related. I've just started with Polysemy so it's quite possible that I'm confused about its use.

Georgi Lyubenov // googleson78

so,
in polysemy, all effects have two additional type arguments usually called m and a

data Effect m a where
...

the m bit is what will eventually be Sem <your-effects>
and the a is what value the effect "produces" in each constructor you give (as is traditionally with monads, I guess)

Georgi Lyubenov // googleson78

is the r thing in heist also "the effect stack that HeistT will eventually be run in"?

Georgi Lyubenov // googleson78

woah, you have a mapping from strings to actions

Georgi Lyubenov // googleson78

at the very least you will need to pass an initial state and Node values to runHeist, so that you have something to do in GetParamNode and RunNode (like with the actual runHeistT)
additionally I'm guessing you'll need to look at Tactics/Strategy stuff, if you want to embed other effects in your Heist constructors

another idea that pops to mind:
HeistT seems to be similar a reader over some state, you could also attempt to use the polysemy-provided versions of those as a "middle-man", instead of directly interpreting your effect :thinking: ?

Kari Pahula

Basically my idea is to run Polysemy to get a [Chunk s] and then run Polysemy on that, again.

Kari Pahula

Is the type of my runHeist ok? Another version I used was

Sem ((Heist s) ': (State (HeistState s r) ': r)) a -> Sem (State (HeistState s r) ': r) a

Or is that just the same thing?

Georgi Lyubenov // googleson78

I think if the first one works this one will as well, and vice versa

Kari Pahula

Can you give me some idea how to think about this?

      Expected type: Sem
                       (WithTactics (Heist s) f m (State (HeistState s r) : r)) (f x)
        Actual type: Sem
                       (WithTactics (Heist s) f (Sem r0) (State (HeistState s r) : r))
                       (Sem (Heist s : State (HeistState s r) : r) (f ()))
Kari Pahula

I suppose I'll try to write this with an explicit state parameter. runHeist :: HeistState s r -> ... and so on.

Georgi Lyubenov // googleson78

can't help much here :/ , I've not had to bang my head against this one enough to figure it out.
I can point you to documentation - https://hackage.haskell.org/package/polysemy-1.3.0.0/docs/Polysemy-Internal-Strategy.html
and this blog post is also related - https://reasonablypolymorphic.com/blog/tactics/

perhaps @Love Waern (King of the Homeless) could help

Kari Pahula

I suppose I did start by jumping to the deep end.

Love Waern (King of the Homeless)

@Kari Pahula Can you show me the interpreter you're trying to write?

Love Waern (King of the Homeless)

Or is

runHeist
  :: Member (State (HeistState s r)) r
  => Sem ((Heist s) ': r) a
  -> Sem r a
runHeist = interpretH \case
  WithLocalSplices ss f -> runT $ modify id
  GetParamNode -> undefined
  RunNode n -> undefined

The up-to-date definition?

Kari Pahula

That's all I have for now. Or I do have some (non-compiling) code which calls Map.union on the splices field and such but I don't think it'll add anything if I can't even get runT $ modify id compile.

Love Waern (King of the Homeless)

Can you describe whatWithLocalSplices should do?

Love Waern (King of the Homeless)

As in, if you call withLocalSplices, how should it act?

Kari Pahula

Run Map.union on the initial splices and the first parameter, update the state with that, call the second parameter, restore splices to what they were and return the result of the action performed.

Love Waern (King of the Homeless)

Sounds like Reader (HeistState s r) is a better fit as underlying effect rather than State (HeistState s r). I'll try to work something out with that.

Kari Pahula

The full version would make state alterations in fas well which would be preserved. Like log errors encountered during the initialization.

Love Waern (King of the Homeless)

Oh, hmm. Is it ok if the type of the computations suspended in the splices are tied to the Heist effect? Like this:

data Heist s r m a where
  WithLocalSplices :: Map ByteString (Sem r [Chunk s]) -> m a -> (Heist s r) m a
  GetParamNode :: (Heist s r) m Node
  RunNode :: Node -> (Heist s r) m [Chunk s]

Note the extra type variable and change to WithLocalSplices. Because if this is not ok... you've just run into one of the shortcomings of the Effect Handlers In Scope basis that Polysemy is built upon.

Kari Pahula

That looks quite alright. I didn't think of trying that.

Love Waern (King of the Homeless)

Actually, when I think about it, there's another way to go about it that keeps your original definition. But your effect is special enough that you've fallen straight into the weirdest part of polysemy.

Love Waern (King of the Homeless)

Oh wait, no, that would require importing Polysemy.Internal and Polysemy.Internal.Union. interpretH isn't powerful enough. Nevermind, then. I'll go with the modified definition.

runHeist
  :: Member (State (HeistState s r)) r
  => Sem ((Heist s r) ': r) a
  -> Sem r a
runHeist = interpretH \case
  WithLocalSplices ss m -> do
    node <- gets paramNode
    oldSplices <- gets splices
    put $! HeistState node (union ss oldSplices)
    m' <- runT m
    fa <- raise $ runHeist m'
    put $! HeistState node oldSplices
    return fa
  GetParamNode -> gets paramNode >>= pureT
  RunNode n -> undefined
Love Waern (King of the Homeless)

The node is used to index into the splices, right? How do you get the ByteStringkey out of the node?

Kari Pahula

If the parameter is a node that's found in the splices map, return that [Chunk s]. Otherwise, generate start and end tags as Pure ByteString chunks and call runNode on the child nodes. I've so far mirrored the basic functions from https://hackage.haskell.org/package/heist-1.1.0.1/docs/Heist-Compiled.html

But I think I can continue from here on my own. This has been educational and it's gratifying to hear that I wasn't completely off base. Thank you.

Love Waern (King of the Homeless)

there's one final part that might trip you up; running the Sem actions suspended in the splices map.

Love Waern (King of the Homeless)

Assuming Node is replaced by ByteString in RunNode, here's how it would look:

  RunNode n -> do
    msplices <- gets (lookup n . splices)
    case msplices of
      Just sem -> raise sem
      _ -> pure []
Love Waern (King of the Homeless)

Inside of interpretH, the monad in use is Sem (WeirdEffectUsedByInterpretH ': r), and not Sem r directly. So to run the Sem r actions stored in the splices, you need to raise them to convert them to Sem (WeirdEffectUsedByInterpretH ': r).

Kari Pahula

Awesome. I need to call it a day now but I can assume that I'll have more questions later. Now that I started with this I can't quit before I have polysemy-heist on Hackage.

Love Waern (King of the Homeless)

Last clarifications: runT is only ever used to convert the higher-order parameters to actions, which is why runT $ modify id didn't work. It also returns a Sem (e ': r) action, which is why you need to recursively use runHeist and run the result to actually run the higher-order parameter provided to WithLocalSplices.

Love Waern (King of the Homeless)

I admit, InterpretH andTactical isn't the most intuitive thing in the world.

Kari Pahula

It looked like something I'd need. At least superficially.

Love Waern (King of the Homeless)

Another edit to the interpreter I gave above: I forgot you also need to use raise following a runT.
If that implementation doesn't work for whatever reason, then come back and I'll look more at it.

Love Waern (King of the Homeless)

Eventually, I'll have time to work on polysemy v2.0. A guide to Tactics will be part of it, so the weird stuff about interpretH gets properly explained.

Kari Pahula

I ended up using

pureT =<< maybe (pure []) raise msplices

for the RunNode case. (pure =<<) is, of course, just id, so I found it puzzling. I'll build an intuition to this yet.

Kari Pahula

Right, it was also in the GetParamNode case. Curious.

Kari Pahula

I came back to try out this thing again. Unfortunately I have lost the code I had back them and now I'm trying to retrace my steps. I'm quite sure I had something that compiled back then but I'm getting "Could not deduce (Member (State (HeistState s0 r0)) r) from Member (State (HeistState s r)) r" now and I'm not sure what to do about it.

import Data.Map
import Polysemy
import Polysemy.State
import Text.XmlHtml

data Chunk s = Pure String
             | RuntimeString (Sem s String)

data HeistState s r = HeistState
  { paramNode :: Node
  , splices :: Map String (Sem r [Chunk s])
  }

data Heist s r m a where
  WithLocalSplices :: Map String (Sem r [Chunk s]) -> m a -> (Heist s r) m a

runHeist
  :: Member (State (HeistState s r)) r
  => Sem ((Heist s r) ': r) a
  -> Sem r a
runHeist = interpretH \case
  WithLocalSplices ss m -> do
    node <- gets paramNode
    oldSplices <- gets splices
    put $! HeistState node (union ss oldSplices)
    m' <- runT m
    fa <- raise $ runHeist m'
    put $! HeistState node oldSplices
    return fa

Anyone have any advice how to make this work? My idea (following along with what Heist library does) is run runHeiston program initialization and get something that I would run again to get HTML output to generate responses for requests.

TheMatten

Kari Pahula said:

I came back to try out this thing again. Unfortunately I have lost the code I had back them and now I'm trying to retrace my steps. I'm quite sure I had something that compiled back then but I'm getting "Could not deduce (Member (State (HeistState s0 r0)) r) from Member (State (HeistState s r)) r" now and I'm not sure what to do about it.

Anyone have any advice how to make this work? My idea (following along with what Heist library does) is run runHeiston program initialization and get something that I would run again to get HTML output to generate responses for requests.

Do you have polysemy plugin running?

Sridhar Ratnakumar

What do you use Heist for, @Kari Pahula ? Heist is an underrated library, that is also sadly not being maintained anymore.

Kari Pahula

https://gitlab.com/piperka/piperka uses it. Though I don't expect rewriting it for Polysemy.