Haskell. From pure code to IO and back - haskell

Are there a possibility to stop a recursive algorithm when it throws some exception provided by us, save it's state, ask user something and then continue the recursion from the saved place?
I changed the question.
I read a file system recursively and keep data in a tree. Suddenly I face with a hidden directory. Can I stop calculations and ask now user should I place information about the directory in my tree and then continue calculations?
About working with IO:
obtainTree :: ByteString -> Tree
...
main = print $ obtainTree partition
as I understand to work with IO inside the algorithm we have to use function like this:
obtainTree :: ByteString -> IO Tree
but can we avoid it?

Sure you can do it. You can always set things up so that you capture the remaining computation as a continuation, which can be resumed externally.
Here's one way to do something like this:
-- intended to be put in a module that only exports the following list:
-- (Resumable, Prompted, prompt, runResumable, extract, resume)
import Control.Applicative
newtype Resumable e r a = R { runResumable :: Either (Prompted e r a) a }
data Prompted e r a = P e (r -> Resumable e r a)
suspend :: e -> (r -> Resumable e r a) -> Resumable e r a
suspend e = R . Left . P e
instance Functor (Resumable e r) where
fmap f (R (Right x)) = pure $ f x
fmap f (R (Left (P e g))) = suspend e $ \x -> f <$> g x
instance Applicative (Resumable e r) where
pure = R . Right
(R (Right f)) <*> (R (Right x)) = pure $ f x
(R (Left (P e f))) <*> x = suspend e $ \y -> f y <*> x
f <*> (R (Left (P e g))) = suspend e $ \y -> f <*> g y
instance Monad (Resumable e r) where
return = pure
(R (Right x)) >>= f = f x
(R (Left (P e f))) >>= g = suspend e $ \x -> f x >>= g
prompt :: e -> Resumable e r r
prompt e = suspend e pure
extract :: Prompted e r a -> e
extract (P e _) = e
resume :: Prompted e r a -> r -> Either (Prompted e r a) a
resume (P _ f) e = runResumable $ f e
This lets you divide up your logic into an internal piece that runs inside Resumable and an external piece that handles the results of the internal part's prompting using whatever method it likes.
Here's a simple example of using this:
askAboutNegatives :: [Int] -> Resumable Int Bool [Int]
askAboutNegatives [] = return []
askAboutNegatives (x:xs) = do
keep <- if x < 0 then prompt x else return True
rest <- askAboutNegatives xs
return $ if keep then x:rest else rest
main :: IO ()
main = do
let ls = [1, -4, 2, -7, 3]
loopIfNeeded (Right r) = return r
loopIfNeeded (Left p) = do
putStrLn $ "Would you like to keep " ++ show (extract p)
i <- getLine
loopIfNeeded $ resume p (i == "y")
asked <- loopIfNeeded $ runResumable (askAboutNegatives ls)
print asked
As a way of making this use case simpler, the module containing Resumable can be augmented to also export this function:
runResumableWithM :: Monad m => (e -> m r) -> Resumable e r a -> m a
runResumableWithM f x = case runResumable x of
Right y -> return y
Left (P e g) -> do
r <- f e
runResumableWithM f $ g r
Which would allow rewriting main from that example as the somewhat simpler:
main :: IO ()
main = do
let ls = [1, -4, 2, -7, 3]
ask x = do
putStrLn $ "Would you like to keep " ++ show x
i <- getLine
return $ i == "y"
asked <- runResumableWithM ask (askAboutNegatives ls)
print asked
The one real issue with this approach is that every prompt must have the same type. Otherwise, it handles the problem nicely, using continuations to capture the rest of the computation implicitly when needed.

First thing first, a pure code cannot go to IO or we can say a pure function needs to become impure if it tries to use some impure function (i.e trying to use IO). In case you are wondering why this so, think about this: If the pure function ask the impure function about some data to complete its own processing then it looses "Referential transparency" because now the pure function can return different result for same input due to the involved impure (IO) call, hence it is no more pure.
Based on the above information, your solution will be as simple as making use of higher order function to ask the user about the information. Something like:
parseFileSystem :: FileSystem -> (Directory -> IO Tree) -> IO Tree
Here the (Directory -> IO Tree) is the function that will ask user about the required information and return a Tree data based on it.

Related

A traversal as data

