sorpaas
sorpaas

Reputation: 43

Reducing over Monads in Haskell

Suppose I have a type defined as:

data Node = forall a b. Node (SimpleWire a b)

The SimpleWire is a monad, where a represents the inputs, and b represents the outputs. I can do function commposition over that monad. So suppose I have wireA of type SimpleWire A B, and wireB of type SimpleWire B C, doing wireA . wireB would give me the type SimpleWire A C.

Now I want to fold over a list of that monad (so of type [Node] for this case). Something like:

buildGraph :: [Node] -> (SimpleWire a b)
buildGraph (Node h):t = h . (buildGraph t)

How do I make this code work in Haskell's type system?

Upvotes: 2

Views: 267

Answers (2)

badcook
badcook

Reputation: 3739

I'm going to assume the following story:

You probably used the type

data Node = forall a b. Node (SimpleWire a b)

instead of just SimpleWire a b because you wanted a list of SimpleWire's where a and b are different. In particular, what you were really hoping for as the argument to buildGraph was something like (in pseudo-Haskell)

buildGraph :: [SimpleWire a b, SimpleWire b c, ..., SimpleWire x y] -> SimpleWire a y

You couldn't express that first list with Haskell's standard homogeneous [] though and tried to use universally-quantified types to get you out of that pickle.

If what I've said is true, you're probably looking for type-threaded lists or "thrists". In particular, you can do away with Node altogether. A Thrist (->) a b is a list of functions a -> a1, a1 -> a2, ..., an -> b. More generally a Thrist f a b is a list of fs f a a1, f a1 a2, ..., f an b.

{-# LANGUAGE GADTs #-}
import qualified Data.Thrist as DT

-- Note that I'll be using (>>>) as a flipped form of (.), i.e. 
-- (>>>) = flip (.)
-- (>>>) is in fact an Arrow operation which is significantly more general
-- than function composition. Indeed your `SimpleWire` type is almost
-- definitely an arrow.
import Control.Arrow ((>>>))

-- A simple take on SimpleWire
type SimpleWire = (->)

-- Ugh a partial function that blows up if the thrist is empty
unsafeBuildGraph :: DT.Thrist SimpleWire a b -> SimpleWire a b
unsafeBuildGraph = DT.foldl1Thrist (>>>)

-- Making it total
buildGraph :: DT.Thrist SimpleWire a b -> Maybe (SimpleWire a b)
buildGraph DT.Nil = Nothing
buildGraph (wire `DT.Cons` rest) = Just $ DT.foldlThrist (>>>) wire rest

-- For syntactic sugar
(*::*) = DT.Cons
infixr 6 *::*

trivialExample :: DT.Thrist SimpleWire a a
trivialExample = id *::* id *::* DT.Nil

lessTrivialExample :: (Num a, Show a) => DT.Thrist SimpleWire a String
lessTrivialExample = (+ 1) *::* (* 2) *::* show *::* DT.Nil

-- result0 is "12"
result0 = (unsafeBuildGraph lessTrivialExample) 5

-- result1 is Just "12"
result1 = fmap ($ 5) (buildGraph lessTrivialExample)

A side note:

Although SimpleWire may very well be a monad, that's probably not going to directly help you. In particular while functions are monads, what you seem to care about is generalizing over the notion of function composition, which is what arrows are for (and which bear only an indirect relationship to monads). There are hints of this in the fact that I used >>> and that Thrist has an Arrow instance. As I mention in the comments to the code, SimpleWire is probably an Arrow.

Upvotes: 6

chi
chi

Reputation: 116139

We can not compose [Node] with the proposed types. This is because otherwise we would get

sw1 :: SimpleWire A B
sw2 :: SimpleWire C D
buildGraph :: [Node] -> (SimpleWire a b)
buildGraph [ sw1, sw2 ] :: SimpleWire E F

Which is way too strong. We were able to compose arbitrary, incompatible types (wrong), and then to result with a random write at the very end (wrong).

The problem is that we lost all the type information in the [Node] type. We need to remember some, namely:

  1. The first and last wire types are known (the intermediate ones are not)
  2. In the list, every adjacent node is composable

So, we get a custom GADT list type

data NodeList a b where
   Nil  :: NodeList a a
   Cons :: Node a b -> NodeList b c -> NodeList a c

And then

buildGraph :: NodeList a b -> SimpleWire a b
buildGraph Nil = id  
buildGraph (Cons (Node h) t) = h . buildGraph t

Upvotes: 6

Related Questions