A -> IO B to IO (A -> B) - haskell

I want to convert a function A -> IO B to IO (A -> B), knowing that there is only a finite number of possible values of A. At the moment I just do
convert :: (A -> IO B) -> IO (A -> B)
convert f = do
b1 <- f a1
b2 <- f a2
...
let f' a1 = b1
f' a2 = b2
...
return f'
However I'm not satisfied with the amount of code this requires.

A slightly souped-up version of Joachim's answer, that uses Data.Map to perform the lookup faster. I'll be using the TupleSections pragma as well.
{-# LANGUAGE TupleSections #-}
import Data.Map
import Control.Monad
For added neatness, assume that your Piece type can be given Ord, Bounded and Enum instances.
data Piece = Knight | Bishop | Rook deriving (Ord,Bounded,Enum,Show)
and define the useful enumerate function
enumerate :: (Bounded a, Enum a) => [a]
enumerate = [minBound..maxBound]
Now you can do
convert :: (Monad m, Bounded a, Enum a, Ord a) => (a -> m b) -> m (a -> b)
convert f = do
memo <- sequence [liftM (a,) (f a) | a <- enumerate]
return (fromList memo!)

If you have a list values :: [A], and A has an Eq-Instance, this would work:
convert :: (A -> IO B) -> IO (A -> B)
convert f = do
lookupTable <- sequence [ (\b -> (a,b)) `fmap` f a | a <- values]
return $ (\a -> fromJust (lookup a lookupTable))
As other have noted, if you don’t mind the additional type class requirements for A, you can use maps or hashmaps to speed up the lookup.
Also, from your use-case description, it seems that you are loading static data from a file that comes with your program. Depending on the environment where your final program runs (e.g. guaranteed that the files exist and are not changing), this might be a valid use for unsafePerformIO to simply define A -> B as a top-level function. Alternatively there are ways to include binary blobs in the compile source.

For the sake of completeness, I'll mention that the countable package on Hackage makes this possible by providing the Finite type class. You define something like
instance Finite Piece where
allValues = [Pawn, Knight, Bishop, Rook, Queen, King]
then you have
assemble :: (Finite a, Applicative f) => (a -> f b) -> f (a -> b)
which will specialise to precisely what you need.
Looking at the source, it seems that it uses an association list, so it would be slow if your type was large. Plus, it defines some orphan instances of Foldable and Traversable and Eq (!) for functions, which some may regard as distasteful.

You have function f :: A -> IO B and you have g :: IO A,
you use your convert function with Applicative <*> :: f (a -> b) -> f a -> f b as
fg :: IO a -> (a ->IO B) -> IO B
fg g f = (convert f) <*> g
But you can just use monad (>>=) :: m a -> (a -> m b) -> m b,
fg :: IO a -> (a ->IO B) -> IO B
fg g f = g >>= f

Your function signature permits any function a->m b on input, yet inside you assume a specific range of values. convert is not as polymorphic as the signature seems to declare.
What you have done is created a Map from a to b, then made a pure function that looks up a pure value in that map. Here's why:
What you are asking for is similar to implementing tensorial strength strength :: (Monad m) => (a, m b) -> m (a, b) for a monoidal category (C, ⊗, I) - given a binary relation ⊗ in category C and a monad m, convert a ⊗ m b to m (a ⊗ b). When this is possible for a binary relationship that meets certain requirements, the monad is strong. In Haskell all monads are strong, if tensorial product a ⊗ b is chosen to be a pair (a, b): strength (a, mb) = mb >>= return . (a,). Yet, here you are attempting to do the same for a binary relationship ->. Unfortunately, a -> b cannot be chosen to be a tensor product, because it is not a bi-functor - it is contravariant in a. So what you want cannot be accomplished for arbitrary functions.
What is different in your case, is that essentially you built all pairs (a,b). The amount of code, therefore, can be reduced if you explicitly enumerate all possible pairs of a and b, for example by building a m (Map a b). The others here offered nice sugars exposing "function-like" interfaces, but they are merely lookups in the map.

Related

Accidentally backticking a non-binary function creates bizarre behaviour

Here's the offending code (also on lpaste.net):
module Data.Graph.Dijkstra
( dijkstra
, dijkstraPath
) where
-- Graph library import
import Data.Graph.Inductive hiding (dijkstra)
-- Priority queue import
import qualified Data.PQueue.Prio.Min as PQ
-- Standard imports
import Data.List (find)
import Data.Maybe (fromJust)
import Data.Monoid
-- Internal routine implementing Dijkstra's shortest paths
-- algorithm. Deemed internal because it needs to be kickstarted with
-- a singleton node queue. Based on FGL's current implementation of
-- Dijkstra.
dijkstraInternal ::
(Graph gr, Ord b, Monoid b) => gr a b -> PQ.MinPQueue b [Node] -> [[Node]]
dijkstraInternal g q
| PQ.null q = []
| otherwise =
case match v g of
(Just cxt,g') -> p:dijkstraInternal g' (PQ.unions (q' : expand cxt minDist p))
(Nothing, g') -> dijkstraInternal g' q'
where ((minDist,p#(v:_)), q') = PQ.deleteFindMin q
expand (_,_,_,s) dist pathToC =
map (\(edgeCost,n) -> PQ.singleton (dist `mappend` edgeCost) (n:pathToC)) s
-- Given a graph and a start node, returns a list of lists of nodes
-- corresponding to the shortest paths from the start to all other
-- nodes, where the edge costs are accumulated according to the Monoid
-- instance of the edge label type and costs are compared by the edge
-- label's Ord instance.
dijkstra :: (Graph gr, Ord b, Monoid b) => gr a b -> Node -> [[Node]]
dijkstra g start = dijkstraInternal g (PQ.singleton `mempty` [start]) -- !!!
dijkstraPath :: (Graph gr, Ord b, Monoid b) => gr a b -> Node -> Node -> [LNode a]
dijkstraPath g start goal =
let paths = dijkstra g start
pathNodes = find ((goal ==) . head) paths -- Can paths be empty?
in
case pathNodes of
Nothing -> []
Just ps -> reverse $ map (\n -> (n, fromJust $ lab g n)) ps
The weirdness is in line 39, marked with the -- !!! comment. This code compiles, but the runtime error is that no matter what, the PQ.singleton function returns an empty priority queue. I realized I had accidentally added backticks to mempty, so when I removed those the code compiled and worked as expected.
This however struck me as strange. How could the code have correctly compiled with backticks around mempty, which is not a binary function at all (mempty :: a)?
After some very generous help on #haskell, I found that it had something to do with the Monoid instance for functions:
instance Monoid b => Monoid (a -> b)
I now have an extremely vague understanding of why this error successfully typechecked, but I still feel somehow morally wronged. Can someone explain exactly how this happened?
Additionally, I'd also like to direct attention to the priority queue's singleton function that I'm using: according to the source, it doesn’t return an empty queue. However, at line 24, that same priority queue immediately gets evaluated as being empty. (I verified this with trace calls.)
So, in general, the code:
a `f` b
is just syntactic sugar for:
f a b
Therefore your code became:
mempty PQ.singleton [start]
So the type-checker inferred the type for that particular mempty:
mempty :: (k -> a -> PQ.MinPQueue k a) -> [Node] -> PQ.MinPQueue b [Node]
You correctly found the right instance that is the problem. Anything of type a -> b is a Monoid, provided that b is. So let's bracket that type above:
mempty :: (k -> a -> PQ.MinPQueue k a) -> ([Node] -> PQ.MinPQueue b [Node])
So, that type can be a Monoid if [Node] -> PQ.MinPQueue b [Node] is a Monoid. And by the same logic, [Node] -> PQ.MinPQueue b [Node] can be a Monoid if PQ.MinPQueue b [Node] is one. Which it is. So the type-checker is fine with this code.
Presumably the implementation of our troublesome instance is:
instance Monoid => Monoid (a -> b) where
mempty = const mempty
So overall, you get an empty priority queue. So really, I think it comes down to a question of whether it was wise for the designers to include this instance at all. Its net effect is that any function returning a monoid can be a monoid, which should allow you to combine the results. The more useful case here is mappend, which can append two a -> b functions by applying them both and using mappend to combine the results. For example:
extremes = (return . minimum) `mappend` (return . maximum)
rather than:
extremes xs = [minimum xs, maximum xs]
Hmmm, maybe someone else can produce a sensible terser example.
So backticks turn a binary function into an infix operator, making
x `op` y
equivalent to
op x y
So op needs to be of type a -> b -> c where x :: a and y :: b.
In your case, op was mempty, with the type Monoid m => m. But we know it to be of the form a -> b -> c, so substitute that and you get (this is no longer valid syntax) Monoid (a -> b -> c) => a -> b -> c, because we can substitute that m for anything as long as the constraint holds.
Now we know (due to the instance declaration) that any function of the form s -> t, where t is a Monoid, is a Monoid itself, and we also know that a -> b -> c is really a -> (b -> c), i.e. a function taking one argument and returning another function. So if we substitute a for s and (b -> c) for t, the we fulfill the Monoid instance, if t is a Monoid. Of course, t is (b -> c), so we can apply the same Monoid instance again (with s = b and t = c), so if c is a Monoid, we're good.
So what is c? The expression you had was
PQ.singleton `mempty` [start]
i.e.
mempty PQ.singleton [start]
The instance declaration for Monoid (a -> b) defines mempty _ = mempty, i.e. it's a function that ignores its argument and returns the empty element of the b Monoid. In other words, we can expand the call above to
mempty [start]
i.e. we ignore the argument and use mempty of the inner Monoid (which is b -> c). Then we repeat, ignoring the argument again:
mempty
So the expression you had is just equivalent to a single mempty, which has the type Monoid c => c, i.e. it can be any Monoid whatsoever.
In your case, the larger expression deduces c to be a PQ.MinPQueue. And MinPQueue is a Monoid instance with mempty being the empty queue.
This is how you end up with the result you're seeing.
You've had a couple good answers here already, I thought I would just post this since it's a bit simpler and helped me as I was puzzling this out in ghci.
mempty :: (a -> b) = mempty _ = mempty So it's essentially const mempty.
λ> :t mempty :: (a -> b)
<interactive>:1:1:
No instance for (Monoid b) arising from a use of `mempty'
So b has to be a Monoid since we're asking for the mempty of that type, makes sense.
λ> :t mempty :: (a -> [b])
mempty :: (a -> [b]) :: a -> [b]
λ> :t mempty :: (a -> c -> [b])
mempty :: (a -> c -> [b]) :: a -> c -> [b]
We can recursively chain these. Since (->) is right associative (a -> b) may represent (a -> c -> d) when b == (c -> d). So we can supply an arbitrary number of arguments and the mempty for functions will be recursively applied until it's consumed all arguments.
λ> import Data.Map
λ> (mempty :: (a -> c -> Map Int Int)) 4 5
fromList []
λ> (mempty :: (a -> c -> d -> Map Int Int)) 4 5 6
fromList []
So we see that applying the function mempty will throw away any arguments it's given and return the mempty for whatever type is expected at the position the expression is in.

How to express existential types using higher rank (rank-N) type polymorphism?

We're used to having universally quantified types for polymorphic functions. Existentially quantified types are used much less often. How can we express existentially quantified types using universal type quantifiers?
It turns out that existential types are just a special case of Σ-types (sigma types). What are they?
Sigma types
Just as Π-types (pi types) generalise our ordinary function types, allowing the resulting type to depend on the value of its argument, Σ-types generalise pairs, allowing the type of second component to depend on the value of the first one.
In a made-up Haskell-like syntax, Σ-type would look like this:
data Sigma (a :: *) (b :: a -> *)
= SigmaIntro
{ fst :: a
, snd :: b fst
}
-- special case is a non-dependent pair
type Pair a b = Sigma a (\_ -> b)
Assuming * :: * (i.e. the inconsistent Set : Set), we can define exists a. a as:
Sigma * (\a -> a)
The first component is a type and the second one is a value of that type. Some examples:
foo, bar :: Sigma * (\a -> a)
foo = SigmaIntro Int 4
bar = SigmaIntro Char 'a'
exists a. a is fairly useless - we have no idea what type is inside, so the only operations that can work with it are type-agnostic functions such as id or const. Let's extend it to exists a. F a or even exists a. Show a => F a. Given F :: * -> *, the first case is:
Sigma * F -- or Sigma * (\a -> F a)
The second one is a bit trickier. We cannot just take a Show a type class instance and put it somewhere inside. However, if we are given a Show a dictionary (of type ShowDictionary a), we can pack it with the actual value:
Sigma * (\a -> (ShowDictionary a, F a))
-- inside is a pair of "F a" and "Show a" dictionary
This is a bit inconvenient to work with and assumes that we have a Show dictionary around, but it works. Packing the dictionary along is actually what GHC does when compiling existential types, so we could define a shortcut to have it more convenient, but that's another story. As we will learn soon enough, the encoding doesn't actually suffer from this problem.
Digression: thanks to constraint kinds, it's possible to reify the type class into concrete data type. First, we need some language pragmas and one import:
{-# LANGUAGE ConstraintKinds, GADTs, KindSignatures #-}
import GHC.Exts -- for Constraint
GADTs already give us the option to pack a type class along with the constructor, for example:
data BST a where
Nil :: BST a
Node :: Ord a => a -> BST a -> BST a -> BST a
However, we can go one step further:
data Dict :: Constraint -> * where
D :: ctx => Dict ctx
It works much like the BST example above: pattern matching on D :: Dict ctx gives us access to the whole context ctx:
show' :: Dict (Show a) -> a -> String
show' D = show
(.+) :: Dict (Num a) -> a -> a -> a
(.+) D = (+)
We also get quite natural generalisation for existential types that quantify over more type variables, such as exists a b. F a b.
Sigma * (\a -> Sigma * (\b -> F a b))
-- or we could use Sigma just once
Sigma (*, *) (\(a, b) -> F a b)
-- though this looks a bit strange
The encoding
Now, the question is: can we encode Σ-types with just Π-types? If yes, then the existential type encoding is just a special case. In all glory, I present you the actual encoding:
newtype SigmaEncoded (a :: *) (b :: a -> *)
= SigmaEncoded (forall r. ((x :: a) -> b x -> r) -> r)
There are some interesting parallels. Since dependent pairs represent existential quantification and from classical logic we know that:
(∃x)R(x) ⇔ ¬(∀x)¬R(x) ⇔ (∀x)(R(x) → ⊥) → ⊥
forall r. r is almost ⊥, so with a bit of rewriting we get:
(∀x)(R(x) → r) → r
And finally, representing universal quantification as a dependent function:
forall r. ((x :: a) -> R x -> r) -> r
Also, let's take a look at the type of Church-encoded pairs. We get a very similar looking type:
Pair a b ~ forall r. (a -> b -> r) -> r
We just have to express the fact that b may depend on the value of a, which we can do by using dependent function. And again, we get the same type.
The corresponding encoding/decoding functions are:
encode :: Sigma a b -> SigmaEncoded a b
encode (SigmaIntro a b) = SigmaEncoded (\f -> f a b)
decode :: SigmaEncoded a b -> Sigma a b
decode (SigmaEncoded f) = f SigmaIntro
-- recall that SigmaIntro is a constructor
The special case actually simplifies things enough that it becomes expressible in Haskell, let's take a look:
newtype ExistsEncoded (F :: * -> *)
= ExistsEncoded (forall r. ((x :: *) -> (ShowDictionary x, F x) -> r) -> r)
-- simplify a bit
= ExistsEncoded (forall r. (forall x. (ShowDictionary x, F x) -> r) -> r)
-- curry (ShowDictionary x, F x) -> r
= ExistsEncoded (forall r. (forall x. ShowDictionary x -> F x -> r) -> r)
-- and use the actual type class
= ExistsEncoded (forall r. (forall x. Show x => F x -> r) -> r)
Note that we can view f :: (x :: *) -> x -> x as f :: forall x. x -> x. That is, a function with extra * argument behaves as a polymorphic function.
And some examples:
showEx :: ExistsEncoded [] -> String
showEx (ExistsEncoded f) = f show
someList :: ExistsEncoded []
someList = ExistsEncoded $ \f -> f [1]
showEx someList == "[1]"
Notice that someList is actually constructed via encode, but we dropped the a argument. That's because Haskell will infer what x in the forall x. part you actually mean.
From Π to Σ?
Strangely enough (although out of the scope of this question), you can encode Π-types via Σ-types and regular function types:
newtype PiEncoded (a :: *) (b :: a -> *)
= PiEncoded (forall r. Sigma a (\x -> b x -> r) -> r)
-- \x -> is lambda introduction, b x -> r is a function type
-- a bit confusing, I know
encode :: ((x :: a) -> b x) -> PiEncoded a b
encode f = PiEncoded $ \sigma -> case sigma of
SigmaIntro a bToR -> bToR (f a)
decode :: PiEncoded a b -> (x :: a) -> b x
decode (PiEncoded f) x = f (SigmaIntro x (\b -> b))
I found an anwer in Proofs and Types by Jean-Yves Girard, Yves Lafont and Paul Taylor.
Imagine we have some one-argument type t :: * -> * and construct an existential type that holds t a for some a: exists a. t a. What can we do with such a type? In order to compute something out of it we need a function that can accept t a for arbitrary a, that means a function of type forall a. t a -> b. Knowing this, we can encode an existential type simply as a function that takes functions of type forall a. t a -> b, supplies the existential value to them and returns the result b:
{-# LANGUAGE RankNTypes #-}
newtype Exists t = Exists (forall b. (forall a. t a -> b) -> b)
Creating an existential value is now easy:
exists :: t a -> Exists t
exists x = Exists (\f -> f x)
And if we want to unpack the existential value, we just apply its content to a function that produces the result:
unexists :: (forall a. t a -> b) -> Exists t -> b
unexists f (Exists e) = e f
However, purely existential types are of very little use. We cannot do anything reasonable with a value we know nothing about. More often we need an existential type with a type class constraint. The procedure is just the same, we just add a type class constraint for a. For example:
newtype ExistsShow t = ExistsShow (forall b. (forall a. Show a => t a -> b) -> b)
existsShow :: Show a => t a -> ExistsShow t
existsShow x = ExistsShow (\f -> f x)
unexistsShow :: (forall a. Show a => t a -> b) -> ExistsShow t -> b
unexistsShow f (ExistsShow e) = e f
Note: Using existential quantification in functional programs is often considered a code-smell. It can indicate that we haven't liberated ourselves from OO thinking.

why can't a function take monadic value and return another monadic value?

Let's say that we have two monadic functions:
f :: a -> m b
g :: b -> m c
h :: a -> m c
The bind function is defined as
(>>=) :: m a -> (a -> m b) -> m b
My question is why can not we do something like below. Declare a function which would take a monadic value and returns another monadic value?
f :: a -> m b
g :: m b -> m c
h :: a -> m c
The bind function is defined as
(>>=) :: m a -> (ma -> m b) -> m b
What is in the haskell that restricts a function from taking a monadic value as it's argument?
EDIT: I think I did not make my question clear. The point is, when you are composing functions using bind operator, why is that the second argument for bind operator is a function which takes non-monadic value (b)? Why can't it take a monadic value (mb) and give back mc . Is it that, when you are dealing with monads and the function you would compose will always have the following type.
f :: a -> m b
g :: b -> m c
h :: a -> m c
and h = f 'compose' g
I am trying to learn monads and this is something I am not able to understand.
A key ability of Monad is to "look inside" the m a type and see an a; but a key restriction of Monad is that it must be possible for monads to be "inescapable," i.e., the Monad typeclass operations should not be sufficient to write a function of type Monad m => m a -> a. (>>=) :: Monad m => m a -> (a -> m b) -> m b gives you exactly this ability.
But there's more than one way to achieve that. The Monad class could be defined like this:
class Functor f where
fmap :: (a -> b) -> f a -> f b
class Functor f => Monad m where
return :: a -> m a
join :: m (m a) -> m a
You ask why could we not have a Monad m => m a -> (m a -> m b) -> m b function. Well, given f :: a -> b, fmap f :: ma -> mb is basically that. But fmap by itself doesn't give you the ability to "look inside" a Monad m => m a yet not be able to escape from it. However join and fmap together give you that ability. (>>=) can be written generically with fmap and join:
(>>=) :: Monad m => m a -> (a -> m b) -> m b
ma >>= f = join (fmap f ma)
In fact this is a common trick for defining a Monad instance when you're having trouble coming up with a definition for (>>=)—write the join function for your would-be monad, then use the generic definition of (>>=).
Well, that answers the "does it have to be the way it is" part of the question with a "no." But, why is it the way it is?
I can't speak for the designers of Haskell, but I like to think of it this way: in Haskell monadic programming, the basic building blocks are actions like these:
getLine :: IO String
putStrLn :: String -> IO ()
More generally, these basic building blocks have types that look like Monad m => m a, Monad m => a -> m b, Monad m => a -> b -> m c, ..., Monad m => a -> b -> ... -> m z. People informally call these actions. Monad m => m a is a no-argument action, Monad m => a -> m b is a one-argument action, and so on.
Well, (>>=) :: Monad m => m a -> (a -> m b) -> m b is basically the simplest function that "connects" two actions. getLine >>= putStrLn is the action that first executes getLine, and then executes putStrLn passing it the result that was obtained from executing getLine. If you had fmap and join and not >>= you'd have to write this:
join (fmap putStrLn getLine)
Even more generally, (>>=) embodies a notion much like a "pipeline" of actions, and as such is the more useful operator for using monads as a kind of programming language.
Final thing: make sure you are aware of the Control.Monad module. While return and (>>=) are the basic functions for monads, there's endless other more high-level functions that you can define using those two, and that module gathers a few dozen of the more common ones. Your code should not be forced into a straitjacket by (>>=); it's a crucial building block that's useful both on its own and as a component for larger building blocks.
why can not we do something like below. Declare a function which would take a monadic value and returns another monadic value?
f :: a -> m b
g :: m b -> m c
h :: a -> m c
Am I to understand that you wish to write the following?
compose :: (a -> m b) -> (m b -> m c) -> (a -> m c)
compose f g = h where
h = ???
It turns out that this is just regular function composition, but with the arguments in the opposite order
(.) :: (y -> z) -> (x -> y) -> (x -> z)
(g . f) = \x -> g (f x)
Let's choose to specialize (.) with the types x = a, y = m b, and z = m c
(.) :: (m b -> m c) -> (a -> m b) -> (a -> m c)
Now flip the order of the inputs, and you get the desired compose function
compose :: (a -> m b) -> (m b -> m c) -> (a -> m c)
compose = flip (.)
Notice that we haven't even mentioned monads anywhere here. This works perfectly well for any type constructor m, whether it is a monad or not.
Now let's consider your other question. Suppose we want to write the following:
composeM :: (a -> m b) -> (b -> m c) -> (a -> m c)
Stop. Hoogle time. Hoogling for that type signature, we find there is an exact match! It is >=> from Control.Monad, but notice that for this function, m must be a monad.
Now the question is why. What makes this composition different from the other one such that this one requires m to be a Monad, while the other does not? Well, the answer to that question lies at the heart of understanding what the Monad abstraction is all about, so I'll leave a more detailed answer to the various internet resources that speak about the subject. Suffice it to say that there is no way to write composeM without knowing something about m. Go ahead, try it. You just can't write it without some additional knowledge about what m is, and the additional knowledge necessary to write this function just happens to be that m has the structure of a Monad.
Let me paraphrase your question a little bit:
why can't don't we use functions of type g :: m a -> m b with Monads?
The answer is, we do already, with Functors. There's nothing especially "monadic" about fmap f :: Functor m => m a -> m b where f :: a -> b. Monads are Functors; we get such functions just by using good old fmap:
class Functor f a where
fmap :: (a -> b) -> f a -> f b
If you have two functions f :: m a -> m b and a monadic value x :: m a, you can simply apply f x. You don't need any special monadic operator for that, just function application. But a function such as f can never "see" a value of type a.
Monadic composition of functions is much stronger concept and functions of type a -> m b are the core of monadic computations. If you have a monadic value x :: m a, you cannot "get into it" to retrieve some value of type a. But, if you have a function f :: a -> m b that operates on values of type a, you can compose the value with the function using >>= to get x >>= f :: m b. The point is, f "sees" a value of type a and can work with it (but it cannot return it, it can only return another monadic value). This is the benefit of >>= and each monad is required to provide its proper implementation.
To compare the two concepts:
If you have g :: m a -> m b, you can compose it with return to get g . return :: a -> m b (and then work with >>=), but
not vice versa. In general there is no way of creating a function of type m a -> m b from a function of type a -> m b.
So composing functions of types like a -> m b is a strictly stronger concept than composing functions of types like m a -> m b.
For example: The list monad represents computations that can give a variable number of answers, including 0 answers (you can view it as non-deterministic computations). The key elements of computing within list monad are functions of type a -> [b]. They take some input and produce a variable number of answers. Composition of these functions takes the results from the first one, applies the second function to each of the results, and merges it into a single list of all possible answers.
Functions of type [a] -> [b] would be different: They'd represent computations that take multiple inputs and produce multiple answers. They can be combined too, but we get something less strong than the original concept.
Perhaps even more distinctive example is the IO monad. If you call getChar :: IO Char and used only functions of type IO a -> IO b, you'd never be able to work with the character that was read. But >>= allows you to combine such a value with a function of type a -> IO b that can "see" the character and do something with it.
As others have pointed out, there is nothing that restricts a function to take a monadic value as argument. The bind function itself takes one, but not the function that is given to bind.
I think you can make this understandable to yourself with the "Monad is a Container" metaphor. A good example for this is Maybe. While we know how to unwrap a value from the Maybe conatiner, we do not know it for every monad, and in some monads (like IO) it is entirely impossible.
The idea is now that the Monad does this behind the scenes in a way you don't have to know about. For example, you indeed need to work with a value that was returned in the IO monad, but you cannot unwrap it, hence the function that does this needs to be in the IO monad itself.
I like to think of a monad as a recipe for constructing a program with a specific context. The power that a monad provides is the ability to, at any stage within your constructed program, branch depending upon the previous value. The usual >>= function was chosen as being the most generally useful interface to this branching ability.
As an example, the Maybe monad provides a program that may fail at some stage (the context is the failure state). Consider this psuedo-Haskell example:
-- take a computation that produces an Int. If the current Int is even, add 1.
incrIfEven :: Monad m => m Int -> m Int
incrIfEven anInt =
let ourInt = currentStateOf anInt
in if even ourInt then return (ourInt+1) else return ourInt
In order to branch based on the current result of a computation, we need to be able to access that current result. The above psuedo-code would work if we had access to currentStateOf :: m a -> a, but that isn't generally possible with monads. Instead we write our decision to branch as a function of type a -> m b. Since the a isn't in a monad in this function, we can treat it like a regular value, which is much easier to work with.
incrIfEvenReal :: Monad m => m Int -> m Int
incrIfEvenReal anInt = anInt >>= branch
where branch ourInt = if even ourInt then return (ourInt+1) else return ourInt
So the type of >>= is really for ease of programming, but there are a few alternatives that are sometimes more useful. Notably the function Control.Monad.join, which when combined with fmap gives exactly the same power as >>= (either can be defined in terms of the other).
The reason (>>=)'s second argument does not take a monad as input is because there is no need to bind such a function at all. Just apply it:
m :: m a
f :: a -> m b
g :: m b -> m c
h :: c -> m b
(g (m >>= f)) >>= h
You don't need (>>=) for g at all.
The function can take a monadic value if it wants. But it is not forced to do so.
Consider the following contrived definitions, using the list monad and functions from Data.Char:
m :: [[Int]]
m = [[71,72,73], [107,106,105,104]]
f :: [Int] -> [Char]
f mx = do
g <- [toUpper, id, toLower]
x <- mx
return (g $ chr x)
You can certainly run m >>= f; the result will have type [Char].
(It's important here that m :: [[Int]] and not m :: [Int]. >>= always "strips off" one monadic layer from its first argument. If you don't want that to happen, do f m instead of m >>= f.)
As others have mentioned, nothing restricts such functions from being written.
There is, in fact, a large family of functions of type :: m a -> (m a -> m b) -> m b:
f :: Monad m => Int -> m a -> (m a -> m b) -> m b
f n m mf = replicateM_ n m >>= mf m
where
f 0 m mf = mf m
f 1 m mf = m >> mf m
f 2 m mf = m >> m >> mf m
... etc. ...
(Note the base case: when n is 0, it's simply normal functional application.)
But what does this function do? It performs a monadic action multiple times, finally throwing away all the results, and returning the application of mf to m.
Useful sometimes, but hardly generally useful, especially compared to >>=.
A quick Hoogle search doesn't turn up any results; perhaps a telling result.

Does a function like this already exist? (Or, what's a better name for this function?)

I've written code with the following pattern several times recently, and was wondering if there was a shorter way to write it.
foo :: IO String
foo = do
x <- getLine
putStrLn x >> return x
To make things a little cleaner, I wrote this function (though I'm not sure it's an appropriate name):
constM :: (Monad m) => (a -> m b) -> a -> m a
constM f a = f a >> return a
I can then make foo like this:
foo = getLine >>= constM putStrLn
Does a function/idiom like this already exist? And if not, what's a better name for my constM?
Well, let's consider the ways that something like this could be simplified. A non-monadic version would I guess look something like const' f a = const a (f a), which is clearly equivalent to flip const with a more specific type. With the monadic version, however, the result of f a can do arbitrary things to the non-parametric structure of the functor (i.e., what are often called "side effects"), including things that depend on the value of a. What this tells us is that, despite pretending like we're discarding the result of f a, we're actually doing nothing of the sort. Returning a unchanged as the parametric part of the functor is far less essential, and we could replace return with something else and still have a conceptually similar function.
So the first thing we can conclude is that it can be seen as a special case of a function like the following:
doBoth :: (Monad m) => (a -> m b) -> (a -> m c) -> a -> m c
doBoth f g a = f a >> g a
From here, there are two different ways to look for an underlying structure of some sort.
One perspective is to recognize the pattern of splitting a single argument among multiple functions, then recombining the results. This is the concept embodied by the Applicative/Monad instances for functions, like so:
doBoth :: (Monad m) => (a -> m b) -> (a -> m c) -> a -> m c
doBoth f g = (>>) <$> f <*> g
...or, if you prefer:
doBoth :: (Monad m) => (a -> m b) -> (a -> m c) -> a -> m c
doBoth = liftA2 (>>)
Of course, liftA2 is equivalent to liftM2 so you might wonder if lifting an operation on monads into another monad has something to do with monad transformers; in general the relationship there is awkward, but in this case it works easily, giving something like this:
doBoth :: (Monad m) => ReaderT a m b -> ReaderT a m c -> ReaderT a m c
doBoth = (>>)
...modulo appropriate wrapping and such, of course. To specialize back to your original version, the original use of return now needs to be something with type ReaderT a m a, which shouldn't be too hard to recognize as the ask function for reader monads.
The other perspective is to recognize that functions with types like (Monad m) => a -> m b can be composed directly, much like pure functions. The function (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) gives a direct equivalent to function composition (.) :: (b -> c) -> (a -> b) -> (a -> c), or you can instead make use of Control.Category and the newtype wrapper Kleisli to work with the same thing in a generic way.
We still need to split the argument, however, so what we really need here is a "branching" composition, which Category alone doesn't have; by using Control.Arrow as well we get (&&&), letting us rewrite the function as follows:
doBoth :: (Monad m) => Kleisli m a b -> Kleisli m a c -> Kleisli m a (b, c)
doBoth f g = f &&& g
Since we don't care about the result of the first Kleisli arrow, only its side effects, we can discard that half of the tuple in the obvious way:
doBoth :: (Monad m) => Kleisli m a b -> Kleisli m a c -> Kleisli m a c
doBoth f g = f &&& g >>> arr snd
Which gets us back to the generic form. Specializing to your original, the return now becomes simply id:
constKleisli :: (Monad m) => Kleisli m a b -> Kleisli m a a
constKleisli f = f &&& id >>> arr snd
Since regular functions are also Arrows, the definition above works there as well if you generalize the type signature. However, it may be enlightening to expand the definition that results for pure functions and simplify as follows:
\f x -> (f &&& id >>> arr snd) x
\f x -> (snd . (\y -> (f y, id y))) x
\f x -> (\y -> snd (f y, y)) x
\f x -> (\y -> y) x
\f x -> x.
So we're back to flip const, as expected!
In short, your function is some variation on either (>>) or flip const, but in a way that relies on the differences--the former using both a ReaderT environment and the (>>) of the underlying monad, the latter using the implicit side-effects of the specific Arrow and the expectation that Arrow side effects happen in a particular order. Because of these details, there's not likely to be any generalization or simplification available. In some sense, the definition you're using is exactly as simple as it needs to be, which is why the alternate definitions I gave are longer and/or involve some amount of wrapping and unwrapping.
A function like this would be a natural addition to a "monad utility library" of some sort. While Control.Monad provides some combinators along those lines, it's far from exhaustive, and I could neither find nor recall any variation on this function in the standard libraries. I would not be at all surprised to find it in one or more utility libraries on hackage, however.
Having mostly dispensed with the question of existence, I can't really offer much guidance on naming beyond what you can take from the discussion above about related concepts.
As a final aside, note also that your function has no control flow choices based on the result of a monadic expression, since executing the expressions no matter what is the main goal. Having a computational structure independent of the parametric content (i.e., the stuff of type a in Monad m => m a) is usually a sign that you don't actually need a full Monad, and could get by with the more general notion of Applicative.
Hmm, I don't think constM is appropriate here.
map :: (a -> b) -> [a] -> [b]
mapM :: (Monad m) => (a -> m b) -> [a] -> m b
const :: b -> a -> b
So perhaps:
constM :: (Monad m) => b -> m a -> m b
constM b m = m >> return b
The function you are M-ing seems to be:
f :: (a -> b) -> a -> a
Which has no choice but to ignore its first argument. So this function does not have much to say purely.
I see it as a way to, hmm, observe a value with a side effect. observe, effect, sideEffect may be decent names. observe is my favorite, but maybe just because it is catchy, not because it is clear.
I don't really have a clue this exactly allready exists, but you see this a lot in parser-generators only with different names (for example to get the thing inside brackets) - there it's normaly some kind of operator (>>. and .>> in fparsec for example) for this. To really give a name I would maybe call it ignore?
There's interact:
http://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/Prelude.html#v:interact
It's not quite what you're asking for, but it's similar.

Is do-notation specific to "base:GHC.Base.Monad"?

The idea that the standard Monad class is flawed and that it should actually extend Functor or Pointed is floating around.
I'm not necessarily claiming that it is the right thing to do, but suppose that one was trying to do it:
import Prelude hiding (Monad(..))
class Functor m => Monad m where
return :: a -> m a
join :: m (m a) -> m a
join = (>>= id)
(>>=) :: m a -> (a -> m b) -> m b
a >>= t = join (fmap t a)
(>>) :: m a -> m b -> m b
a >> b = a >>= const b
So far so good, but then when trying to use do-notation:
whileM :: Monad m => m Bool -> m ()
whileM iteration = do
done <- iteration
if done
then return ()
else whileM iteration
The compiler complains:
Could not deduce (base:GHC.Base.Monad m) from the context (Monad m)
Question:
Does do-notation work only for base:GHC.Base.Monad? Is there a way to make it work with an alternative Monad class?
Extra context:
What I really want to do is replace base:Control.Arrow.Arrow with a "generalized" Arrow class:
{-# LANGUAGE TypeFamilies #-}
class Category a => Arrow a where
type Pair a :: * -> * -> *
arr :: (b -> c) -> a b c
first :: a b c -> a (Pair a b d) (Pair a c d)
second :: a b c -> a (Pair a d b) (Pair a d c)
(***) :: a b c -> a b' c' -> a (Pair a b b') (Pair a c c')
(&&&) :: a b c -> a b c' -> a b (Pair a c c')
And then use the Arrow's proc-notation with my Arrow class, but that fails like in the example above of do-notation and Monad.
I'll use mostly Either as my pair type constructor and not the (,) type constructor as with the current Arrow class. This might allow to make the code of my toy RTS game (cabal install DefendTheKind) much prettier.
You need to use the NoImplicitPrelude extension for full rebindable syntax, including do and proc. In that case, you get the following, among other stuff:
"Do" notation is translated using whatever functions (>>=), (>>), and fail, are in scope (not the Prelude versions). List comprehensions, mdo (Section 7.3.6, “The recursive do-notation ”), and parallel array comprehensions, are unaffected.
You can also tweak some handling of negation, equality, literal values, and whatnot. Great way to obfuscate code!
p.s. -- If you're going to rebind the do syntax, what sigfpe calls "parameterized monads" are great fun. The same idea is available in category-extras under Control.Monad.Indexed. And yes, they do work with rebindable syntax, despite the wildly different type signatures!

Resources