I heard about this construction which is loosely described as “a traversal represented in data, applied to some structure, without the need for the applicative”
It can be defined as:
data X a b r =
| Done r
| Step a (X a b (b -> r))
A word description would be as follows:
the type X a b r describes the shape of a structure
which contains things of type a
and for each a you get the opportunity to produce something of type b
and provided you do that for each a,
you get something of type r.
Thus a “traversal” of a list, [a], has type X a b [b], because if you can turn each a of the list into a b then you get a [b].
My question is: what is this thing called? Is there a reference to more information about it?
Example usage:
instance Functor (X a b) where
fmap f (Done r) = f r
fmap f (Step a next) = Step a (fmap (f .) next)
f :: [a] -> X a b [b]
f [] = Done []
f (a:as) = Step a (fmap (flip (:)) as)
g :: Applicative f => (a -> f b) -> X a b r -> f r
g f (Done r) = pure r
g f (Step a next) = g f next <*> f a
More generally:
instance Applicative (X a b) where
pure x = Done x
Done f <*> y = fmap (\y -> f y) y
Step a next <*> y = Step a (fmap flip next <*> y)
t :: Traversable t => t a -> X a b (t b)
t = traverse (\a -> Step a (Done id))
And, assuming I haven’t made any errors, we should find that:
flip g . t == traverse
Edit: I’ve thought about this some more. There is something this doesn’t have which a traversal has: a traversal can split up the computation into something that isn’t “one at a time,” for example to traverse a binary tree one can traverse the left and right half “in parallel.” Here is a structure that I think gives the same effect:
data Y a b r =
| Done r
| One a (b -> r)
| forall s t. Split (Y a b s) (Y a b t) (s -> t -> r)
(Slightly vague syntax as I don’t remember it and don’t want to write this as a gadt)
f1 :: X a b r -> Y a b r
f1 (Done x) = Done x
f1 (Step a next) = Split (One a id) (f1 next) (flip ($))
f2 :: Y a b r -> X a b r
f2 (Done x) = Done x
f2 (One a f) = Step a (Done f)
f2 (Split x y f) = f <$> f2 x <*> f2 y

Pattern matching in `Alternative`

