Mapping over Either's Left - haskell

Somewhere in my app I receive an Either ParserError MyParseResult from Parsec. Downstream this result gets some other parsing done over using other libs. During that second phase of parsing there also may occur some kind of error which I would like to pass as a Left String, but for that I need to convert the result from Parsec to String too. To achieve that I need a function which will allow me to map over a Left with a show function.
The mapping function I'm thinking of looks something like this:
mapLeft :: (a -> b) -> Either a c -> Either b c
mapLeft f (Left x) = Left $ f x
mapLeft _ x = x
But I was quite surprised not to find anything matching on hackage db. So now I'm having doubts whether I'm using a correct approach to my problem.
Why isn't there such a function in standard lib? What is wrong with my approach?

We have such a function in the standard libraries,
Control.Arrow.left :: a b c -> a (Either b d) (Either c d)
is the generalisation to arbitrary Arrows. Substitute (->) for a and apply it infix, to get the specialisation
left :: (b -> c) -> Either b d -> Either c d
There is nothing wrong with your approach in principle, it's a sensible way to handle the situation.

Another option is to use Bifunctor instance of Either. Then you have
first :: (a -> b) -> Either a c -> Either b c
(Also Bifunctor can be used to traverse over the first part of (a,b).)

This can be done easily with lens:
import Control.Lens
over _Left (+1) $ Left 10 => Left 11
over _Left (+1) $ Right 10 => Right 10
over _Right (+1) $ Right 10 => Right 11

Another simple option is mapLeft in Data.Either.Combinators:
mapLeft :: (a -> c) -> Either a b -> Either c b

Related

"Either Fmap" which Continues until a Right Result has been Reached

If Either fmap is
(a -> b) -> p a a -> p a b
which stops mapping once a Left is returned.
What's name or type signature for a function which doesn't stop until it gets a Right result.
I suspect a bifunctor, but I really need it spelled out - don't quite get the subtlety of the logic of these things yet.
Perhaps some sort of fold fits also...
Data.Bifunctor.first :: (a -> b) -> Either a c -> Either b c
In ghci:
Data.Bifunctor> first (+1) (Left 0)
Left 1
Data.Bifunctor> first (+1) (Right 0)
Right 0

Haskell - Maybe Either

