I am writing a currying experiment to get a feel for how multiple statements in haskell are chained together to work one after another.
Here is what I got so far
testCurry :: IO ()
testCurry =
(\b ->
(\_ -> putStrLn b)
((\a ->
putStrLn a
) (show 2))
) (show 3)
testCurryExpected :: IO ()
testCurryExpected = do {
a <- return (show 2);
putStrLn a;
b <- return (show 3);
putStrLn b;
}
main :: IO ()
main =
putStrLn "expected: " >>
testCurryExpected >>
putStrLn "given: " >>
testCurry
I know it works if I do it this way:
testCurry :: IO ()
testCurry =
(\b ->
(\next -> next >> putStrLn b)
((\a ->
putStrLn a
) (show 2))
) (show 3)
testCurryExpected :: IO ()
testCurryExpected = do {
a <- return (show 2);
putStrLn a;
b <- return (show 3);
putStrLn b;
}
main :: IO ()
main =
putStrLn "expected: " >>
testCurryExpected >>
putStrLn "given: " >>
testCurry
But I don't know how to simulate the ">>"(then) behavior only using functions.
I know a >> b is defined in terms of a >>= \_ -> b, but I am not sure how >>= is defined in terms of IO a >>= IO b but don't know how to translate this into raw function composition.
Can somebody please help me get this experiment to work?
In short, I want to know if there is a way to do this without >> or >>= operators nor wrapping these operators.
(\a -> \b -> a >> b)(putStrLn "one")(putStrLn "two")
Note: For the sake of concept, I restrict myself to using anonymous functions of at most one argument.
Edit: I found a good-enough solution by creating my own Free representation of putStrLn called Free_PutStrLn that is free of interpretation; using Lists to construct the operation chain, then evaluate it myself later.
data Free_PutStrLn = Free_PutStrLn String deriving Show
eval :: [Free_PutStrLn] -> IO ()
eval a =
foldl (\a -> \b ->
let deconstruct (Free_PutStrLn str) = str in
a >> putStrLn (deconstruct b)
) (return ()) a
testCurry :: [Free_PutStrLn]
testCurry =
(\a ->
[Free_PutStrLn a] ++
((\b ->
[Free_PutStrLn b]
) (show 3))
)(show 2)
main =
putStrLn (show testCurry) >>
eval (testCurry)
JavaScript proof of concept:
// | suspends an object within a function context.
// | first argument is the object to suspend.
// | second argument is the function object into which to feed the suspended
// | argument(first).
// | third argument is where to feed the result of the first argument feeded into
// | second argument. use a => a as identity.
const pure = obj => fn => f => f(fn(obj));
// | the experiment
pure({'console': {
'log': str => new function log() {
this.str = str;
}
}})(free =>
pure(str => () => console.log(str))
(putStrLn =>
pure("hello")(a =>
[free.console.log(a)].concat (
pure("world")(b =>
[free.console.log(b)]
)(a => a))
)((result =>
pure(logObj => logObj.str)
(deconstruct =>
result.map(str => putStrLn(deconstruct(str)))
)(result =>
result.forEach(f => f())
)
)
)
)(a => a)
)(a => a)
But I don't know how to simulate the >> (then) behavior only using functions.
Well, you can't! >> is (in this case) about ordering side-effects. A Haskell function can never have a side effect†. Side effects can only happen in monadic actions, and can be thus ordered by monadic combinators including >>, but without a Monad‡ constraint the notion of “do this and also that” simply doesn't make any sense in Haskell. A Haskell function is not executed, it's merely a mathematical transformation whose result you may evaluate. That result may itself be an actual action with type e.g. IO (), and such an action can be executed and/or monadically chained with other actions. But this is actually somewhat orthogonal to the evaluation of the function that yielded this action.
So that's the answer: “How can I get this currying experiment to behave as expected?” You can't, you need to use one of the monadic combinators instead (or do notation, which is just syntactic sugar for the same).
To also tackle this question from a bit of a different angle: you do not “need monads” to express sequencing of side effects. I might for instance define a type that “specifies side-effects” by generating e.g. Python code which when executed has these effects:
newtype Effect = Effect { pythons :: [String] }
Here, you could then sequence effects by simply concatenating the instruction lists. Again though, this sequencing would not be accomplished by any kind of currying exercise but by boring list concatenation. The preferable interface for this is the monoid class:
import Data.Monoid
instance Monoid Effect where
mempty = Effect []
mappend (Effect e₀) (Effect e₁) = Effect $ e₀ ++ e₁
And then you could simply do:
hello :: Effect
hello = Effect ["print('hello')"] <> Effect ["print('world')"]
(<> is just a shorthand synonym for mappend. You could as well define a custom operator, say # instead to chain those actions, but if there's a standard class that supports some operation it's usually a good idea to employ that!)
Ok, perfectly fine sequencing, no monadic operators required.
But very clearly, just evaluating hello would not cause anything to be printed: it would merely give you some other source code. You'd actually need to feed these instructions to a Python interpreter to accomplish the side-effects.And in principle that's no different with the IO type: evaluating an IO action also never causes any side-effects, only linking it to main (or to the GHCi repl) does. How many lambdas you wrap the subexpressions in is completely irrelevant for this, because side-effect occurance has nothing to do with whether a function gets called anywhere! It only has to do with how the actions get linked to an actual “executor”, be that a Python interpreter or Haskell's own main.
If you now wonder why it has to be those whacky monads if the simpler Monoid also does the trick... the problem with Effect is that it has no such thing as a return value. You can perfectly well generate “pure output” actions this way that simply execute a predetermined Python program, but you can never get back any values from Python this way to use within Haskell to decide what should happen next. This is what monads allow you to do.
†Yes, never. Haskell does not include something called unsafePerformIO. Anybody who claims otherwise in the comments shall suffer nuclear retaliation.
‡To be precise, the weaker Applicative is sufficient.
Related
I am trying to solve arithmetic problems with SBV.
For example
solution :: SymbolicT IO ()
solution = do
[x, y] <- sFloats ["x", "y"]
constrain $ x + y .<= 2
Main> s1 = sat solution
Main> s2 = isSatisfiable solution
Main> s1
Satisfiable. Model:
x = -1.2030502e-17 :: Float
z = -2.2888208e-37 :: Float
Main> :t s1
s1 :: IO SatResult
Main> s2
True
Main> :t s2
s2 :: IO Bool
While I can do useful things, it is easier for me to work with the pure value (SatResult or Bool) and not with the IO monad.
According to the documentation
sat :: Provable a => a -> IO SatResult
constrain :: SolverContext m => SBool -> m ()
sFloats :: [String] -> Symbolic [SFloat]
type Symbolic = SymbolicT IO
Given the type of functions I use, I understand why I always get to the IO monad.
But looking in the generalized versions of the functions for example sFloats.
sFloats :: MonadSymbolic m => [String] -> m [SFloat]
Depending on type of the function, I can work with a different monad than IO. This gives me hope that we will reach a more useful monad, the Identity monad for example.
Unfortunately looking at the examples always solves the problems within the IO monad, so I couldn't find any examples that would work for me.Besides that I don't have much experience working with monads.
Finally My question is:
Is there any way to avoid the IO monad when solving such a problem with SBV?
Thanks in advance
SBV calls out to the SMT solver of your choice (most likely z3, but others are available too), and presents the results back to you. This means that it performs IO under the hood, and thus you cannot be outside the IO monad. You can create custom monads using MonadSymbolic, but that will not get you out of the IO monad: Since the call to the SMT solver does IO you'll always be in IO.
(And I'd strongly caution against uses of unsafePerformIO as suggested in one of the comments. This is really a bad idea; and you can find lots more information on this elsewhere why you shouldn't do so.)
Note that this is no different than any other IO based computation in Haskell: You perform the IO "in-the-wrapper," but once you get your results, you can do whatever you'd like to do with them in a "pure" environment.
Here's a simple example:
import Data.SBV
import Data.SBV.Control
example :: IO ()
example = runSMT $ do
[x, y] <- sFloats ["x", "y"]
constrain $ x + y .<= 2
query $ do cs <- checkSat
case cs of
Unsat -> io $ putStrLn "Unsatisfiable"
Sat -> do xv <- getValue x
yv <- getValue y
let result = use xv yv
io $ putStrLn $ "Result: " ++ show result
_ -> error $ "Solver said: " ++ show cs
-- Use the results from the solver, in a purely functional way
use :: Float -> Float -> Float
use x y = x + y
Now you can say:
*Main> example
Result: -Infinity
The function example has type IO (), because it does involve calling out to the solver and getting the results. However, once you extract those results (via calls to getValue), you can pass them to the function use which has a very simple purely functional type. So, you keep the "wrapper" in the monad, but actual processing, use-of-the values, etc., remain in the pure world.
Alternatively, you can also extract the values and continue from there:
import Data.SBV
import Data.SBV.Control
example :: IO (Maybe (Float, Float))
example = runSMT $ do
[x, y] <- sFloats ["x", "y"]
constrain $ x + y .<= 2
query $ do cs <- checkSat
case cs of
Unsat -> pure Nothing
Sat -> do xv <- getValue x
yv <- getValue y
pure $ Just (xv, yv)
_ -> error $ "Solver said: " ++ show cs
Now you can say:
*Main> Just (a, b) <- example
*Main> a
-Infinity
*Main> b
4.0302105e-21
Long story short: Don't avoid the IO monad. It's there for a very good reason. Get into it, get your results out, and then the rest of your program can remain purely functional, or whatever other monad you might find yourself in.
Note that none of this is really SBV specific. This is the usual Haskell paradigm of how to use functions with side-effects. (For instance, anytime you use readFile to read the contents of a file to process it further.) Do not try to "get rid of the IO." Instead, simply work with it.
Depending on type of the function, I can work with a different monad than IO.
Not meaningfully different, in the sense you'd hope. Every instance of this class is going to be some transformed version of IO. Sorry!
Time to make a plan that involves understanding and working with IO.
I have a concern regarding how far the introduction of IO trickles through a program. Say a function deep within my program is altered to include some IO; how do I isolate this change to not have to also change every function in the path to IO as well?
For instance, in a simplified example:
a :: String -> String
a s = (b s) ++ "!"
b :: String -> String
b s = '!':(fetch s)
fetch :: String -> String
fetch s = reverse s
main = putStrLn $ a "hello"
(fetch here could more realistically be reading a value from a static Map to give as its result)
But say if due to some business logic change, I needed to lookup the value returned by fetch in some database (which I can exemplify here with a call to getLine):
fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
So my question is, how to prevent having to rewrite every function call in this chain?
a :: String -> IO String
a s = fmap (\x -> x ++ "!") (b s)
b :: String -> IO String
b s = fmap (\x -> '!':x) (fetch s)
fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
main = a "hello" >>= putStrLn
I can see that refactoring this would be much simpler if the functions themselves did not depend on each other. That is fine for a simple example:
a :: String -> String
a s = s ++ "!"
b :: String -> String
b s = '!':s
fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
doit :: String -> IO String
doit s = fmap (a . b) (fetch s)
main = doit "hello" >>= putStrLn
but I don't know if that is necessarily practical in more complicated programs.
The only way I've found thus far to really isolate an IO addition like this is to use unsafePerformIO, but, by its very name, I don't want to do that if I can help it. Is there some other way to isolate this change? If the refactoring is substantial, I would start to feel inclined to avoid having to do it (especially under deadlines, etc).
Thanks for any advice!
Here are a few methods I use.
Reduce dependencies on effects by inverting control. (One of the methods you described in your question.) That is, execute the effects outside and pass the results (or functions with those results partially applied) into pure code. Instead of having main → a → b → fetch, have main → fetch and then main → a → b:
a :: String -> String
a f = b f ++ "!"
b :: String -> String
b f = '!' : f
fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
main = do
f <- fetch "hello"
putStrLn $ a f
For more complex cases of this, where you need to thread an argument to do this sort of “dependency injection” through many levels, Reader/ReaderT lets you abstract over the boilerplate.
Write pure code that you expect might need effects in monadic style from the start. (Polymorphic over the choice of monad.) Then if you do eventually need effects in that code, you don’t need to change the implementation, only the signature.
a :: (Monad m) => String -> m String
a s = (++ "!") <$> b s
b :: (Monad m) => String -> m String
b s = ('!' :) <$> fetch s
fetch :: (Monad m) => String -> m String
fetch s = pure (reverse s)
Since this code works for any m with a Monad instance (or in fact just Applicative), you can run it directly in IO, or purely with the “dummy” monad Identity:
main = putStrLn =<< a "hello"
main = putStrLn $ runIdentity $ a "hello"
Then as you need more effects, you can use “mtl style” (as #dfeuer’s answer describes) to enable effects on an as-needed basis, or if you’re using the same monad stack everywhere, just replace m with that concrete type, e.g.:
newtype Fetch a = Fetch { unFetch :: IO a }
deriving (Applicative, Functor, Monad, MonadIO)
a :: String -> Fetch String
a s = pure (b s ++ "!")
b :: String -> Fetch String
b s = ('!' :) <$> fetch s
fetch :: String -> Fetch String
fetch s = do
x <- liftIO getLine
return $ s ++ x
main = putStrLn =<< unFetch (a "hello")
The advantage of mtl style is that you can have multiple different implementations of your effects. That makes things like testing & mocking easy, since you can reuse the logic but run it with different “handlers” for production & testing. In fact, you can get even more flexibility (at the cost of some runtime performance) using an algebraic effects library such as freer-effects, which not only lets the caller change how each effect is handled, but also the order in which they’re handled.
Roll up your sleeves and do the refactoring. The compiler will tell you everywhere that needs to be updated anyway. After enough times doing this, you’ll naturally end up recognising when you’re writing code that will require this refactoring later, so you’ll consider effects from the beginning and not run into the problem.
You’re quite right to doubt unsafePerformIO! It’s not just unsafe because it breaks referential transparency, it’s unsafe because it can break type, memory, and concurrency safety as well—you can use it to coerce any type to any other, cause a segfault, or cause deadlocks and concurrency errors that would ordinarily be impossible. You’re telling the compiler that some code is pure, so it’s going to assume it can do all the transformations it does with pure code—such as duplicating, reordering, or even dropping it, which may completely change the correctness and performance of your code.
The main legitimate use cases for unsafePerformIO are things like using the FFI to wrap foreign code (that you know is pure), or doing GHC-specific performance hacks; stay away from it otherwise, since it’s not meant as an “escape hatch” for ordinary code.
First off, the refactoring doesn't tend to be as bad as you might imagine. Once you make the first change, the type checker will point you to the next few, and so on. But suppose you have a reason to suspect from the start that you might need some extra capability to make a function go. A common way to do this (called mtl-style, after the monad transformer library) is to express your needs in a constraint.
class Monad m => MonadFetch m where
fetch :: String -> m String
a :: MonadFetch m => String -> m String
a s = fmap (\x -> x ++ "!") (b s)
b :: MonadFetch m => String -> m String
b s = fmap (\x -> '!':x) (fetch s)
instance MonadFetch IO where
-- fetch :: String -> IO String
fetch s = do
x <- getLine
return $ s ++ x
instance MonadFetch Identity where
-- fetch :: String -> Identity String
fetch = Identity . reverse
You're no longer tied to a particular monad: you just need one that can fetch. Code operating on an arbitrary MonadFetch instance is pure, except that it can fetch.
I'm using a graphic library in Haskell called Threepenny-GUI. In this library the main function returns a UI monad object. This causes me much headache as when I attempt to unpack IO values into local variables I receive errors complaining of different monad types.
Here's an example of my problem. This is a slightly modified version of the standard main function, as given by Threepenny-GUI's code example:
main :: IO ()
main = startGUI defaultConfig setup
setup :: Window -> UI ()
setup w = do
labelsAndValues <- shuffle [1..10]
shuffle :: [Int] -> IO [Int]
shuffle [] = return []
shuffle xs = do randomPosition <- getStdRandom (randomR (0, length xs - 1))
let (left, (a:right)) = splitAt randomPosition xs
fmap (a:) (shuffle (left ++ right))
Please notice the fifth line:
labelsAndValues <- shuffle [1..10]
Which returns the following error:
Couldn't match type ‘IO’ with ‘UI’
Expected type: UI [Int]
Actual type: IO [Int]
In a stmt of a 'do' block: labelsAndValues <- shuffle [1 .. 10]
As to my question, how do I unpack the IO function using the standard arrow notation (<-), and keep on having these variables as IO () rather than UI (), so I can easily pass them on to other functions.
Currently, the only solution I found was to use liftIO, but this causes conversion to the UI monad type, while I actually want to keep on using the IO type.
A do block is for a specific type of monad, you can't just change the type in the middle.
You can either transform the action or you can nest it inside the do. Most times transformations will be ready for you. You can, for instance have a nested do that works with io and then convert it only at the point of interaction.
In your case, a liftIOLater function is offered to handle this for you by the ThreePennyUI package.
liftIOLater :: IO () -> UI ()
Schedule an IO action to be run later.
In order to perform the converse conversion, you can use runUI:
runUI :: Window -> UI a -> IO a
Execute an UI action in a particular browser window. Also runs all scheduled IO action.
This is more an extended comment - it doesn't address the main question, but your implementation of shufffle. There are 2 issues with it:
Your implementation is inefficient - O(n^2).
IO isn't the right type for it - shuffle has no general side effects, it just needs a source of randomness.
For (1) there are several solutions: One is to use Seq and its index, which is O(log n), which would make shuffle O(n log n). Or you could use ST arrays and one of the standard algorithms to get O(n).
For (2), all you need is threading a random generator, not full power of IO. There is already nice library MonadRandom that defines a monad (and a type-class) for randomized computations. And another package already provides the shuffle function. Since IO is an instance of MonadRandom, you can just use shuffle directly as a replacement for your function.
Under the cover, do is simply syntactic sugar for >>= (bind) and let:
do { x<-e; es } = e >>= \x -> do { es }
do { e; es } = e >> do { es }
do { e } = e
do {let ds; es} = let ds in do {es}
And the type of bind:
(>>=) :: Monad m => a -> (a -> m b) -> m b
So yeah it only "supports" one Monad
I found the following Haskell code, but I'm confused:
main = putStrLn "Enter 1st String:"
>> getLine
>>= \a -> read a
What do the two "greater than" symbols (>>) mean? A new statement?
What do the two "greater than" symbols followed by an equal sign (>>=) mean?
This Haskell code throws the following error:
a.hs:3:13:
No instance for (Read (IO t0)) arising from a use of ‘read’
In the expression: read a
In the second argument of ‘(>>=)’, namely ‘\ a -> read a’
In the expression:
putStrLn "Enter 1st String:" >> getLine >>= \ a -> read a
1) does two greater than symbols mean a new statement?
In this context, yes. In the IO monad, >> is a rough equivalent of the ; in many imperative programming languages.
2) what does two greater than symbols followed by equal sign mean?
x >>= y is like x >> y except it takes the result of x and applies to y, which has to be a function. Briefly put, getLine >>= \a -> action means "read a line, bind that value to variable a, and run action (which can depend from a).
I'd recommend a monad tutorial to fully understand these. You can start with a general tutorial such as LYAH.
Your code is more commonly written in do notation:
main = do
putStrLn "Enter 1st String:"
a <- getLine
read a
where the last line makes no sense: read returns a value but does not do any I/O, so we can not chain that to a sequence of I/O actions. This triggers a compiler error. If you know some imperative programming, think about the pseudocode
print("some message");
a = inputLine();
toInteger(a);
The last line makes no sense: it converts the string into an integer... and then does not use the result in any way.
About your second question: your main is not a valid monadic expression. When specialised to the IO monad, the bind and then operators have type
(>>=) :: IO a -> (a -> IO b) -> IO b
(>>) :: IO a -> IO b -> IO b
If you try to align the types of your main expression, you will identify the problem very quickly:
putStrLn "Enter 1st String:" >> getLine >>= \a -> read a
{ IO () } {IO String} {actual: Read t => String -> t }
{ IO String } {expected: String -> IO t} ??? }
The type expected for the second argument of >>= is String -> IO t, but read doesn't return an IO value.
I thought that in principle Haskell's type system would forbid calls to impure functions (i.e. f :: a -> IO b) from pure ones, but today I realized that by calling them with return they compile just fine. In this example:
h :: Maybe ()
h = do
return $ putStrLn "???"
return ()
h works in the Maybe monad, but it's a pure function nevertheless. Compiling and running it simply returns Just () as one would expect, without actually doing any I/O. I think Haskell's laziness puts the things together (i.e. putStrLn's return value is not used - and can't since its value constructors are hidden and I can't pattern match against it), but why is this code legal? Are there any other reasons that makes this allowed?
As a bonus, related question: in general, is it possible to forbid at all the execution of actions of a monad from within other ones, and how?
IO actions are first-class values like any other; that's what makes Haskell's IO so expressive, allowing you to build higher-order control structures (like mapM_) from scratch. Laziness isn't relevant here,1 it's just that you're not actually executing the action. You're just constructing the value Just (putStrLn "???"), then throwing it away.
putStrLn "???" existing doesn't cause a line to be printed to the screen. By itself, putStrLn "???" is just a description of some IO that could be done to cause a line to be printed to the screen. The only execution that happens is executing main, which you constructed from other IO actions, or whatever actions you type into GHCi. For more information, see the introduction to IO.
Indeed, it's perfectly conceivable that you might want to juggle about IO actions inside Maybe; imagine a function String -> Maybe (IO ()), which checks the string for validity, and if it's valid, returns an IO action to print some information derived from the string. This is possible precisely because of Haskell's first-class IO actions.
But a monad has no ability to execute the actions of another monad unless you give it that ability.
1 Indeed, h = putStrLn "???" `seq` return () doesn't cause any IO to be performed either, even though it forces the evaluation of putStrLn "???".
Let's desugar!
h = do return (putStrLn "???"); return ()
-- rewrite (do foo; bar) as (foo >> do bar)
h = return (putStrLn "???") >> do return ()
-- redundant do
h = return (putStrLn "???") >> return ()
-- return for Maybe = Just
h = Just (putStrLn "???") >> Just ()
-- replace (foo >> bar) with its definition, (foo >>= (\_ -> bar))
h = Just (putStrLn "???") >>= (\_ -> Just ())
Now, what happens when you evaluate h?* Well, for Maybe,
(Just x) >>= f = f x
Nothing >>= f = Nothing
So we pattern match the first case
f x
-- x = (putStrLn "???"), f = (\_ -> Just ())
(\_ -> Just ()) (putStrLn "???")
-- apply the argument and ignore it
Just ()
Notice how we never had to perform putStrLn "???" in order to evaluate this expression.
*n.b. It is somewhat unclear at which point "desugaring" stops and "evaluation" begins. It depends on your compiler's inlining decisions. Pure computations could be evaluated entirely at compile time.