I have a function that pattern matches on its arguments to produce a computation in StateT () Maybe (). This computation can fail when run, in which case I want the current pattern match branch to fail, so to speak.
I highly doubt it's possible to have something like
compute :: Int -> StateT () Maybe Int
compute = return
f :: Maybe Int -> Maybe Int -> StateT () Maybe ()
f (Just n1) (Just n2) = do
m <- compute (n1 + n2)
guard (m == 42)
f (Just n) _ = do
m <- compute n
guard (m == 42)
f _ (Just n) = do
m <- compute n
guard (m == 42)
behave in the way I want it to: When the first computation fails due to the guard or somewhere in compute, I want f to try the next pattern.
Obviously the above can't work, because StateT (as any other monad might) involves an additional parameter when expanded, so I probably can't formulate this as simple pattern guards.
The following does what I want, but it's ugly:
f' :: Maybe Int -> Maybe Int -> StateT () Maybe ()
f' a b = asum (map (\f -> f a b) [f1, f2, f3])
where
f1 a b = do
Just n1 <- pure a
Just n2 <- pure b
m <- compute (n1 + n2)
guard (m == 42)
f2 a _ = do
Just n <- pure a
m <- compute n
guard (m == 42)
f3 _ b = do
Just n <- pure b
m <- compute n
guard (m == 42)
A call like execStateT (f (Just 42) (Just 1)) () would fail for f but return Just () for f', because it matches f2.
How do I get the behavior of f' while having elegant pattern matching with as little auxiliary definitions as possible like in f? Are there other, more elegant ways to formulate this?
Complete runnable example:
#! /usr/bin/env stack
-- stack --resolver=lts-11.1 script
import Control.Monad.Trans.State
import Control.Applicative
import Control.Monad
import Data.Foldable
compute :: Int -> StateT () Maybe Int
compute = return
f :: Maybe Int -> Maybe Int -> StateT () Maybe ()
f (Just n1) (Just n2) = do
m <- compute (n1 + n2)
guard (m == 42)
f (Just n) _ = do
m <- compute n
guard (m == 42)
f _ (Just n) = do
m <- compute n
guard (m == 42)
f' :: Maybe Int -> Maybe Int -> StateT () Maybe ()
f' a b = asum (map (\f -> f a b) [f1, f2, f3])
where
f1 a b = do
Just n1 <- pure a
Just n2 <- pure b
m <- compute (n1 + n2)
guard (m == 42)
f2 a _ = do
Just n <- pure a
m <- compute n
guard (m == 42)
f3 _ b = do
Just n <- pure b
m <- compute n
guard (m == 42)
main = do
print $ execStateT (f (Just 42) (Just 1)) () -- Nothing
print $ execStateT (f' (Just 42) (Just 1)) () -- Just (), because `f2` succeeded
Edit: I elicited quite some clever answers with this question so far, thanks! Unfortunately, they mostly suffer from overfitting to the particular code example I've given. In reality, I need something like this for unifying two expressions (let-bindings, to be precise), where I want to try unifying the RHS of two simultaneous lets if possible and fall through to the cases where I handle let bindings one side at a time by floating them. So, actually there's no clever structure on Maybe arguments to exploit and I'm not computeing on Int actually.
The answers so far might benefit others beyond the enlightenment they brought me though, so thanks!
Edit 2: Here's some compiling example code with probably bogus semantics:
module Unify (unify) where
import Control.Applicative
import Control.Monad.Trans.State.Strict
data Expr
= Var String -- meta, free an bound vars
| Let String Expr Expr
-- ... more cases
-- no Eq instance, fwiw
-- | If the two terms unify, return the most general unifier, e.g.
-- a substitution (`Map`) of meta variables for terms as association
-- list.
unify :: [String] -> Expr -> Expr -> Maybe [(String, Expr)]
unify metaVars l r = execStateT (go [] [] l r) [] -- threads the current substitution as state
where
go locals floats (Var x) (Var y)
| x == y = return ()
go locals floats (Var x) (Var y)
| lookup x locals == Just y = return ()
go locals floats (Var x) e
| x `elem` metaVars = tryAddSubstitution locals floats x e
go locals floats e (Var y)
| y `elem` metaVars = tryAddSubstitution locals floats y e
-- case in point:
go locals floats (Let x lrhs lbody) (Let y rrhs rbody) = do
go locals floats lrhs rrhs -- try this one, fail current pattern branch if rhss don't unify
-- if we get past the last statement, commit to this branch, no matter
-- the next statement fails or not
go ((x,y):locals) floats lbody rbody
-- try to float the let binding. terms mentioning a floated var might still
-- unify with a meta var
go locals floats (Let x rhs body) e = do
go locals (Left (x,rhs):floats) body e
go locals floats e (Let y rhs body) = do
go locals (Right (y,rhs):floats) body e
go _ _ _ _ = empty
tryAddSubstitution = undefined -- magic
When I need something like this, I just use asum with the blocks inlined. Here I also condensed the multiple patterns Just n1 <- pure a; Just n2 <- pure b into one, (Just n1, Just n2) <- pure (a, b).
f :: Maybe Int -> Maybe Int -> StateT () Maybe ()
f a b = asum
[ do
(Just n1, Just n2) <- pure (a, b)
m <- compute (n1 + n2)
guard (m == 42)
, do
Just n <- pure a
m <- compute n
guard (m == 42)
, do
Just n <- pure b
m <- compute n
guard (m == 42)
]
You can also use chains of <|>, if you prefer:
f :: Maybe Int -> Maybe Int -> StateT () Maybe ()
f a b
= do
(Just n1, Just n2) <- pure (a, b)
m <- compute (n1 + n2)
guard (m == 42)
<|> do
Just n <- pure a
m <- compute n
guard (m == 42)
<|> do
Just n <- pure b
m <- compute n
guard (m == 42)
This is about as minimal as you can get for this kind of “fallthrough”.
If you were using Maybe alone, you would be able to do this with pattern guards:
import Control.Monad
import Control.Applicative
ensure :: Alternative f => (a -> Bool) -> a -> f a
ensure p a = a <$ guard (p a)
compute :: Int -> Maybe Int
compute = return
f :: Maybe Int -> Maybe Int -> Maybe Int
f (Just m) (Just n)
| Just x <- ensure (== 42) =<< compute (m + n)
= return x
f (Just m) _
| Just x <- ensure (== 42) =<< compute m
= return x
f _ (Just n)
| Just x <- ensure (== 42) =<< compute n
= return x
f _ _ = empty
(ensure is a general purpose combinator. Cf. Lift to Maybe using a predicate)
As you have StateT on the top, though, you would have to supply a state in order to pattern match on Maybe, which would foul up everything. That being so, you are probably better off with something in the vein of your "ugly" solution. Here is a whimsical attempt at improving its looks:
import Control.Monad
import Control.Applicative
import Control.Monad.State
import Control.Monad.Trans
import Data.Foldable
ensure :: Alternative f => (a -> Bool) -> a -> f a
ensure p a = a <$ guard (p a)
compute :: Int -> StateT () Maybe Int
compute = return
f :: Maybe Int -> Maybe Int -> StateT () Maybe Int
f a b = asum (map (\c -> f' (c a b)) [liftA2 (+), const, flip const])
where
f' = ensure (== 42) <=< compute <=< lift
While this is an answer specific to the snippet I've given, the refactorings only apply limited to the code I was facing.
Perhaps it's not that far-fetched of an idea to extract the skeleton of the asum expression above to a more general combinator:
-- A better name would be welcome.
selector :: Alternative f => (a -> a -> a) -> (a -> f b) -> a -> a -> f b
selector g k x y = asum (fmap (\sel -> k (sel x y)) [g, const, flip const])
f :: Maybe Int -> Maybe Int -> StateT () Maybe Int
f = selector (liftA2 (+)) (ensure (== 42) <=< compute <=< lift)
Though it is perhaps a bit awkward of a combinator, selector does show the approach is more general than it might appear at first: the only significant restriction is that k has to produce results in some Alternative context.
P.S.: While writing selector with (<|>) instead of asum is arguably more tasteful...
selector g k x y = k (g x y) <|> k x <|> k y
... the asum version straightforwardly generalises to an arbitrary number of pseudo-patterns:
selector :: Alternative f => [a -> a -> a] -> (a -> f b) -> a -> a -> f b
selector gs k x y = asum (fmap (\g -> k (g x y)) gs)
It looks like you could get rid of the whole pattern match by relying on the fact that Int forms a Monoid with addition and 0 as the identity element, and that Maybe a forms a Monoid if a does. Then your function becomes:
f :: Maybe Int -> Maybe Int -> StateT () Maybe Int
f a b = pure $ a <> b >>= compute >>= pure . mfilter (== 42)
You could generalise by passing the predicate as an argument:
f :: Monoid a => (a -> Bool) -> Maybe a -> Maybe a -> StateT () Maybe a
f p a b = pure $ a <> b >>= compute >>= pure . mfilter p
The only thing is that compute is now taking a Maybe Int as input, but that is just a matter of calling traverse inside that function with whatever computation you need to do.
Edit: Taking into account your last edit, I find that if you spread your pattern matches into separate computations that may fail, then you can just write
f a b = f1 a b <|> f2 a b <|> f3 a b
where f1 (Just a) (Just b) = compute (a + b) >>= check
f1 _ _ = empty
f2 (Just a) _ = compute a >>= check
f2 _ _ = empty
f3 _ (Just b) = compute b >>= check
f3 _ _ = empty
check x = guard (x == 42)

Understanding Monadic Fibonacci

I am learning haskell and learning monads. I've watched and read various tutorials and coded some simple examples for state monad, however I am not able to understand the following piece of code (taken from Haskell Wiki):
import Control.Monad.State
fib n = flip evalState (0,1) $ do
forM [0..(n-1)] $ \_ -> do
(a,b) <- get
put (b,a+b)
(a,b) <- get
return a
My question boils down to the following:
What is going inside the first statement of the inner do, i.e what does (a,b)<-get result into. What will be the values of a and b for some concrete example.
Why would you want to use the state monad over here?
In this example, the state is a pair containing the previous two numbers generated in the sequence. This is initially (0, 1) provided to evalState.
The type of get is MonadState s m => m s so in the inner do block
(a, b) <- get
fetches the state pair and binds a and b to the first and second elements respectively. The state is then updated in the following put.
The state will therefore be:
(0, 1), (1, 1), (1, 2), (3, 2), (3, 5), ...
The outer
(a, b) <- get
return a
unpacks the final state value and returns the first element.
First lets make clear the Fibonacci algorithm being used. The idea is to start with the tuple (0, 1), then find the next as (1, 0 + 1), the next as (1, 1 + 1), (2, 2 + 1), (3, 3 + 2), and so on. Generally, the step is \(a, b) -> (b, a + b). You can see that in these tuples are the Fibonacci numbers.
What is going inside the first statement of the inner do, i.e what
does (a,b)<-get result into?
Haskell does not have statements, only expressions.
y <- x is not a complete expression. It is similar to x >>= \y ->.
y <- x
m
Is a complete expression and is equivalent to x >>= \y -> m. A line n not of the form y <- n is equivalent to _ <- n (excluding let lines and maybe some others I forget).
Using this we can desugar do-notation.
fib n =
flip evalState (0, 1)
( forM
[0..(n-1)]
(\_ -> get >>= (\(a, b) -> put (b, a + b)))
>>= (\_ -> get >>= (\(a, b) -> return a)))
)
Now it is just about understanding >>=, return, get, put, and so on.
State is actually just functions of the type s -> (s, a). They take an initial state and yield the next state plus some other value.
m >>= n a.k.a. "bind" has the type Monad m => m a -> (a -> m b) -> m b. Then, if our Monad is State s, this is the same as:
m >>= n ::
( s -> (s, a))
-> (a -> s -> (s, b))
-> ( s -> (s, b))
The a returned by m has to be passed to n. What else can we guess? We expect the state to pass along as well, so the state returned by m must be passed to n as well. The function m >>= n must return the state and value that n returns. We then know how to implement bind:
m >>= n = uncurry (flip n) . m
return :: Monad m => a -> m a which is then equivalent to return :: a -> s -> (s, a):
return = flip (,)
get :: State s s is equivalent to get :: s -> (s, s):
get = join (,)
put :: s -> State s () or put :: s -> s -> (s, ()):
put s _ = (s, ())
evalState :: s -> State s a -> a or evalState :: s -> (s -> (s, a)) -> a:
evalState s f = snd (f s)
You can expand all the definitions and see exactly what is happening in the example. Just the intuitions should suffice though.
forM
[0..(n-1)]
(\_ -> get >>= (\(a, b) -> put (b, a + b)))
We don't care about having the numbers 0 to n - 1 so the first argument is dropped. get retrieves the current state, then put writes the new state. We do this n times.
>>= (\_ -> get >>= (\(a, b) -> return a)))
We don't care about the accumulated value (which is unit) and so the first parameter is dropped. Then we get the current state and project just the first element of the pair. This is the final answer we're looking for.
flip evalState (0, 1) …
Finally we run starting from the initial state (0, 1).
There are some cleanups we can make to this implementation. First, we don't care about the range [0..(n-1)], we just care about repeating an action n times. A more direct way to do this is the following:
replicateM n (get >>= \(a, b) -> put (b, a + b))
The result is a list of unit which is unused, so a more efficient version is:
replicateM_ n (get >>= \(a, b) -> put (b, a + b))
There is already a function for the common pattern of get followed by put named modify, which is defined as \f -> get >>= put . f. Therefore:
replicateM_ n (modify (\(a, b) -> (b, a + b)))
Then there is the part:
>>= (\_ -> get >>= (\(a, b) -> return a)))
Any time we don't care about the previous result we can use >>.
>> get >>= (\(a, b) -> return a))
This is:
>> get >>= return . fst
m >>= return . f simplifies to fmap f m:
>> fmap fst get
Now we have, in total:
fib n =
evalState
( replicateM_ n (modify (\(a, b) -> (b, a + b)))
>> fmap fst get
)
(0, 1)
We might also use, for comparison:
fib n =
fst
( evalState
( replicateM_ n (modify (\(a, b) -> (b, a + b)))
>> get
)
(0, 1)
)
And then because I am silly:
fib =
fst
. flip evalState (0, 1)
. (>> get)
. flip replicateM_ (modify (snd &&& uncurry (+)))
Why would you want to use the state monad over here?
You wouldn't. This is clear because we only use the state value; the other value is always unit and discarded. In other words, we only need n (i.e. which Fibonacci number to find) at the beginning and afterwards we only need the accumulated tuple.
Sometimes you think to have a string of compositions like h . g . f but you want to send two arguments through instead of just one. That is when State may be applicable.
If some functions read and some write the state (the second argument), or do both, then State fits the bill. If there are only readers then use Reader and if there are only writers then use Writer.
We can alter the example to make better use of the State Monad. I will make the tuple disappear!
fib =
flip evalState 0
. foldr (=<<) (return 1)
. flip replicate (\x -> get >>= \y -> put x $> x + y)
So the docs state: get :: m s -- Return the state from the internals of the monad (see here).
But I remember very well that when I tried to wrap my head around the State Monad this didn't help me a lot.
I can only recommend playing around with :i and :t in ghci and test out different sub-expressions. Just to get a feel for it. A bit like this:
import Control.Monad.State.Lazy
runState (get) 0
runState (get >>= \x -> put (x+1)) 0
:t return 1 :: State Int Int
runState (return 1) 0
runState (return 1 >>= \x -> (get >>= \y -> return (x+y))) 0
-- Keeping a pair of (predecessor/current) in the state:
let f = (get >>= (\(a,b) -> put (b,a+b))) :: State (Int, Int) ()
runState (f >> f >> f >> f >> f >> f) (0,1)
-- only keeping the predecessor in the state:
let f x = (get >>= (\y -> put x >> return (x+y))) :: State Int Int
runState (return 1 >>= f >>= f >>= f >>= f >>= f >>= f) 0
Also play around with modify, runState, evalState, execState.