-- | Convert a 'Maybe a' to an equivalent 'Either () a'. Should be inverse
-- to 'eitherUnitToMaybe'.
maybeToEitherUnit :: Maybe a -> Either () a
maybeToEitherUnit a = error "Not yet implemented: maybeToEitherUnit"
-- | Convert a 'Either () a' to an equivalent 'Maybe a'. Should be inverse
-- to 'maybeToEitherUnit'.
eitherUnitToMaybe :: Either () a -> Maybe a
eitherUnitToMaybe = error "Not yet implemented: eitherUnitToMaybe"
-- | Convert a pair of a 'Bool' and an 'a' to 'Either a a'. Should be inverse
-- to 'eitherToPairWithBool'.
pairWithBoolToEither :: (Bool,a) -> Either a a
pairWithBoolToEither = undefined -- What should I do here?
-- | Convert an 'Either a a' to a pair of a 'Bool' and an 'a'. Should be inverse
-- to 'pairWithBoolToEither'.
eitherToPairWithBool :: Either a a -> (Bool,a)
eitherToPairWithBool = undefined -- What should I do here?
-- | Convert a function from 'Bool' to 'a' to a pair of 'a's. Should be inverse
-- to 'pairToFunctionFromBool'.
functionFromBoolToPair :: (Bool -> a) -> (a,a)
functionFromBoolToPair = error "Not yet implemented: functionFromBoolToPair"
-- | Convert a pair of 'a's to a function from 'Bool' to 'a'. Should be inverse
-- to 'functionFromBoolToPair'.
pairToFunctionFromBool :: (a,a) -> (Bool -> a)
pairToFunctionFromBool = error "Not yet implemented: pairToFunctionFromBool"
I don't really know what to do. I know what maybe is, but I think I have a problem with either, because Either a a makes no sense in my mind. Either a b would be okay. This is either a or b but Either a a is a?!
I don't have any idea in general how to write these functions.
Given that I think this is homework, I'll not answer, but give important hints:
If you look for the definitions on hoogle (http://www.haskell.org/hoogle/)
you find
data Bool = True | False
data Either a b = Left a | Right b
This means that Bool can only be True or False, but that Either a b can be Left a or Right b.
which means your functions should look like
pairWithBoolToEither :: (Bool,a) -> Either a a
pairWithBoolToEither (True,a) = ....
pairWithBoolToEither (False,a) = ....
and
eitherToPairWithBool :: Either a a -> (Bool,a)
eitherToPairWithBool (Left a) = ....
eitherToPairWithBool (Right a) = ....
Comparing with Maybe
Maybe a is given by
data Maybe a = Just a | Nothing
so something of type Maybe Int could be Just 7 or Nothing.
Similarly, something of type Either Int Char could be Left 5 or Right 'c'.
Something of type Either Int Int could be Left 7 or Right 4.
So something with type Either Int Char is either an Int or a Char, but something of type Either Int Int is either an Int or an Int. You don't get to choose anything other than Int, but you'll know whether it was a Left or a Right.
Why you've been asked this/thinking behind it
If you have something of type Either a a, then the data (eg 5 in Left 5) is always of type a, and you've just tagged it with Left or Right. If you have something of type (Bool,a) the a-data (eg 5 in (True,5)) is always the same type, and you've paired it with False or True.
The maths word for two things which perhaps look different but actually have the same content is "isomorphic". Your instructor has asked you to write a pair of functions which show this isomorphism. Your answer will go down better if pairWithBoolToEither . eitherToPairWithBool and eitherToPairWithBool . pairWithBoolToEither do what id does, i.e. don't change anything. In fact, I've just spotted the comments in your question, where it says they should be inverses. In your write-up, you should show this by doing tests in ghci like
ghci> eitherToPairWithBool . pairWithBoolToEither $ (True,'h')
(True,'h')
and the other way round.
(In case you haven't seen it, $ is defined by f $ x = f x but $ has really low precedence (infixr 0 $), so f . g $ x is (f . g) $ x which is just (f . g) x and . is function composition, so (f.g) x = f (g x). That was a lot of explanation to save one pair of brackets!)
Functions that take or return functions
This can be a bit mind blowing at first when you're not used to it.
functionFromBoolToPair :: (Bool -> a) -> (a,a)
The only thing you can pattern match a function with is just a variable like f, so we'll need to do something like
functionFromBoolToPair f = ...
but what can we do with that f? Well, the easiest thing to do with a function you're given is to apply it to a value. What value(s) can we use f on? Well f :: (Bool -> a) so it takes a Bool and gives you an a, so we can either do f True or f False, and they'll give us two (probably different) values of type a. Now that's handy, because we needed to a values, didn't we?
Next have a look at
pairToFunctionFromBool :: (a,a) -> (Bool -> a)
The pattern match we can do for the type (a,a) is something like (x,y) so we'll need
pairToFunctionFromBool (x,y) = ....
but how can we return a function (Bool -> a) on the right hand side?
There are two ways I think you'll find easiest. One is to notice that since -> is right associative anyway, the type (a,a) -> (Bool -> a) is the same as (a,a) -> Bool -> a so we can actually move the arguments for the function we want to return to before the = sign, like this:
pairToFunctionFromBool (x,y) True = ....
pairToFunctionFromBool (x,y) False = ....
Another way, which feels perhaps a little easier, would to make a let or where clause to define a function called something like f, where f :: Bool -> a< a bit like:
pairToFunctionFromBool (x,y) = f where
f True = ....
f False = ....
Have fun. Mess around.
Perhaps it's useful to note that Either a b is also called the coproduct, or sum, of the types a and b. Indeed it is now common to use
type (+) = Either
You can then write Either a b as a + b.
eitherToPairWithBool :: (a+a) -> (Bool,a)
Now common sense would dictate that we rewrite a + a as something like 2 ⋅ a. Believe it or not, that is exactly the meaning of the tuple type you're transforming to!
To explain: algebraic data types can roughly be seen as "counting1 the number of possible constructions". So
data Bool = True | False
has two constructors. So sort of (this is not valid Haskell!)
type 2 = Bool
Tuples allow all the combinations of constructors from each argument. So for instance in (Bool, Bool), we have the values
(False,False)
(False,True )
(True, False)
(True, True )
You've guessed it: tuples are also called products. So the type (Bool, a) is basically 2 ⋅ a: for every value x :: a, we can create both the (False, x) tuple and the (True, x) tuple, alltogether twice as many as there are x values.
Much the same thing for Either a a: we always have both Left x and Right x as a possible value.
All your functions with "arithmetic types":
type OnePlus = Maybe
maybeToEitherUnit :: OnePlus a -> () + a
eitherUnitToMaybe :: () + a -> OnePlus a
pairWithBoolToEither :: 2 ⋅ a -> a + a
eitherToPairWithBool :: a + a -> 2 ⋅ a
functionFromBoolToPair :: a² -> a⋅a
pairToFunctionFromBool :: a⋅a -> a²
1For pretty much any interesting type there are actually infinitely many possible values, still this kind of naïve arithmetic gets you surprisingly far.
Either a a makes no sense in my mind.
Yes it does. Try to figure out the difference between type a and Either a a. Either is a disjoint union. Once you understand the difference between a and Either a a, your homework should be easy in conjunction with AndrewC's answer.
Note that Either a b means quite literally that a value of such a type can be either an a, or an a. It sounds like you have actually grasped this concept, but the piece you're missing is that the Either type differentiates between values constructed with Left and those constructed with Right.
For the first part, the idea is that Maybe is either Just a thing or Nothing -- Nothing corresponds to () because both are "in essence" data types with only one possible value.
The idea behind converting (Bool, a) pairs to Either a a pairs might seem a little trickier, but just think about the correspondence between True and False and Left and Right.
As for converting functions of type (Bool -> a) to (a, a) pairs, here's a hint: Consider the fact that Bool can only have two types, and write down what that initial function argument might look like.
Hopefully those hints help you to get started.

Continual signal switching in arrowized FRP

I've been playing around with Arrowized FRP libraries in Haskell (Yampa, in particular), but I can't quite figure out how to do "continual" switching. By that I mean that a signal passes through a signal function (sf below) which is itself a signal (as drawn in the upper half of the image).
Since I don't know ahead of time what the parameters of the switch will be, I can't see how to reduce this to a simpler, binary switch.
How then should one do it, if it's possible at all? I'd prefer Yampa code, but am happy with any Arrowized FRP code. I haven't tried other libraries (e.g. Sodium or Reactive Banana) to know whether I'd have the same confusion in those cases, but I'm curious about them too.
EDIT
To make this clearer an more concrete, I've labeled the image; possible types for the labels are:
in: Either Int (Int -> Int)
1: (Int -> Int) -> (Either Int (Int -> Int) -> (Int -> Int))
sf could be:
(Either Int (Int -> Int) -> (Int -> Int)) -> Either Int (Int -> Int) -> (Int -> Int)
(e.g., app). But that's only if the part labeled with a question mark represents an input into sf. If it represents a more complex switch, the type would be
(Either Int (Int -> Int) -> (Int -> Int)) -> (Int -> Int)
instead.
2 and out are pretty much irrelevant.
The idea is that I want the circuit to behave as if sf were app, with the signal labeled f representing the function that is applied to in, and with in itself being the source of both the arguments to fs, and the fs themselves. I want to get a circuit that can process inputs and change it's behavior (the signal functions that constitute it) dynamically based on those inputs.
On the one hand, it seems to me like sf can't in fact be app, since in this case we don't have an ArrowApply; but on the other hand I imagine that same behavior can be achieved with some form of sophisticated switching.
You're asking to have an arrow that's output by an arrow to be used as an arrow.
That's what app from ArrowApply is for.
If you want to use that in some looped construct like your diagram, you might need ArrowLoop, but actually the do notation allows you to be fairly flexible with all this stuff anyway.
There's quite a lengthy explanation of app in this answer but I'll copy the main relevant bit:
What does app exactly do? it's type doesn't even have an (->) It lets you use the output of an arrow as an arrow. Let's look at the type.
app :: ArrowApply m => m (m b c, b) c
I prefer to use m to a because m feels more like a computation and a feels like a value. Some people like to use a type operator (infix type constructor), so you get
app :: ArrowApply (~>) => (b ~> c, b) ~> c
We think of b ~> c as an arrow, and we think of an arrow as a thing which takes bs, does something and gives cs. So this means app is an arrow that takes an arrow and a value, and can produce the value that the first arrow would have produced on that input.
It doesn't have -> in the type signature because when programming with arrows, we can turn any function into an arrow using arr :: Arrow (~>) => (b -> c) -> b ~> c, but you can't turn every arrow into a function, thus (b ~> c, b) ~> c is usable where (b ~> c, b) -> c or (b -> c, b) ~> c would not be.
I still think it's a case of ArrowLoop!
You have
in :: Arr () A
sf :: Arr (A -> B, A) B
one :: Arr B (A -> B)
two :: Arr B C
sf is just arr (uncurry ($)).
Then you have sf >>> (one &&& two) :: Arr (A -> B, A) (A -> B, C) and you can use loop (or rather loop with arr swap judiciously placed) to get an Arr A C.
Will that give you what you want?

How do I extract information from inner parameters in Haskell?

In most of programming languages that support mutable variables, one can easily implement something like this Java example:
interface Accepter<T> {
void accept(T t);
}
<T> T getFromDoubleAccepter(Accepter<Accepter<T>> acc){
final List<T> l = new ArrayList<T>();
acc.accept(new Accepter<T>(){
#Override
public void accept(T t) {
l.add(t);
}
});
return l.get(0); //Not being called? Exception!
}
Just for those do not understand Java, the above code receives something can can be provided a function that takes one parameter, and it supposed to grape this parameter as the final result.
This is not like callCC: there is no control flow alternation. Only the inner function's parameter is concerned.
I think the equivalent type signature in Haskell should be
getFromDoubleAccepter :: (forall b. (a -> b) -> b) -> a
So, if someone can gives you a function (a -> b) -> b for a type of your choice, he MUST already have an a in hand. So your job is to give them a "callback", and than keep whatever they sends you in mind, once they returned to you, return that value to your caller.
But I have no idea how to implement this. There are several possible solutions I can think of. Although I don't know how each of them would work, I can rate and order them by prospected difficulties:
Cont or ContT monad. This I consider to be easiest.
RWS monad or similar.
Any other monads. Pure monads like Maybe I consider harder.
Use only standard pure functional features like lazy evaluation, pattern-matching, the fixed point contaminator, etc. This I consider the hardest (or even impossible).
I would like to see answers using any of the above techniques (and prefer harder ways).
Note: There should not be any modification of the type signature, and the solution should do the same thing that the Java code does.
UPDATE
Once I seen somebody commented out getFromDoubleAccepter f = f id I realize that I have made something wrong. Basically I use forall just to make the game easier but it looks like this twist makes it too easy. Actually, the above type signature forces the caller to pass back whatever we gave them, so if we choose a as b then that implementation gives the same expected result, but it is just... not expected.
Actually what came up to my mind is a type signature like:
getFromDoubleAccepter :: ((a -> ()) -> ()) -> a
And this time it is harder.
Another comment writer asks for reasoning. Let's look at a similar function
getFunctionFromAccepter :: (((a -> b) -> b) -> b) -> a -> b
This one have an naive solution:
getFunctionFromAccepter f = \a -> f $ \x -> x a
But in the following test code it fails on the third:
exeMain = do
print $ getFunctionFromAccepter (\f -> f (\x -> 10)) "Example 1" -- 10
print $ getFunctionFromAccepter (\f -> 20) "Example 2" -- 20
print $ getFunctionFromAccepter (\f -> 10 + f (\x -> 30)) "Example 3" --40, should be 30
In the failing case, we pass a function that returns 30, and we expect to get that function back. However the final result is in turn 40, so it fails. Are there any way to implement doing Just that thing I wanted?
If this can be done in Haskell there are a lot of interesting sequences. For example, tuples (or other "algebraic" types) can be defined as functions as well, since we can say something like type (a,b) = (a->b->())->() and implement fst and snd in term of this. And this, is the way I used in a couple of other languages that do not have native "tuple" support but features "closure".
The type of accept is void accept(T) so the equivalent Haskell type is t -> IO () (since every function in Java is essentially IO). Thus getFromDoubleAccepted can be directly translated as
import Data.IORef
type Accepter t = t -> IO ()
getFromDoubleAccepter :: Accepter (Accepter a) -> IO a
getFromDoubleAccepter acc = do
l <- newIORef $ error "Not called"
acc $ writeIORef l
readIORef l
If you want an idiomatic, non-IO solution in Haskell, you need to be more specific about what your actual end goal is besides trying to imitate some Java-pattern.
EDIT: regarding the update
getFromDoubleAccepter :: ((a -> ()) -> ()) -> a
I'm sorry, but this signature is in no way equal to the Java version. What you are saying is that for any a, given a function that takes a function that takes an a but doesn't return anything or do any kind of side effects, you want to somehow conjure up a value of type a. The only implementation that satisfies the given signature is essentially:
getFromDoubleAccepter :: ((a -> ()) -> ()) -> a
getFromDoubleAccepter f = getFromDoubleAccepter f
First, I'll transliterate as much as I can. I'm going to lift these computations to a monad because accept returns void (read () in Haskell-land), which is useless unless there is some effect.
type Accepter m t = t -> m ()
getFromDoubleAccepter :: (MonadSomething m) => Accepter m (Accepter m t) -> m t
getFromDoubleAccepter acc = do
l <- {- new mutable list -}
acc $ \t -> add l t
return (head l)
Of course, we can't make a mutable list like that, so we'll have to use some intuitive sparks here. When an action just adds an element to some accumulator, I think of the Writer monad. So maybe that line should be:
acc $ \t -> tell [t]
Since you are simply returning the head of the list at the end, which doesn't have any effects, I think the signature should become:
getFromDoubleAccepter :: Accepter M (Accepter M t) -> t
where M is an appropriate monad. It needs to be able to write [t]s, so that gives us:
type M t = Writer [t]
getFromDoubleAccepter :: Accepter (M t) (Accepter (M t) t) -> t
And now the type of this function informs us how to write the rest of it:
getFromDoubleAccepter acc =
head . execWriter . acc $ \t -> tell [t]
We can check that it does something...
ghci> getFromDoubleAccepter $ \acc -> acc 42
42
So that seems right, I guess. I'm still a bit unclear on what this code is supposed to mean.
The explicit M t in the type signature is a bit aesthetically bothersome to me. If I knew what problem I was solving I would look at that carefully. If you mean that the argument can be a sequence of commands, but otherwise has no computational features available, then you could specialize the type signature to:
getFromDoubleAccepter :: (forall m. (Monad m) => Accepter m (Accepter m t)) -> t
which still works with our example. Of course, this is all a bit silly. Consider
forall m. (Monad m) => Accepter m (Accepter m t))
= forall m. (Monad m) => (t -> m ()) -> m ()
The only thing a function with this type can do is call its argument with various ts in order and then return (). The information in such a function is completely characterized[1] by those ts, so we could just as easily have used
getFromDoubleAccepter :: [t] -> t
getFromDoubleAccepter = head
[1] As long as I'm going on about nothing, I might as well say that that is not quite accurate in the face of infinity. The computation
crazy :: Integer -> Accepter m (Accepter m Integer)
crazy n acc = crazy (n+1) >> acc n
can be used to form the infinite sequence
... >> acc 3 >> acc 2 >> acc 1 >> acc 0
which has no first element. If we tried to interpret this as a list, we would get an infinite loop when trying to find the first element. However this computation has more information than an infinite loop -- if instead of a list, we used the Last monoid to interpret it, we would be able to extract 0 off the end. So really
forall m. (Monad m) => Accepter m (Accepter m t)
is isomorphic to something slightly more general than a list; specifically a free monoid.
Thanks to the above answers, I finally concluded that in Haskell we can do some different things than other languages.
Actually, the motivation of this post is to translate the famous "single axiom classical logic reduction system". I have implemented this in some other languages. It should be no problem to implement the
Axiom: (a|(b|c)) | ((d|(d|d)) | ((e|b) | ((a|e) | (a|e))))
However, since the reduction rule looks like
Rule: a|(b|c), a |-- c
It is necessary to extract the inner parameter as the final result. In other languages, this is done by using side-effects like mutable slots. However, in Haskell we do not have mutable slots and involving IO will be ugly so I keep looking for solutions.
In the first glance (as show in my question), the getFromDoubleAccepter f = f id seems nonsense, but I realise that it actually work in this case! For example:
rule :: (forall r.a -> (b -> c -> r) -> r) -> a -> c
rule abc a = abc a $ flip const
The trick is still the same: since the existential qualification hides r from the caller, and it is up to the callee to pick up a type for it, we can specify c to be r, so we simply apply the given function to get the result. On the other hand, the given function has to use our input to produce the final answer, so it effectively limiting the implementation to what we exactally want!
Putting them together, let's see what we can do with it:
newtype I r a b = I { runI :: a -> b -> r }
rule :: (forall r. I r a (I r b c)) -> a -> c
rule (I abc) a = abc a (I (\b c -> c))
axiom :: I r0 (I r1 a (I r2 b c))
(I r0 (I r3 d (I r3 d d))
(I r4 (I r2 e b) (I r4 (I r1 a e) (I r1 a e))))
axiom = let
a1 (I eb) e = I $ \b c -> eb e b
a2 = I $ \d (I dd) -> dd d d
a3 (I abc) eb = I $ \a e -> abc a (a1 eb e)
a4 abc = I $ \eb aeae -> runI a2 (a3 abc eb) aeae
in I $ \abc (I dddebaeae) -> dddebaeae a2 (a4 abc)
Here I use a naming convention to trace the type signatures: a variable name is combinded by the "effective" type varialbes (means it is not result type - all r* type variable).
I wouldn't repeat the prove represented in the sited essay, but I want to show something. In the above definition of axiom we use some let bindings variables to construct the result. Not surprisingly, those variables themselves can be extracted by using rule and axiom. let's see how:
--Equal to a4
t4 :: I r0 a (I r1 b c) -> I r2 (I r1 d b) (I r2 (I r0 a d) (I r0 a d))
t4 abc = rule axiom abc
--Equal to a3
t3 :: I r0 a (I r1 b c) -> I r1 d b -> I r0 a d
t3 abc eb = rule (t4 abc) eb
--Equal to a2
t2 :: I r a (I r a a)
t2 = rule (t3 axiom (t3 (t4 axiom) axiom)) axiom
--Equal to a1
t1 :: I r a b -> a -> I r b c
t1 ab a = rule (t3 t2 (t3 (t3 t2 t2) ab)) a
One thing left to be proved is that we can use t1 to t4 only to prove all tautologies. I feel it is the case but have not yet proved it.
Compare to other languages, the Haskell salutation seems more effective and expressive.

What are the alternatives to prelude's iterate if the "output" values are not the same as those being iterated on?

I have come across a pattern where, I start with a seed value x and at each step generate a new seed value and a value to be output. My desired final result is a list of the output values. This can be represented by the following function:
my_iter :: (a -> (a, b)) -> a -> [b]
my_iter f x = y : my_iter f x'
where (x',y) = f x
And a contrived example of using this would be generating the Fibonacci numbers:
fibs:: [Integer]
fibs = my_iter (\(a,b) -> let c = a+b in ((b, c), c)) (0,1)
-- [1, 2, 3, 5, 8...
My problem is that I have this feeling that there is very likely a more idiomatic way to do this kind of stuff. What are the idiomatic alternatives to my function?
The only ones I can think of right now involve iterate from the Prelude, but they have some shortcomings.
One way is to iterate first and map after
my_iter f x = map f2 $ iterate f1 x
where f1 = fst . f
f2 = snd . f
However, this can look ugly if there is no natural way to split f into the separate f1 and f2 functions. (In the contrived Fibonacci case this is easy to do, but there are some situations where the generated value is not an "independent" function of the seed so its not so simple to split things)
The other way is to tuple the "output" values together with the seeds, and use a separate step to separate them (kind of like the "Schwartzian transform" for sorting things):
my_iter f x = map snd . tail $ iterate (f.fst) (x, undefined)
But this seems wierd, since we have to remember to ignore the generated values in order to get to the seed (the (f.fst) bit) and add we need an "undefined" value for the first, dummy generated value.
As already noted, the function you want is unfoldr. As the name suggests, it's the opposite of foldr, but it might be instructive to see exactly why that's true. Here's the type of foldr:
(a -> b -> b) -> b -> [a] -> b
The first two arguments are ways of obtaining something of type b, and correspond to the two data constructors for lists:
[] :: [a]
(:) :: a -> [a] -> [a]
...where each occurrence of [a] is replaced by b. Noting that the [] case produces a b with no input, we can consolidate the two as a function taking Maybe (a, b) as input.
(Maybe (a, b) -> b) -> ([a] -> b)
The extra parentheses show that this is essentially a function that turns one kind of transformation into another.
Now, simply reverse the direction of both transformations:
(b -> Maybe (a, b)) -> (b -> [a])
The result is exactly the type of unfoldr.
The underlying idea this demonstrates can be applied similarly to other recursive data types, as well.
The standard function you're looking for is called unfoldr.
Hoogle is a very useful tool in this case, since it doesn't only support searching functions by name, but also by type.
In your case, you came up with the desired type (a -> (a, b)) -> a -> [b]. Entering it yields no results - hmm.
Well, maybe there's a standard function with a slightly different syntax. For example, the standard function might have its arguments flipped; let's look for something with (a -> (a, b)) in its type signature somewhere. This time we're lucky as there are plenty of results, but all of them are in exotic packages and none of them seems very helpful.
Maybe the second part of your function is a better match, you want to generate a list out of some initial element after all - so type in a -> [b] and hit search. First result: unfoldr - bingo!
Another possibility is iterateM in State monad:
iterateM :: Monad m => m a -> m [a]
iterateM = sequence . repeat
It is not in standard library but it's easy to build.
So your my_iter is
evalState . sequence . repeat :: State s a -> s -> [a]

Resources