I’ve been playing around with the TangleT
monad transformer for the last couple days. It seems pretty interesting, but I haven’t been able to find any papers or blog posts about it, so I thought I’d ask if anyone had any pointers.
TangleT
can be thought of as the “Dynamic Programming Monad Transformer” or the “Memoization Monad Transformer”. I first saw TangleT in the extensible
package, but there is a simpler formation that I haven’t yet been able to find on Hackage. In the rest of this post I explain what I’ve figured out so far about these data types, as well as follow-up with some questions I still have.
TangleT from extensible
The extensible
package from Fumiaki Kinoshita provides a rich library of open sum types, open product types, and extensible records.
The TangleT
monad transformer is provided by this package:
newtype TangleT xs h m a = TangleT
{ unTangleT :: RWST (xs :& Comp (TangleT xs h m) h) () (xs :& Nullable h) m a }
This is somewhat complicated if you’re not familiar with extensible
(and probably somewhat complicated even if you are familiar with extensible
), so in the next section I introduce a simpler version of this data type.
Simpler TangleT
A simpler version of TangleT
may look like the following:
newtype Wrangle a = Wrangle { unWrangle :: [Wrangle String] -> IO a }
There is one important operation that this monad gives:
hitchAt :: Int -> Wrangle String
The running function looks like this:
runWrangle :: [Wrangle String] -> IO [String]
Wrangle
is a monad that lets you build up a list of String
s recursively, while using hitchAt
to get other String
s from the list.
Here is an example of using it, along with inline comments:
example1 :: IO ()
example1 = do
strings <- runWrangle myWrangle
print strings
where
myWrangle :: [Wrangle String]
myWrangle =
[ do
-- Get the 3rd String from this list. This causes the third
-- computation in this list to be evaluated.
thirdStr <- hitchAt 2
pure $ "in first, got third: " <> thirdStr
, pure "second string"
, do
-- read in a string from the user
lift $ putStr "in third, asking for string: "
str <- lift getLine
pure str
]
Running this would look like the following:
> example1
in third, asking for string: foo
in third, asking for string: bar
["in first, got third: foo", "second string", "bar"]
You can see how Wrangle
allows you to build up a list of computations that returns Strings
, but where all the computations can use hitchAt
to refer to other elements in the list.
This formulation of Wrangle
is a little easier to understand than TangleT
, but it is not useful. We can’t easily use Wrangle
as a dynamic programming monad.
In the above example1
, you see that the third element of myWrangle
is evaluated twice, asking the user to input two strings. In order to use this for dynamic programming, we’d like the value of each computation to be memoized, so it is only ever evaluated once.
Memoized Wrangle: Mangle
Mangle
carries around a list of Maybe String
as a State
monad:
newtype Mangle a = Mangle
{ unMangle :: [Mangle String] -> [Maybe String] -> IO (a, [Maybe String]) }
The type signatures on hitchAt
and runMangle
are the same as the above, but now hitchAt
is also responsible for updating the [Maybe String]
list whenever it is called.
example1
would look exactly the same as above (just replacing Wrangle
with Mangle
), but now running it is slightly different:
> example1
in third, asking for string: foo
["in first, got third: foo", "second string", "foo"]
You can see that the third element in the list only gets evaluated once, so the user is only asked to input a string once. The user inputs foo
, and this gets memoized.
Generalizations
There are a couple generalizations we can make to Mangle
.
First, we can make it a monad transformer (instead of hard-coding to run in IO
):
newtype TwogleT m a = TwogleT
{ unTwogleT :: [TwogleT m String] -> [Maybe String] -> m (a, [Maybe String]) }
hitchAt
and the run function are similar to above.
You can also stop hard-coding String
, and instead use any type:
newtype ToogleT b m a = ToogleT
{ unToogleT :: [ToogleT b m b] -> [Maybe b] -> m (a, [Maybe b]) }
hitchAt
and the run function are still similar to above.
The most interesting generalization is making it be able to build up any data structure, not just lists:
newtype StoogleT f b m a = StoogleT
{ unStoogleT :: f (StoogleT b m b) -> f (Maybe b) -> m (a, f (Maybe b)) }
This changes the type signatures of hitchAt
and the run function:
hitchAt
:: forall f b m
. Monad m
=> (forall x. Traversal' (f x) x)
-> StoogleT f b m (Maybe b)
The first argument to hitchAt
is a Traversal'
. This would generally be the Traversal
produced by ix
.
The run function is generalized to work with any TraversableWithIndex
:
runStoogleT
:: forall b f i m
. TraverableWithIndex i f
=> f (Stoogle f b m b)
-> m (f b)
This allows you build up not only lists in f
, but any data structure that is TraversableWithIndex
, including Map
s, Vector
s, multi-dimensional arrays, etc. This is quite convenient, given that these types of data structures are often used in dynamic programming problems.
(Actually, the constraints on runStoogleT
are somewhat of a lie. You also need a constraint similar to forall x. Ixed (f x)
, which would let you use [ix
] on the f (Stoogle f b m b)
argument. However, type families are involved in Ixed
, so it is not possible to write this type of constraint.)
Questions / Additional Observations
I’ve been playing around with TangleT
for a while, but I still have some fundamental questions:
-
Is the
StoogleT
type above some sort of specialization of a more general or well-known data type?The only reference I’ve seen to a type like this is a paper that uses it as a memoization monad in section 4.2.
-
I don’t know if I’ve ever seen a recursive type where the recursion happens in a negative position. Are there any other good examples of common data types that do this?
I was also somewhat surprised that the recursion isn’t polymorphic on the
a
, but it makes sense why this can’t be the case (can’t write theFunctor
instance). -
The running function is monomorphic in the
b
(which wasString
above). This makes it feel somewhat similar toContT
. -
I’ve seen
MonadFix
used for doing recursive monadic stuff, butStoogleT
doesn’t useMonadFix
anywhere. Is there some relation betweenStoogleT
andMonadFix
? -
Is there some relationship to hyperfunctions? I asked if anyone was familiar with
TangleT
on the FP Chat Slack, and someone pointed me to hyperfunctions. However, I couldn’t really figure out a way to makeTangleT
into a hyperfunction. -
Is there some comonadic version of
StoogleT
that does something interesting?
Full Code
While I don’t have any clean, understandable code implementing the above, I do have some hacky, hard-to-understand code that implements the various flavors of TangleT
I show above:
-
Implementations of some of the above: https://github.com/cdepillabout/hacky-extensible/blob/d6304d4e40d63fcceb6bdc8e1c63516721902029/src/Lib.hs#L497
-
Using
StoogleT
to solve a Advent of Code 2020 Day 10, which is a dynamic programming problem: https://github.com/cdepillabout/advent-of-code/blob/4678b23066e8d949a2a8f1a00141d1780e89d0d6/2020/haskell/app/Day10.hs#L303