Is there a way to elegantly represent this pattern in Haskell?

Mind the pure function below, in an imperative language:
def foo(x,y):
x = f(x) if a(x)
if c(x):
x = g(x)
else:
x = h(x)
x = f(x)
y = f(y) if a(y)
x = g(x) if b(y)
return [x,y]
That function represents a style where you have to incrementally update variables. It can be avoided in most cases, but there are situations where that pattern is unavoidable - for example, writing a cooking procedure for a robot, which inherently requires a series of steps and decisions. Now, imagine we were trying to represent foo in Haskell.
foo x0 y0 =
let x1 = if a x0 then f x0 else x0 in
let x2 = if c x1 then g x1 else h x1 in
let x3 = f x2 in
let y1 = if a y0 then f y0 else y0 in
let x4 = if b y1 then g x3 else x3 in
[x4,y1]
That code works, but it is too complicated and error prone due to the need for manually managing the numeric tags. Notice that, after x1 is set, x0's value should never be used again, but it still can. If you accidentally use it, that will be an undetected error.
I've managed to solve this problem using the State monad:
fooSt x y = execState (do
(x,y) <- get
when (a x) (put (f x, y))
(x,y) <- get
if c x
then put (g x, y)
else put (h x, y)
(x,y) <- get
put (f x, y)
(x,y) <- get
when (a y) (put (x, f y))
(x,y) <- get
when (b y) (put (g x, x))) (x,y)
This way, need for tag-tracking goes away, as well as the risk of accidentally using an outdated variable. But now the code is verbose and much harder to understand, mainly due to the repetition of (x,y) <- get.
So: what is a more readable, elegant and safe way to express this pattern?
Full code for testing.
Your goals
While the direct transformation of imperative code would usually lead to the ST monad and STRef, lets think about what you actually want to do:
You want to manipulate values conditionally.
You want to return that value.
You want to sequence the steps of your manipulation.
Requirements
Now this indeed looks first like the ST monad. However, if we follow the simple monad laws, together with do notation, we see that
do
x <- return $ if somePredicate x then g x
else h x
x <- return $ if someOtherPredicate x then a x
else b x
is exactly what you want. Since you need only the most basic functions of a monad (return and >>=), you can use the simplest:
The Identity monad
foo x y = runIdentity $ do
x <- return $ if a x then f x
else x
x <- return $ if c x then g x
else h x
x <- return $ f x
y <- return $ if a x then f y
else y
x <- return $ if b y then g x
else y
return (x,y)
Note that you cannot use let x = if a x then f x else x, because in this case the x would be the same on both sides, whereas
x <- return $ if a x then f x
else x
is the same as
(return $ if a x then (f x) else x) >>= \x -> ...
and the x in the if expression is clearly not the same as the resulting one, which is going to be used in the lambda on the right hand side.
Helpers
In order to make this more clear, you can add helpers like
condM :: Monad m => Bool -> a -> a -> m a
condM p a b = return $ if p then a else b
to get an even more concise version:
foo x y = runIdentity $ do
x <- condM (a x) (f x) x
x <- fmap f $ condM (c x) (g x) (h x)
y <- condM (a y) (f y) y
x <- condM (b y) (g x) x
return (x , y)
Ternary craziness
And while we're up to it, lets crank up the craziness and introduce a ternary operator:
(?) :: Bool -> (a, a) -> a
b ? ie = if b then fst ie else snd ie
(??) :: Monad m => Bool -> (a, a) -> m a
(??) p = return . (?) p
(#) :: a -> a -> (a, a)
(#) = (,)
infixr 2 ??
infixr 2 #
infixr 2 ?
foo x y = runIdentity $ do
x <- a x ?? f x # x
x <- fmap f $ c x ?? g x # h x
y <- a y ?? f y # y
x <- b y ?? g x # x
return (x , y)
But the bottomline is, that the Identity monad has everything you need for this task.
Imperative or non-imperative
One might argue whether this style is imperative. It's definitely a sequence of actions. But there's no state, unless you count the bound variables. However, then a pack of let … in … declarations also gives an implicit sequence: you expect the first let to bind first.
Using Identity is purely functional
Either way, the code above doesn't introduce mutability. x doesn't get modified, instead you have a new x or y shadowing the last one. This gets clear if you desugar the do expression as noted above:
foo x y = runIdentity $
a x ?? f x # x >>= \x ->
c x ?? g x # h x >>= \x ->
return (f x) >>= \x ->
a y ?? f y # y >>= \y ->
b y ?? g x # x >>= \x ->
return (x , y)
Getting rid of the simplest monad
However, if we would use (?) on the left hand side and remove the returns, we could replace (>>=) :: m a -> (a -> m b) -> m b) by something with type a -> (a -> b) -> b. This just happens to be flip ($). We end up with:
($>) :: a -> (a -> b) -> b
($>) = flip ($)
infixr 0 $> -- same infix as ($)
foo x y = a x ? f x # x $> \x ->
c x ? g x # h x $> \x ->
f x $> \x ->
a y ? f y # y $> \y ->
b y ? g x # x $> \x ->
(x, y)
This is very similar to the desugared do expression above. Note that any usage of Identity can be transformed into this style, and vice-versa.
The problem you state looks like a nice application for arrows:
import Control.Arrow
if' :: (a -> Bool) -> (a -> a) -> (a -> a) -> a -> a
if' p f g x = if p x then f x else g x
foo2 :: (Int,Int) -> (Int,Int)
foo2 = first (if' c g h . if' a f id) >>>
first f >>>
second (if' a f id) >>>
(\(x,y) -> (if b y then g x else x , y))
in particular, first lifts a function a -> b to (a,c) -> (b,c), which is more idiomatic.
Edit: if' allows a lift
import Control.Applicative (liftA3)
-- a functional if for lifting
if'' b x y = if b then x else y
if' :: (a -> Bool) -> (a -> a) -> (a -> a) -> a -> a
if' = liftA3 if''
I'd probably do something like this:
foo x y = ( x', y' )
where x' = bgf y' . cgh . af $ x
y' = af y
af z = (if a z then f else id) z
cgh z = (if c z then g else h) z
bg y x = (if b y then g else id) x
For something more complicated, you may want to consider using lens:
whenM :: Monad m => m Bool -> m () -> m ()
whenM c a = c >>= \res -> when res a
ifM :: Monad m => m Bool -> m a -> m a -> m a
ifM mb ml mr = mb >>= \b -> if b then ml else mr
foo :: Int -> Int -> (Int, Int)
foo = curry . execState $ do
whenM (uses _1 a) $
_1 %= f
ifM (uses _1 c)
(_1 %= g)
(_1 %= h)
_1 %= f
whenM (uses _2 a) $
_2 %= f
whenM (uses _2 b) $ do
_1 %= g
And there's nothing stopping you from using more descriptive variable names:
foo :: Int -> Int -> (Int, Int)
foo = curry . execState $ do
let x :: Lens (a, c) (b, c) a b
x = _1
y :: Lens (c, a) (c, b) a b
y = _2
whenM (uses x a) $
x %= f
ifM (uses x c)
(x %= g)
(x %= h)
x %= f
whenM (uses y a) $
y %= f
whenM (uses y b) $ do
x %= g
This is a job for the ST (state transformer) library.
ST provides:
Stateful computations in the form of the ST type. These look like ST s a for a computation that results in a value of type a, and may be run with runST to obtain a pure a value.
First-class mutable references in the form of the STRef type. The newSTRef a action creates a new STRef s a reference with an initial value of a, and which can be read with readSTRef ref and written with writeSTRef ref a. A single ST computation can use any number of STRef references internally.
Together, these let you express the same mutable variable functionality as in your imperative example.
To use ST and STRef, we need to import:
{-# LANGUAGE NoMonomorphismRestriction #-}
import Control.Monad.ST.Safe
import Data.STRef
Instead of using the low-level readSTRef and writeSTRef all over the place, we can define the following helpers to match the imperative operations that the Python-style foo example uses:
-- STRef assignment.
(=:) :: STRef s a -> ST s a -> ST s ()
ref =: x = writeSTRef ref =<< x
-- STRef function application.
($:) :: (a -> b) -> STRef s a -> ST s b
f $: ref = f `fmap` readSTRef ref
-- Postfix guard syntax.
if_ :: Monad m => m () -> m Bool -> m ()
action `if_` guard = act' =<< guard
where act' b = if b then action
else return ()
This lets us write:
ref =: x to assign the value of ST computation x to the STRef ref.
(f $: ref) to apply a pure function f to the STRef ref.
action `if_` guard to execute action only if guard results in True.
With these helpers in place, we can faithfully translate the original imperative definition of foo into Haskell:
a = (< 10)
b = even
c = odd
f x = x + 3
g x = x * 2
h x = x - 1
f3 x = x + 2
-- A stateful computation that takes two integer STRefs and result in a final [x,y].
fooST :: Integral n => STRef s n -> STRef s n -> ST s [n]
fooST x y = do
x =: (f $: x) `if_` (a $: x)
x' <- readSTRef x
if c x' then
x =: (g $: x)
else
x =: (h $: x)
x =: (f $: x)
y =: (f $: y) `if_` (a $: y)
x =: (g $: x) `if_` (b $: y)
sequence [readSTRef x, readSTRef y]
-- Pure wrapper: simply call fooST with two fresh references, and run it.
foo :: Integral n => n -> n -> [n]
foo x y = runST $ do
x' <- newSTRef x
y' <- newSTRef y
fooST x' y'
-- This will print "[9,3]".
main = print (foo 0 0)
Points to note:
Although we first had to define some syntactical helpers (=:, $:, if_) before translating foo, this demonstrates how you can use ST and STRef as a foundation to grow your own little imperative language that's directly suited to the problem at hand.
Syntax aside, this matches the structure of the original imperative definition exactly, without any error-prone restructuring. Any minor changes to the original example can be mirrored directly to Haskell. (The addition of the temporary x' <- readSTRef x binding in the Haskell code is only in order to use it with the native if/else syntax: if desired, this can be replaced with an appropriate ST-based if/else construct.)
The above code demonstrates giving both pure and stateful interfaces to the same computation: pure callers can use foo without knowing that it uses mutable state internally, while ST callers can directly use fooST (and for example provide it with existing STRefs to modify).
#Sibi said it best in his comment:
I would suggest you to stop thinking imperatively and rather think in a functional way. I agree that it will take some time to getting used to the new pattern, but try to translate imperative ideas to functional languages isn't a great approach.
Practically speaking, your chain of let can be a good starting point:
foo x0 y0 =
let x1 = if a x0 then f x0 else x0 in
let x2 = if c x1 then g x1 else h x1 in
let x3 = f x2 in
let y1 = if a y0 then f y0 else y0 in
let x4 = if b y1 then g x3 else x3 in
[x4,y1]
But I would suggest using a single let and giving descriptive names to the intermediate stages.
In this example unfortunately I don't have a clue what the various x's and y's do, so I cannot suggest meaningful names. In real code you would use names such as x_normalized, x_translated, or such, instead of x1 and x2, to describe what those values really are.
In fact, in a let or where you don't really have variables: they're just shorthand names you give to intermediate results, to make it easy to compose the final expression (the one after in or before the where.)
This is the spirit behind the x_bar and x_baz below. Try to come up with names that are reasonably descriptive, given the context of your code.
foo x y =
let x_bar = if a x then f x else x
x_baz = f if c x_bar then g x_bar else h x_bar
y_bar = if a y then f y else y
x_there = if b y_bar then g x_baz else x_baz
in [x_there, y_bar]
Then you can start recognizing patterns that were hidden in the imperative code. For example, x_bar and y_bar are basically the same transformation, applied respectively to x and y: that's why they have the same suffix "_bar" in this nonsensical example; then your x2 probably doesn't need an intermediate name , since you can just apply f to the result of the entire "if c then g else h".
Going on with the pattern recognition, you should factor out the transformations that you are applying to variables into sub-lambdas (or whatever you call the auxiliary functions defined in a where clause.)
Again, I don't have a clue what the original code did, so I cannot suggest meaningful names for the auxiliary functions. In a real application, f_if_a would be called normalize_if_needed or thaw_if_frozen or mow_if_overgrown... you get the idea:
foo x y =
let x_bar = f_if_a x
y_bar = f_if_a y
x_baz = f (g_if_c_else_h x_bar)
x_there = g_if_b x_baz y_bar
in [x_there, y_bar]
where
f_if_a x
| a x = f x
| otherwise = x
g_if_c_else_h x
| c x = g x
| otherwise = h x
g_if_b x y
| b y = g x
| otherwise = x
Don't disregard this naming business.
The whole point of Haskell and other pure functional languages is to express algorithms without the assignment operator, meaning the tool that can modify the value of an existing variable.
The names you give to things inside a function definition, whether introduced as arguments, let, or where, can only refer to one value (or auxiliary function) throughout the entire definition, so that your code can be more easily reasoned about and proven correct.
If you don't give them meaningful names (and conversely giving your code a meaningful structure) then you're missing out on the entire purpose of Haskell.
(IMHO the other answers so far, citing monads and other shenanigans, are barking up the wrong tree.)
I always prefer layering state transformers to using a single state over a tuple: it definitely declutters things by letting you "focus" on a specific layer (representations of the x and y variables in our case):
import Control.Monad.Trans.Class
import Control.Monad.Trans.State
foo :: x -> y -> (x, y)
foo x y =
(flip runState) y $ (flip execStateT) x $ do
get >>= \v -> when (a v) (put (f v))
get >>= \v -> put ((if c v then g else h) v)
modify f
lift $ get >>= \v -> when (a v) (put (f v))
lift get >>= \v -> when (b v) (modify g)
The lift function allows us to focus on the inner state layer, which is y.

List Iterator using ContT

I have a simple list that I would like to iterate over "yield"ing between each element and printing that element to the output. I am trying to use the ContT monad to do this but running into issues. Here's what I have so far:
data K a = Nil | K (a,() -> K a)
listIterator :: (Monad m) => [r] -> m (K r)
listIterator [] = return Nil
listIterator (x:xs) = return (ContT (\k -> K (x,k))) >> listIterator xs
runIterator :: IO ()
runIterator = do
a <- listIterator ([1,2,3] :: [Int])
let loop Nil = liftIO $ print "nil"
loop (K (curr,newI)) =
do
liftIO $ print curr
loop (newI ())
loop a
The expected output is:
1
2
3
nil
What I get is:
nil
Any help is appreciated!
listIterator (x:xs) = return (ContT (\k -> K (x,k))) >> listIterator xs
does not do what you expect, equational reasoning
listIterator (x:xs)
= return (ContT (\k -> K (x,k))) >> listIterator xs
= (return (ContT (\k -> K (x,k)))) >>= \_ -> listIterator xs
= (\_ -> listIterator xs) (ContT (\k -> K (x,k)))
= listIterator xs
I'm not sure exactly why you want to use an iterator. Haskell is already lazy, so iteration patterns like this are mostly used only when you have resource management issues that need to interact well with a demand driven usage pattern. And, you don't need the continuation monad at all:
Instead of writing the K constructor to take a tuple it is more idiomatic to
data K a = Nil | K a (() -> K a)
intuitively, the type for the listIterator does not use its monadic structure: it just constructs a value, so
listIterator ::[r] -> K r
listIterator [] = Nil
listIterator (x:xs) = K x (\_ -> listIterator xs)
now life is trivial
runIterator :: IO ()
runIterator = do
let a = listIterator ([1,2,3] :: [Int])
loop Nil = liftIO $ print "nil"
loop (K curr newI) =
do
liftIO $ print curr
loop (newI ())
loop a
which would probably be best to write without the use of do notation.
This may not be the answer you were looking for, but if you are interested in this style of programming, you should look into pipes and similar libraries. (conduit is the rising star in the "real world", but pipes provides a simpler tool for teaching which is why I use it here.)
$ cabal update && cabal install pipes
Pipes are like iterators, except they come in three flavors: those that can acquire input (Consumers), those that produce output (Producers), and those that do both (Pipes). If you connect pipes such that the input and output ends are all satisfied, then it is called a "Pipeline", and it is a self-contained unit that can be run without any additional input.
Pipe provides a monad instance for convenience in creating pipes. The >+> operator connects two pipes together.
import Control.Pipe
import Control.Monad.Trans.Class
import Control.Monad.IO.Class
-- annoyingly, Pipe does not provide a MonadIO instance
instance (MonadIO m) => MonadIO (Pipe a b m) where
liftIO = lift . liftIO
listIterator :: Monad m => [a] -> Producer (Maybe a) m ()
listIterator (x:xs) = yield (Just x) >> listIterator xs
listIterator [] = yield Nothing
printer :: (MonadIO m, Show a) => Consumer (Maybe a) m ()
printer = do
mx <- await
case mx of
Just x -> liftIO (print x) >> printer
Nothing -> liftIO (putStrLn "nil")
main = runPipe $ listIterator [1, 2, 3] >+> printer
The source for Control.Pipe is delightfully simple, especially if you have been reading Gabriel's recent blog posts about Free monads, particularly Why free monads matter and Purify code using free monads.

Resources