The Haskell RNG and state - haskell

As a Java person learning Haskell I was getting use to the new way of thinking about everything but I've spent half a day trying to implement something with a simple RNG and am getting nowhere. In Java I could crate a static RNG and call it with Classname.random.nextInt(10) and it would meet these criteria:
I wouldn't have to keep a reference to the RNG and I could call it ad-hoc (even from inside a loop or a recursive function)
It would produce a new random number every time it was called
It would produce a new set of random numbers every time the project executed
So far in Haskell I'm facing the classic programmers dilemma - I can have 2/3. I'm still learning and have absolutely no idea about Monads, except that they might be able to help me here.
My Most recent attempt has been this:
getRn :: (RandomGen g) => Int -> Int -> Rand g Int
getRn lo hi= getRandomR (lo,hi)
--EDIT: Trimming my questions so that it's not so long winded, replacing with a summary and then what I ended up doing instead:
After creating a bunch of random cities (for TSP), I maped over them with a function createEdges that took a city and connected it to the rest of the cities: M.mapWithKey (\x y -> (x,(createEdges y [1..3] makeCountry)))
PROBLEM:
I wanted to replace [1..3] with something random. I.e. I wanted to map randomness (IO) over pure code. This caused no end of confusion for me (see people's attempt to answer me below to get a good sense of my confusion). In fact I'm still not even sure if I'm explaining the problem correctly.
I was getting this type of error: Couldn't match expected type [Int] with actual type IO [Int]
SOLUTION:
So after finding out that what I wanted to do was fundamentally wrong in a functional environment, I decided to change my approach. Instead of generating a list of cities and then applying randomness to connect them, I instead created an [[Int]] where each inner list represented the random edges. Thereby creating my randomness at the start of the process, rather than trying to map randomness over the pure code.
(I posted the final result as my own answer, but SO won't let me accept my own answer yet. Once it does I've reached that threshold I'll come back and accept)

You can work with random numbers without any monads or IO at all if you like.
All you have to know is, that as there is state (internal state of the random-number-generator) involved you have to take this state with you.
In my opinion the easiest framework for this is Sytem.Random.
Using this your getRn function could look like this:
getRn :: (RandomGen g) => Int -> Int -> g -> (Int, g)
getRn lo hi g = randomR (lo,hi) g
here you can view g as the state I mentioned above - you put it in and you get another back like this (in ghci):
> let init = mkStdGen 11
> let (myNr, nextGen) = getRn 1 6 init
> myNr
6
> let (myNr, nextGen') = getRn 1 6 nextGen
> myNr
4
I think you can start by using just this - thread the gen around and later when you get all the monad stuff come back and make it a bit easier to write/read.
I don't know the definitions of your data but here is a simple example that uses this technique:
module StackOQuestion where
import System.Random
getRn :: (RandomGen g) => Int -> Int -> g -> (Int, g)
getRn lo hi = randomR (lo,hi)
getRnList :: (RandomGen g) => (g -> (a, g)) -> Int -> g -> ([a], g)
getRnList f n g
| n <= 0 = ([], g)
| otherwise = let (ls, g') = getRnList f (n-1) g
(a, g'') = f g'
in (a:ls, g'')
type City = (Int, Int)
randomCity :: (RandomGen g) => g -> (City, g)
randomCity g =
let (f, g') = getRn 1 6 g
(s, g'') = getRn 1 6 g'
in ((f, s), g'')
randomCities :: (RandomGen g) => (Int, Int) -> g -> ([City], g)
randomCities (minC, maxC) g =
let (count, g') = getRn minC maxC g
in getRnList randomCity count g'
and you can test it like this:
> let init = mkStdGen 23
> randomCities (2,6) init
([(4,3),(1,2)],394128088 652912057)
As you can see this creates two Cities (here simply represented as an integer-pair) - for other values of init you will get other answers.
If you look the right way at this you can see that there is already the beginning of a state-monad there (the g -> ('a, g) part) ;)
PS: mkStdGen is a bit like the Random-initialization you know from Java and co (the part where you usually put your system-clock's tick-count in) - I choose 11 because it was quick to type ;) - of course you will always get the same numbers if you stick with 11 - so you will need to initialize this with something from IO - but you can push this pack to main and keep pure otherwise if you just pass then g around

I would say if you want to work with random numbers, the easiest thing to do is to use an utility library like Control.Monad.Random.
The more educational, work intensive path is to learn to write your own monad like that. First you want to understand the State monad and get comfortable with it. I think studying this older question (disclaimer: I have an answer there) may be a good starting point for studying this. The next step I would take is to be able to write the State monad on my own.
After that, the next exercise I would try is to write a "utility" monad for random number generation. By "utility" monad what I mean is a monad that basically repackages the standard State monad with an API that makes it easier for that specific task. This is how that Control.Monad.Random package is implemented:
-- | A monad transformer which adds a random number generator to an
-- existing monad.
newtype RandT g m a = RandT (StateT g m a)
Their RandT monad is really just a newtype definition that reuses StateT and adds a few utility functions so that you can concentrate on using random numbers rather than on the state monad itself. So for this exercise, you basically design a random number generation monad with the API you'd like to have, then use the State and Random libraries to implement it.

Edit: After a lot more reading and some extra help from a friend, I finally reduced it to this solution. However I'll keep my original solution in the answer as well just in case the same approach helps another newbie like me (it was a vital part of my learning process as well).
-- Use a unique random generator (replace <$> newStdGen with mkStdGen 123 for testing)
generateTemplate = createCitiesWeighted <$> newStdGen
-- create random edges (with weight as pair) by taking a random sized sample of randoms
multiTakePair :: [Int] -> [Int] -> [Int] -> [[(Int,Int)]]
multiTakePair ws (l:ls) is = (zip chunka chunkb) : multiTakePair remaindera ls remainderb
where
(chunkb,remainderb) = splitAt l is
(chunka,remaindera) = splitAt l ws
-- pure version of utilizing multitake by passing around an RNG using "split"
createCitiesWeighted :: StdGen -> [[(Int,Int)]]
createCitiesWeighted gen = take count result
where
(count,g1) = randomR (15,20) gen
(g2,g3) = split g1
cs = randomRs (0, count - 2) g1
es = randomRs (3,7) g2
ws = randomRs (1,10) g3
result = multiTakePair ws es cs
The original solution -----
As well as #user2407038's insightful comments, my solution relied very heavily on what I read from these two questions:
Sampling sequences of random numbers in Haskell
Random Integer in Haskell
(NB. I was having an issue where I couldn't work out how to randomize how many edges each city would have, #AnrewC provided an awesome response that not only answered that question but massively reduce excess code)
module TspRandom (
generateCityTemplate
) where
import Control.Monad (liftM, liftM2) -- promote a pure function to a monad
-- #AndrewC's suggestion
multiTake :: [Int] -> [Int] -> [[Int]]
multiTake (l:ls) is = chunk : multiTake ls remainder
where (chunk,remainder) = splitAt l is
-- Create a list [[Int]] where each inner int is of a random size (3-7)
-- The values inside each inner list max out at 19 (total - 1)
createCities = liftM (take 20) $ liftM2 multiTake (getRandomRs (3,7)) (getRandomRs (0, 19))
-- Run the generator
generateCityTemplate = do
putStrLn "Calculating # Cities"
x <- createCities
print x
return ()

The state monad is actually very simple. It is just a function from a state to a value and a new state, or:
data State s a = State {getState :: s -> (s, a)}
In fact, this is exactly what the Rand monad is. It isn't necessary to understand the mechanics of State to use Rand. You shouldn't be evaluating the Rand inside of IO, just use it directly, using the same do notation you have been using for IO. do notation works for any monad.
createCities :: Rand StdGen Int
createCities = getRn minCities maxCities
x :: Cities -> X
x = ...
func :: Rand StdGen X
func = do
cities <- createCities
return (x cities)
-- also valid
func = cities <$> createCities
func = createCities >>= return . x
You can't write getConnections like you have written it. You must do the following:
getConnections :: City -> Country -> Rand StdGen [Int]
getConnections c country = do
edgeCount <- createEdgeCount
fromIndecies [] edgeCount (citiesExcludeSelf c country)
Any function which calls getConnections will have to also return a value of type Rand StdGen x. You can only get rid of it once you have written the entire algorithm and want to run it.
Then, you can run the result using evalRandIO func, or, if you want to test some algorithm and you want to give it the same inputs on every test, you can use evalRand func (mkStdGen 12345), where 12345, or any other number, is your seed value.

Related

How and when to use State functor and State applicative?

I've seen the Maybe and Either functor (and applicative) used in code and that made sense, but I have a hard time coming up with an example of the State functor and applicative. Maybe they are not very useful and only exist because the State monad requires a functor and an applicative? There are plenty of explanations of their implementations out there but not any examples when they are used in code, so I'm looking for illustrations of how they might be useful on their own.
I can think of a couple of examples off the top of my head.
First, one common use for State is to manage a counter for the purpose of making some set of "identifiers" unique. So, the state itself is an Int, and the main primitive state operation is to retrieve the current value of the counter and increment it:
-- the state
type S = Int
newInt :: State S Int
newInt = state (\s -> (s, s+1))
The functor instance is then a succinct way of using the same counter for different types of identifiers, such as term- and type-level variables in some language:
type Prefix = String
data Var = Var Prefix Int
data TypeVar = TypeVar Prefix Int
where you generate fresh identifiers like so:
newVar :: Prefix -> State S Var
newVar s = Var s <$> newInt
newTypeVar :: Prefix -> State S TypeVar
newTypeVar s = TypeVar s <$> newInt
The applicative instance is helpful for writing expressions constructed from such unique identifiers. For example, I've used this approach pretty frequently when writing type checkers, which will often construct types with fresh variables, like so:
typeCheckAFunction = ...
let freshFunctionType = ArrowType <$> newTypeVar <*> newTypeVar
...
Here, freshFunctionType is a new a -> b style type with fresh type variables a and b that can be passed along to a unification step.
Second, another use of State is to manage a seed for random number generation. For example, if you want a low-quality but ultra-fast LCG generator for something, you can write:
lcg :: Word32 -> Word32
lcg x = (a * x + c)
where a = 1664525
c = 1013904223
-- monad for random numbers
type L = State Word32
randWord32 :: L Word32
randWord32 = state $ \s -> let s' = lcg s in (s', s')
The functor instance can be used to modify the Word32 output using a pure conversion function:
randUniform :: L Double
randUniform = toUnit <$> randWord32
where toUnit w = fromIntegral w / fromIntegral (maxBound `asTypeOf` w)
while the applicative instance can be used to write primitives that depend on multiple Word32 outputs:
randUniform2 :: L (Double, Double)
randUniform2 = (,) <$> randUniform <*> randUniform
and expressions that use your random numbers in a reasonably natural way:
-- area of a random triangle, say
a = areaOf <$> (Triangle <$> randUniform2 <*> randUniform2 <$> randUniform2)

Avoiding thunks in sparsely evaluated list generated by monadic unfold

I have a simulation library that uses the FFI wrapped in a monad M, carrying a context. All the foreign functions are pure, so I've decided to make the monad lazy, which is normally convenient for flow-control. I represent my simulation as a list of simulation-frames, that I can consume by either writing to a file, or by displaying the frame graphically.
simulation :: [(Frame -> M Frame)] -> Frame -> M [Frame]
simulation [] frame = return [frame]
simulation (step:steps) frame
= step frame >>= fmap (frame:) . simulation steps
Each frame consists of a tuple of newtype-wrapped ForeignPtrs that I can lift to my Haskell representation with
lift :: Frame -> M HFrame
Since the time-steps in my simulation are quite short, I only want to look at every n frames, for which I use
takeEvery n l = foldr cons nil l 0 where
nil _ = []
cons x rest 0 = x : rest n
cons x rest n = rest (n-1)
So my code looks something like
main = consume
$ takeEvery n
$ runM
$ simulation steps initialFrame >>= mapM lift
Now, the problem is that as I increase n, a thunk builds up. I've tried a couple of different ways to try to strictly evaluate each frame in simulation, but I have yet to figure out how to do so. ForeignPtr doesn't appear to have a NFData instance, so I can't use deepseq, but all my attempts with seq, including using seq on each element in the tuple, have been without noticeable effect.
EDIT:
Upon request, I have included more specifics, that I initially excluded since I think they are probably mostly noise for this question.
The monad
newtype FT c a = FT (Context -> a)
instance Functor (FT c) where
fmap f (FT a) = FT (f.a)
instance Applicative (FT c) where
pure a = FT (\_ -> a)
(<*>) (FT a) (FT b) = FT (\c -> a c $ b c)
instance Monad (FT c) where
return = pure
(>>=) (FT a) f = FT (\c -> (\(FT b) -> b c) $ f $ a c)
runFTIn :: Context -> (forall c. FT c a) -> a
runFTIn context (FT a) = a context
runFTWith :: [ContextOption] -> (forall c. FT c a) -> a
runFTWith options a
= unsafePerformIO
$ getContext options >>= \c -> return $ runFTIn c a
runFT = runFTWith []
unsafeLiftFromIO :: (Context -> IO a) -> FT c a
unsafeLiftFromIO a = FT (\c -> unsafePerformIO $ a c)
All the foreign functions are lifted from IO with unsafeLiftFromIO
newtype Box c = Box (ForeignPtr RawBox)
newtype Coordinates c = Coordinates (ForeignPtr RawCoordinates)
type Frame c = (Box c, Coordinates c)
liftBox :: Box c -> FT c HBox
liftCoordinates :: Coordinates c -> FT c HCoordinates
liftFrame (box, coordinates) = do
box' <- liftBox box
coordinates' <- liftCoordinates coordinates
return (box', coordinates')
The steps themselves are supposed to be arbitrary (Frame c -> FT c (Frame c)), so strictness should preferably be in the higher level code.
EDIT2:
I have now tried to use Streamly, however the problem persists, so I think the issue really is finding a way to strictly evaluate ForeignPtrs.
current implementations:
import Streamly
import qualified Streamly.Prelude as S
import qualified Streamly.Internal.Data.Stream.Serial as Serial
takeEvery n = Serial.unfoldrM ((fmap.fmap) (\(h, t) -> (h, S.drop (n-1) t)) . S.uncons)
(#) = flip ($)
simulation
:: (IsStream t)
=> Frame c
-> t (FT c) (Frame c -> FT c (Frame c))
-> t (FT c) (Frame c)
simulation frame = S.scanlM' (#) frame
EDIT3:
To clarify the symptoms and how I have diagnosed the problem.
The library calls OpenCL functions running on a GPU. I am sure that the freeing of the pointers is handled correctly - the ForeignPtrs have the correct freeing functions, and memory use is independent of total number of steps as long as this number is larger than n. What I find is that memory use on the GPU is basically linearly correlated to n. The consumer I've been using for this testing is
import qualified Data.ByteString.Lazy as BL
import Data.Binary
import Data.Binary.Put
writeTrajectory fn = fmap (BL.writeFile fn . runPut) . S.foldr ((>>).putFrame) (pure ()) . serially
For my streamly implementation, and
writeTrajectory fn = BL.writeFile fn . runPut . MapM_ putFrame
For the original implementation. Both should consume the stream continuously. I've generated the steps for testing with replicate.
I am unsure of how to more precisely analyze the memory-use on the GPU. System memory use is not an issue here.
Update:
I am starting to think it's not a matter of strictness, but of GC-problems. The run-time system does not know the size of the memory allocated on the GPU and so does not know to collect the pointers, this is less of an issue when there is stuff going on CPU-side as well, as that will produce allocations too, activating the GC. This would explain the slightly non-determinstic memory usage, but linear correlation to n that I've seen. How too solve this nicely is another issue, but I suspect there will be a substantial overhaul to my code.
I think the issue really is finding a way to strictly evaluate ForeignPtrs
If that is really the issue, one way to do that is to change the second clause of simulation:
{-# LANGUAGE BangPatterns #-}
simulation :: [(Frame -> M Frame)] -> Frame -> M [Frame]
simulation [] frame = return [frame]
simulation (step:steps) frame#(!_, !_) -- Evaluate both components of the pair
= step frame >>= fmap (frame:) . simulation steps

Create an event stream of polymorphic functions - possible? If yes, how?

I am currently learning FRP with reactive-banana and wanted to create a stream of random functions. I've come up with this:
-- | take number generator, and some pulse event stream, generate random function stream
mkRandom :: (Random a,RandomGen g) => g -> Event t b -> Event t ((a,a) -> a)
mkRandom rng es = (\f -> \r -> fst $ f r) <$> (accumE first $ next <$> es)
where first = flip randomR rng
next _ prev range = randomR range g
where (a,g) = prev range
It seems to work, I can use it like this:
randFuncs = mkRandom rnd (pulse 1000 time)
some = ($ (0,10::Int)) <$> randFuncs
But, of course, when I try to share that stream to generate numbers of a different type:
some2 = ($ (0,10::Double)) <$> randFuncs
The type checker complains, which I understand. Then I tried to generalize the function to the following:
mkRandom :: (RandomGen g) => g -> Event t b -> Event t (forall a. Random a => (a,a) -> a)
Then GHC complained about illegal polymorphic signature and whether I'd like to enable ImpredicativeTypes. I did it and for quite a while tried to annotate everything to make it work, but GHC always complained that it could not match the types.
My question is - is it possible to do what I want? Do I really need ImpredicativeTypes for that or am I just doing it wrong?
I thought RankNTypes should be enough for it, but I have no experience with such extensions yet.
Thanks in advance!
EDIT:
For the record, now my solution based on the helpful response is:
newtype RandomSource = Rand { getRand :: forall a. (Random a) => (a,a) -> [a] }
-- | take number generator and some pulse event stream, generate randomness stream
mkRandom :: RandomGen g => g -> Event t a -> Behavior t RandomSource
mkRandom rng es = fst <$> (accumB (next id (id,rng)) $ next <$> es)
where next _ (_,rng) = (Rand $ flip randomRs g1, g2)
where (g1,g2) = split rng
-- | take a rand. source, a range and a pulse, return stream of infinite lists of random numbers
randStream :: Random a => Behavior t RandomSource -> (a,a) -> Event t b -> Event t [a]
randStream funcs range pulse = ($ range) . getRand <$> funcs <# pulse
ImpredicativeTypes is an incredibly brittle extension that is not really supported or maintained and so keeps breaking further in new GHC versions.
A much better working option is to use RankNTypes together with a newtype wrapper:
newtype PolyRandFun = PR { getPR :: forall a. Random a => (a,a) -> a) }
This requires you to explicitly wrap and unwrap the newtype constructor, but otherwise works fine for passing around polymorphic functions like this.
Unfortunately I foresee another problem in this case. Different Random a instances use their random generator a different amount, and in the case of e.g. Integer the amount of primitive random numbers generated to build the Integer result will even depend on the size of the range. So you cannot get the next g without knowing the type and range used when actually calling your functions.
Fortunately there's a function in the System.Random API that can get around this: split gives you a new random generator that can be passed into subcalculations when you really need to generate several random values entirely independently.

project euler 14 using the state monad

I'm trying to teach myself Haskell (again) by working through Project Euler. Question 14 (https://projecteuler.net/problem=14) is begging for dynamic programming and historically I've been vehemently anti-monad (on account of repeatedly failing to learn to use them well enough to make life easier instead of harder) so I'm trying to bite the bullet and use the State monad to memoize my code... it's not going well. I want to be clear, I've already solved the problem the easy/slow way, at this point I'm trying to learn something (ie Project Euler No. 14 Haskell is not what I'm looking for).
My code so far is:
collatzMemoCheck :: Int -> State (Map Int Int) Int
collatzMemoCheck n = state $ \s -> maybe (let (a, s') = runState (collatzFast n) s
in (a+1, Map.insert n (a+1) s'))
(\len -> (len, s))
(Map.lookup n s)
collatzFast :: Int -> State (Map Int Int) Int
collatzFast 1 = state $ \_ -> (1, Map.singleton 1 1)
collatzFast n
| even n = collatzMemoCheck (n `quot` 2)
| otherwise = collatzMemoCheck (3 * n + 1)
which works for individual queries in cabal repl, but for the life of me I can't figure out how to chain up the state of repeated calls to collatzFast. I want something like
-- DOES NOT WORK
allCollatzLengths = scanl (>>= collatzFast) (return Map.empty) [1..999999]
but I think this is inside out. Bind takes the result portion of the previous State computation and passes it to the next call, but I want it to take the state portion of the previous State computation and pass it to the next call.
Is there a right way to do this or have I painted myself into a corner? If I can't use >>=, what's the point of having a monad? ... or is there no point because this is a stupid approach? Help?
You might like
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
In particular, mapM collatzFast :: [Int] -> State (Map Int Int) [Int].

How do you use the list monad to compute/represent the outcome of a non-deterministic computation?

I want to structure a computation where the context is the history of all paths leading the present (which forms a tree), and the function is the present state conditional on the past state. The function itself is non-deterministic so one past state could result in several future states, thus the tree branches. It makes sense to represent the outcome of this computation as a tree, but is there a way to tersely express it with a list monad? Or some other construct that I don't know?
I'd like to add to Tikhon Jelvis's answer that if you need to trace how your executions branch, you could use a more complicated monad stack combination. For example:
import Control.Monad
import Control.Monad.Writer
import Data.Sequence
-- | Represents a non-deterministic computation
-- that allows to trace the execution by sequences of 'w'.
type NonDet w a = WriterT (Seq w) [] a
A value of WriterT (Seq w) [] a is inside [(a, Seq w)], that is, a list of possible outcomes, each holding the result together with a sequence of marks of type w. We use these marks to trace our steps.
We first create a helper function that just adds a mark to the current trace of execution:
-- | Appends a mark to the current trace.
mark :: w -> NonDet w ()
mark = tell . singleton
and perhaps a more convenient function that adds a mark and then proceeds with a given computation:
-- | A helper function appends a mark and proceeds.
(#>) :: w -> NonDet w a -> NonDet w a
(#>) x = (mark x >>)
As a very simple example, let's say we want to traverse a tree
data Tree a = Leaf a | Bin (Tree a) (Tree a)
(In reality, there would be no tree of course, branching would be determined by something sophisticated.)
And we will remember the path we traversed using a sequence of directions
data Direction = L | R
deriving (Show, Read, Eq, Ord, Enum, Bounded)
Our traversal function would then look like this:
traverse :: Tree a -> NonDet Direction a
traverse (Leaf x) = return x
traverse (Bin l r) = (L #> traverse l) `mplus` (R #> traverse r)
Calling
runWriterT $ traverse $ Bin (Bin (Leaf "a") (Leaf "b")) (Leaf "c")
produces in
[("a",fromList [L,L]),("b",fromList [L,R]),("c",fromList [R])]
Notes:
Note the usage of mplus for branching the monadic computation. It is more convenient to use mplus and mzero (or derived msum, mfilter, guard etc.) from MonadPlus than using list operations directly. If you later change your monad stack, for example from [] to our NonDet Direction, your existing code will work without modifications.
For WriterT we can use any monoid, not just sequences. For example, if all we cared about was the number of steps taken, we could define
type NonDet a = WriterT (Sum Int) [] a
mark :: NonDet w ()
mark tell (Sum 1)
Then calling mark would just increment our counter, and the result of calling (slightly modified traverse) would be
[("a",Sum {getSum = 2}),("b",Sum {getSum = 2}),("c",Sum {getSum = 1})]
Using the list monad would let you structure the computation like a tree, but it would lose the source information. At the end, you would have a list of results, but you would not know where each individual result came from.
If this is all you care about, the list monad is perfect. Let's imagine you have a non-deterministic step function:
step :: State -> [State]
if we want to just step it through a bunch of times, we could write something like:
startState >>= step >>= step >>= step
this will give us all the possible results after 3 steps. If we wanted to generalize this to any number, we could write a simple helper function by using the monadic composition operator (<=<) from Control.Monad. This works just like ., except for function of the form a -> m b instead of normal functions (a -> b). It could look something like this:
stepN :: Int -> (State -> [State]) -> State -> [State]
stepN n f = foldr (<=<) return (replicate n f)
Now to get three non-deterministic steps, we can just write stepN 3 step. (You'll probably want to come up with better names for the functions :P.)
In summary: using the list monad, the computation itself is shaped like a tree, but you only get to look at the results at the end. This should be clear from the types involved: at the end, you get a [State], which is by its very nature flat. However, the function State -> [State] branches, so the computation to arrive to the end has to look like a tree.
For things like that, the list type is very convenient to use.
You can actually do even better than the other proposed solutions. You can keep an independent history for each successive branch and trace the execution path in real time.
Here's how you do it using pipes-4.0.0 (currently still on Github):
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State
import Pipes
import qualified Pipes.Prelude as P
branch :: Int -> StateT [Int] (ListT' IO) [Int]
branch n =
if (n <= 0) then get
else do
path <- lift $ P.each [1, 2]
lift $ lift $ putStrLn $ "Taking path " ++ show path
modify (path:)
branch (n - 1)
pipe :: () -> Producer' [Int] IO ()
pipe () = runRespondT (evalStateT (branch 3) [])
main = runProxy $ (pipe >-> P.print) ()
Here's what it outputs:
Taking path 1
Taking path 1
Taking path 1
[1,1,1]
Taking path 2
[2,1,1]
Taking path 2
Taking path 1
[1,2,1]
Taking path 2
[2,2,1]
Taking path 2
Taking path 1
Taking path 1
[1,1,2]
Taking path 2
[2,1,2]
Taking path 2
Taking path 1
[1,2,2]
Taking path 2
[2,2,2]
Normally if you want to save a context of currently visited states you would use:
StateT [node] [] r
... where node is a place you have visited. StateT keeps track of every node you visit, and [] is the non-determinism part. However, if you want to add effects you need to replace [] with the monad transformer equivalent: ListT:
StateT [node] (ListT IO) r
This is how you derive the type of branch. In our particular case the nodes we are visiting are Ints and branch returns the current context at the end of each path that it takes.
When you evalStateT that with an empty initial context you get:
evalStateT (branch 3) [] :: ListT IO [Int]
That's a non-deterministic computation that will try out each branch, tracing the result in IO as it goes along, and then return the local context at the end of the result. There will be 8 final results since our branch is going to take 8 total paths.
If we run that using runRespondT, we get a Producer:
pipe :: () -> Producer' [Int] IO ()
This producer will emit results as it reaches the end of each execution path, tracing as it goes along. We don't have to wait until the end of the computation to see the traces. All we need to view the [Int]s that it is outputting is to hook it up to a Consumer:
P.print :: () -> Consumer [Int] IO r
pipe >-> P.print :: () -> Effect IO ()
This transforms our final computation into an Effect in the base monad (in this case IO). We can run this effect using runProxy:
runProxy $ (pipe >-> P.print) () :: IO ()
This then both traces the computation and prints out the end point of each path.

Resources