generate infinite list of RandomGen - list

I want to apply a function f which needs a RandomGen over a list. I tried to generate me therefore a infinite list of RandomGen as you can see below. (just random values as generated by the function "randoms" isn't sufficient, because the needed range of the value depends on the input for f.)
module Test where
import System.Random (getStdGen, RandomGen, randomR, random)
f :: (RandomGen g, Integral a) => g -> a -> Bool
randomGens :: RandomGen g => g -> [g]
randomGens gen =
let (i, gen') = (random gen) :: (Int, g1)
in gen : (repeatGen gen')
Unfortunately the compiler tells me, that it fails
Test.hs:13:26:
Could not deduce (g1 ~ g)
from the context (RandomGen g)
bound by the type signature for
randomGens :: RandomGen g => g -> (g, g)
at Test.hs:11:14-39
or from (RandomGen g1)
bound by an expression type signature: RandomGen g1 => (Int, g1)
at Test.hs:13:19-55
`g1' is a rigid type variable bound by
an expression type signature: RandomGen g1 => (Int, g1)
at Test.hs:13:19
`g' is a rigid type variable bound by
the type signature for randomGens :: RandomGen g => g -> (g, g)
at Test.hs:11:14
In the first argument of `random', namely `gen'
In the expression: random gen :: RandomGen g => (Int, g)
In a pattern binding:
(i, gen') = random gen :: RandomGen g => (Int, g)
Just skipping in the let-binding the type annotation (Int, g1) doesn't work. He needs to have the result-type for the application of "random"

Disregarding for a while whether generating an infinite list of random generators is really the way to go, there exists a function called split in System.Random that can be used to create a new generator instead of calling random on a dummy type and throwing the generated value away. Using split you can implement randomGens like this:
import Data.List (unfoldr)
import System.Random
randomGens :: RandomGen g => g -> [g]
randomGens = unfoldr (Just . split)
However, you should probably just use randomRs which generates an infinite stream of values in the given range.

Quick answer
You can define the function you want as
randomGens :: (RandomGen g) => g -> [g]
randomGens g = let (g0,g1) = split g in g0 : randomGens g1
Slightly longer answer
The above probably isn't the best way to go about applying a function that requires randomness to a list. I might define a helper function to do that
mapRandom :: (RandomGen g) => (g -> a -> b) -> g -> [a] -> (g, [b])
mapRandom _ g [] = (g, [])
mapRandom f g (a:as) = let (_,g1) = next g
in f g a : mapRandom f g1 as
You can then write
>> g <- newStdGen
>> mapRandom f g [1..5]
([False,False,True,False,True], 1839473859 293842934)
Best answer
The function mapRandom looks very messy. That's because we have to mess around with the fiddly details of manually updating the generator. Fortunately, you don't have to do that! The package Control.Monad.Random gives you nice combinators to almost completely abstract away the idea of generators. Say you currently have
f :: (RandomGen g) => g -> Int -> Bool
f g n = let (x,_) = random g in x < n
I would rewrite that to be
f :: (RandomGen g) => Int -> Rand g Bool
f n = do
x <- getRandom
return (x < n)
and just use mapM to map this function over lists. You can run it with
>> gen <- newStdGen
>> runRand (mapM f [1..10]) gen
([False,True,True,False,True], 1838593757 1838473759)
where the first element of the pair is the result of mapping your random function over the list, and the last element is the current value of the generator. Notice that when defining f you don't have to worry about the generator at all - Haskell takes care of updating the generator and generating new random numbers behind the scenes.

The main problem here - compiler can't understand the equality g1 and g (list are always homomorphic!)
It is need to use ScopedTypeVariables extension, like this:
{-# LANGUAGE ScopedTypeVariables #-}
randomGens :: forall g. RandomGen g => g -> [g]
randomGens gen =
let (i, gen') = (random gen) :: RandomGen g => (Int, g)
in gen : (randomGens gen')
We add forall g to point on scope context of g.
As Chris Taylor mention, this function isn't effective, it is need to calculate random number twice - first time to calculate new g and second time to calculate new random number.
So, much nicer to use MonadRand saving new generator numbers in the state.
UPDATED
For simple cases we could use zipWith
randomsMap :: (RandomGen g, Random a) => g -> (a -> b -> c) -> [b] -> [c]
randomsMap g f xs = zipWith f (randoms g) xs

Related

High order SML questions

So, I am trying to create a high order SML function that takes in a number and returns all the functions and returns its factors. I have done questions where I would take a list of values and return the values that are divisible but I never did anything like take a number and make a list out of it. Following the question:
Define a function factorize = fn: int -> int list that takes an integer and returns all its factors in a list. For example, factorize 12 will return [1, 2, 3, 4, 6, 12].
The second one is a tricky one, I couldn't understand how its done so dropping it here. I would appreciate any help I get on this one.
Define a function cfoldl that behaves exactly same as the standard foldl except that the type of the function argument does not take a 2-tuple’ instead, the input function should use the currying notation as is ’a -> ’b -> ’b. Thus, the type of cfoldl should be fn : (’a -> b -> ’b) -> ’b -> ’a list -> ’b. For example, cfoldl (fn a => fn b => a-b) 1 [1,2,3,4]; will return 3.
I made this for the foldl:
fun cfoldl f b [] = b
| cfoldl f b (x::xs) = cfoldl f (f (x, b)) xs;
Thank you!
factorize = fn: int -> int list that takes an integer and returns all its factors in a list
Here's a recursive function that takes a number and generates a list of numbers from 1 up to that number:
fun upto n =
let fun go i = if i < n
then i :: go (i+1)
else []
in go 1
end
Could you make a function isFactor x y that is true when x is a factor of y?
If you had such a function, could you modify the above function to make use of it?
a function cfoldl that should use the currying notation as is ’a -> ’b -> ’b
fun cfoldl f b [] = b | cfoldl f b (x::xs) = cfoldl f (f (x, b)) xs;
This is exactly foldl.
fun foldl f e [] = e
| foldl f e (x::xr) = foldl f (f(x, e)) xr;
Here, f : ('a * 'b) -> 'b because f is being used as f(x, e), so naturally it will assume a tuple. You can change the inferred type of f by using it differently.
Can you think of a way where f : 'a -> 'b -> 'b?

What is a Lambda Calculus equivalent of the map function in Haskell?

The map function returns a list constructed by applying a function (the first argument) to all items in a list passed as the second argument.
I'm trying to figure out what this would look like if displayed in Lambda Calculus notation. Can anyone give an example?
Since this is tagged haskell I'll write the answer in Haskell, but building everything on functions like you would in lambda calculus. This generally incurs carrying around an extra type parameter r for the continuation-passing style.
Lists are usually can be encoded as deconstruction-matchers: (this is Scott encoding, as the comments inform me)
newtype List r a = List { deconstructList
:: r -- ^ `Nil` case
-> (a -> List r a -> r) -- ^ `Cons` case
-> r -- ^ result
}
Now we want to give this a Functor instance. As with other problems, you can let the compiler guide you:
instance Functor (List r) where
fmap f (List l) = List _
This will prompt
LambdaList.hs:8:26: error:
• Found hole: _ :: r -> (b -> List r b -> r) -> r
Where: ‘b’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List r a -> List r b
at LambdaList.hs:8:3-6
‘r’ is a rigid type variable bound by
the instance declaration
at LambdaList.hs:7:10-25
• In the first argument of ‘List’, namely ‘_’
In the expression: List _
In an equation for ‘fmap’: fmap f (List l) = List _
• Relevant bindings include
l :: r -> (a -> List r a -> r) -> r (bound at LambdaList.hs:8:16)
f :: a -> b (bound at LambdaList.hs:8:8)
fmap :: (a -> b) -> List r a -> List r b
(bound at LambdaList.hs:8:3)
Valid hole fits include
const :: forall a b. a -> b -> a
with const #r #(b -> List r b -> r)
(imported from ‘Prelude’ at LambdaList.hs:1:1
(and originally defined in ‘GHC.Base’))
return :: forall (m :: * -> *) a. Monad m => a -> m a
with return #((->) (b -> List r b -> r)) #r
(imported from ‘Prelude’ at LambdaList.hs:1:1
(and originally defined in ‘GHC.Base’))
pure :: forall (f :: * -> *) a. Applicative f => a -> f a
with pure #((->) (b -> List r b -> r)) #r
(imported from ‘Prelude’ at LambdaList.hs:1:1
(and originally defined in ‘GHC.Base’))
|
8 | fmap f (List l) = List _
| ^
So we're supposed to define a function; well then it's probably a good idea to start with lambda-binding some arguments:
instance Functor (List r) where
fmap f (List l) = List $ \nilCs consCs -> _
LambdaList.hs:8:45: error:
• Found hole: _ :: r
Where: ‘r’ is a rigid type variable bound by
the instance declaration
at LambdaList.hs:7:10-25
• In the expression: _
In the second argument of ‘($)’, namely ‘\ nilCs consCs -> _’
In the expression: List $ \ nilCs consCs -> _
• Relevant bindings include
consCs :: b -> List r b -> r (bound at LambdaList.hs:8:35)
nilCs :: r (bound at LambdaList.hs:8:29)
l :: r -> (a -> List r a -> r) -> r (bound at LambdaList.hs:8:16)
f :: a -> b (bound at LambdaList.hs:8:8)
fmap :: (a -> b) -> List r a -> List r b
(bound at LambdaList.hs:8:3)
Valid hole fits include nilCs :: r (bound at LambdaList.hs:8:29)
The CPS-result should still come from the original list, so we need to use that at this point – with args still TBD, but the nil case won't change so we can right away pass that too:
instance Functor (List r) where
fmap f (List l) = List $ \nilCs consCs -> l nilCs _
LambdaList.hs:8:53: error:
• Found hole: _ :: a -> List r a -> r
Where: ‘a’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List r a -> List r b
at LambdaList.hs:8:3-6
‘r’ is a rigid type variable bound by
the instance declaration
at LambdaList.hs:7:10-25
• In the second argument of ‘l’, namely ‘_’
In the expression: l nilCs _
In the second argument of ‘($)’, namely
‘\ nilCs consCs -> l nilCs _’
• Relevant bindings include
consCs :: b -> List r b -> r (bound at LambdaList.hs:8:35)
nilCs :: r (bound at LambdaList.hs:8:29)
l :: r -> (a -> List r a -> r) -> r (bound at LambdaList.hs:8:16)
f :: a -> b (bound at LambdaList.hs:8:8)
fmap :: (a -> b) -> List r a -> List r b
(bound at LambdaList.hs:8:3)
So it's again function-time, i.e. bind some arguments:
instance Functor (List r) where
fmap f (List l) = List
$ \nilCs consCs -> l nilCs $ \lHead lTail -> _
LambdaList.hs:9:51: error:
• Found hole: _ :: r
Where: ‘r’ is a rigid type variable bound by
the instance declaration
at LambdaList.hs:7:10-25
• In the expression: _
In the second argument of ‘($)’, namely ‘\ lHead lTail -> _’
In the expression: l nilCs $ \ lHead lTail -> _
• Relevant bindings include
lTail :: List r a (bound at LambdaList.hs:9:42)
lHead :: a (bound at LambdaList.hs:9:36)
consCs :: b -> List r b -> r (bound at LambdaList.hs:9:15)
nilCs :: r (bound at LambdaList.hs:9:9)
l :: r -> (a -> List r a -> r) -> r (bound at LambdaList.hs:8:16)
f :: a -> b (bound at LambdaList.hs:8:8)
(Some bindings suppressed; use -fmax-relevant-binds=N or -fno-max-relevant-binds)
Valid hole fits include nilCs :: r (bound at LambdaList.hs:9:9)
At this point we have a lot in scope that could conceivably be used, but a good rule of thumb is that we should probably use all of them at least once, so let's bring in consCs, with two TBD arguments:
instance Functor (List r) where
fmap f (List l) = List
$ \nilCs consCs -> l nilCs $ \lHead lTail -> consCs _ _
LambdaList.hs:9:58: error:
• Found hole: _ :: b
Where: ‘b’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List r a -> List r b
at LambdaList.hs:8:3-6
• In the first argument of ‘consCs’, namely ‘_’
In the expression: consCs _ _
In the second argument of ‘($)’, namely
‘\ lHead lTail -> consCs _ _’
• Relevant bindings include
lTail :: List r a (bound at LambdaList.hs:9:42)
lHead :: a (bound at LambdaList.hs:9:36)
consCs :: b -> List r b -> r (bound at LambdaList.hs:9:15)
nilCs :: r (bound at LambdaList.hs:9:9)
l :: r -> (a -> List r a -> r) -> r (bound at LambdaList.hs:8:16)
f :: a -> b (bound at LambdaList.hs:8:8)
(Some bindings suppressed; use -fmax-relevant-binds=N or -fno-max-relevant-binds)
Ok, there's only one way to obtain a b value: using f, which needs an a as its argument, for which we have exactly one, namely lHead:
instance Functor (List r) where
fmap f (List l) = List
$ \nilCs consCs -> l nilCs
$ \lHead lTail -> consCs (f lHead) _
LambdaList.hs:9:60: error:
• Found hole: _ :: List r b
Where: ‘b’ is a rigid type variable bound by
the type signature for:
fmap :: forall a b. (a -> b) -> List r a -> List r b
at LambdaList.hs:8:3-6
‘r’ is a rigid type variable bound by
the instance declaration
at LambdaList.hs:7:10-25
• In the second argument of ‘consCs’, namely ‘_’
In the expression: consCs _ _
In the second argument of ‘($)’, namely
‘\ lHead lTail -> consCs _ _’
• Relevant bindings include
lTail :: List r a (bound at LambdaList.hs:9:42)
lHead :: a (bound at LambdaList.hs:9:36)
consCs :: b -> List r b -> r (bound at LambdaList.hs:9:15)
nilCs :: r (bound at LambdaList.hs:9:9)
l :: r -> (a -> List r a -> r) -> r (bound at LambdaList.hs:8:16)
f :: a -> b (bound at LambdaList.hs:8:8)
(Some bindings suppressed; use -fmax-relevant-binds=N or -fno-max-relevant-binds)
Here we have a bit of a problem: no List r b is in scope or in the result of any of the bindings. However, what does yield a List r b is the function we're just defining here: fmap f. In standard lambda calculus you can't actually recursively call a definition (you need to use a fixpoint combinator to emulate it), but I'll ignore this here. This is a valid Haskell solution:
instance Functor (List r) where
fmap f (List l) = List
$ \nilCs consCs -> l nilCs
$ \lHead lTail -> consCs (f lHead) (fmap f lTail)
Or written in lambda style (erasing the List newtype constructor),
map = \f l ν ζ ⟼ l ν (\h t ⟼ ζ (f h) (map f t))

Haskell recursively applying function to every element but first?

So I've been doing this program which receives a function f, a number a and a list b and it should return a list [a, f(a,b), f(f(a,b),b, ..] iterating through the list b and using recursion. Do you guys know how I can optimize my code?
calculate :: (a -> b -> a) -> a -> [b] -> [a]
help :: (a -> b -> a) -> a -> [b] -> [a]
help f a (x:xs) = (f a x) : (calculate f (f a x) xs)
help f a [] = []
calculate f a b = a : (help f a b)
calculate f a b = tail . concatMap (replicate 2) . scanl f a $ b.
The replicate bit is probably in error. If so, then simply calculate = scanl.
This translates the code, as the "[a, f(a,b), f(f(a,b),b, ..]" from the text contradicts it (and it contradicts the text itself, which talks of "iterating through the list b").

How to do stateful list operations in haskell

I need an operation which iterates over a list and produces a new list, where the new list elements depend on all elements previously seen. To do this I would like to pass an accumulator/state from iteration to iteration.
Think for example of a list of tuples, where the components of a tuple can be "undefined". An undefined value shall assume the latest value of the same component earlier in the list, if any. So at any stage I will have a state of defined components, which I need to pass to the next iteration.
So with a list of type [l] and an accumulator/state of type a there will be a function of type
f :: a -> l -> (a,l)
i.e it spits out a new list element and a new accumulator.
Is there a function which allows simply applying f to a list? I looked at fold, scan and unfold, but none of them seem to do the trick.
Edit: While the state monad looks promising, I can only see how I would get the final state, but I fail to see how I would get the new list elements.
There are some standard functions you can use to do what you ask.
It sounds very much like you want mapAccum, so you just need to import Data.List and decide which way round you're accumulating. (I suspect you want mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]).)
mapAccumL
import Data.List
data Instruction = NoChange | Reset | MoveBy Int
tell :: Int -> Instruction -> (Int,String) -- toy accumulating function
tell n NoChange = (n,"")
tell n Reset = (0,"Reset to zero")
tell n (MoveBy i) = (n+i,"Add "++show i++" to get "++ show (n+i))
which would give
ghci> mapAccumL tell 10 [MoveBy 5, MoveBy 3, NoChange, Reset, MoveBy 7]
(7,["Add 5 to get 15","Add 3 to get 18","","Reset to zero","Add 7 to get 7"])
scanL
But maybe you don't need to use the full power of mapAccum because sometimes the accumulator is what you want in the new list, so scanl :: (a -> b -> a) -> a -> [b] -> [a] will do the trick
act :: Int -> Instruction -> Int
act n NoChange = n
act n Reset = 0
act n (MoveBy i) = n+i
like this:
ghci> scanl act 10 [MoveBy 5, MoveBy 3, NoChange, Reset, MoveBy 7]
[10,15,18,18,0,7]
Definition for mapAccum
Anyway, here's how mapAccumL and mapAccumR are described in Data.List:
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
mapAccumL _ state [] = (state, [])
mapAccumL f state (x:xs) = (finalstate,y:ys)
where (nextstate, y ) = f state x
(finalstate,ys) = mapAccumL f nextstate xs
The mapAccumL function behaves like a combination of map and foldl; it applies a function to each element of a list, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new list.
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
mapAccumR _ state [] = (state, [])
mapAccumR f state (x:xs) = (finalstate, y:ys)
where (finalstate,y ) = f nextstate x
(nextstate, ys) = mapAccumR f state xs
The mapAccumR function behaves like a combination of map and foldr; it applies a function to each element of a list, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new list.
You want mapM in conjunction with the State monad where your accumulator a will be the State. First, to see why you need State, just take your type signature and flip the order of arguments and results:
import Data.Tuple
f :: a -> l -> (a, l)
uncurry f :: (a, l) -> (a, l)
swap . uncurry f . swap :: (l, a) -> (l, a)
curry (swap . uncurry f . swap) :: l -> a -> (l, a)
Or you could just define f to already have the arguments and results in the right order, whichever you prefer. I will call this swapped function f':
f' :: l -> a -> (l, a)
Now lets add an extra set of parentheses around the right half of the type signature of f':
f' :: l -> (a -> (l, a))
That part grouped in parentheses is a State computation where the state is a and the result is l. So I will go ahead and convert it to the State type using the state function from Control.Monad.Trans.State:
state :: (a -> (l, a)) -> State a l
So the converted f' would look like this:
f'' :: l -> State a l
f'' = state . f'
However, the function you really want in the end is something of type:
final :: [l] -> a -> ([l], a)
-- which is really just:
state . final :: [l] -> State a [l]
So that means that I need some function that takes a l -> State a l and converts it to a [l] -> State a [l]. This is precisely what mapM does, except that mapM works for any Monad, not just State:
mapM :: (Monad m) => (a -> m b) -> ([a] -> m [b])
Notice how if we replace m with State a, and set a and b to l, then it has exactly the right type:
mapM :: (l -> State a l) -> ([l] -> State a [l])
f''' :: [l] -> State a [l]
f''' = mapM f''
Now we can unwrap the State using runState to get back a list-threading function of the appropriate type:
final :: [l] -> a -> ([l], a)
final = runState . f'''
So if we combine all those steps into one we get:
final = runState . mapM (state . f')
... where f' is your function written to swap the order of arguments and results. If you choose not to modify your original function then the solution is slightly more verbose:
final = runState . mapM (state . uncurry (swap . curry f . swap))
Without the specifics of what you are actually trying to achieve, getting to an answer is a bit difficult. But it seems to be that if your f had the type:
f :: (a, [l]) -> l -> (a,l)
Then you could define a function, f':
f' :: (a, [l]) -> l -> (a,l)
f' acc#(y, xs) x = (z, x':xs)
where
(z, x') = f acc
Which can then be used in a fold.
foldr f' (e, []) xs
The new signature of f allows it to have access to all preceding elements in the list, and f' adds the new element from the call to f to the list.

Implementing filter using HoF in Haskell

I'm trying to write a function that takes a predicate f and a list and returns a list consisting of all items that satisfy f with preserved order. The trick is to do this using only higher order functions (HoF), no recursion, no comprehensions, and of course no filter.
You can express filter in terms of foldr:
filter p = foldr (\x xs-> if p x then x:xs else xs) []
I think you can use map this way:
filter' :: (a -> Bool) -> [a] -> [a]
filter' p xs = concat (map (\x -> if (p x) then [x] else []) xs)
You see? Convert the list in a list of lists, where if the element you want doesn't pass p, it turns to an empty list
filter' (> 1) [1 , 2, 3 ] would be: concat [ [], [2], [3]] = [2,3]
In prelude there is concatMap that makes the code simplier :P
the code should look like:
filter' :: (a -> Bool) -> [a] -> [a]
filter' p xs = concatMap (\x -> if (p x) then [x] else []) xs
using foldr, as suggested by sclv, can be done with something like this:
filter'' :: (a -> Bool) -> [a] -> [a]
filter'' p xs = foldr (\x y -> if p x then (x:y) else y) [] xs
You're obviously doing this to learn, so let me show you something cool. First up, to refresh our minds, the type of filter is:
filter :: (a -> Bool) -> [a] -> [a]
The interesting part of this is the last bit [a] -> [a]. It breaks down one list and it builds up a new list.
Recursive patterns are so common in Haskell (and other functional languages) that people have come up with names for some of these patterns. The simplest are the catamorphism and it's dual the anamorphism. I'll show you how this relates to your immediate problem at the end.
Fixed points
Prerequisite knowledge FTW!
What is the type of Nothing? Firing up GHCI, it says Nothing :: Maybe a and I wouldn't disagree. What about Just Nothing? Using GHCI again, it says Just Nothing :: Maybe (Maybe a) which is also perfectly valid, but what about the value that this a Nothing embedded within an arbitrary number, or even an infinite number, of Justs. ie, what is the type of this value:
foo = Just foo
Haskell doesn't actually allow such a definition, but with a slight tweak we can make such a type:
data Fix a = In { out :: a (Fix a) }
just :: Fix Maybe -> Fix Maybe
just = In . Just
nothing :: Fix Maybe
nothing = In Nothing
foo :: Fix Maybe
foo = just foo
Wooh, close enough! Using the same type, we can create arbitrarily nested nothings:
bar :: Fix Maybe
bar = just (just (just (just nothing)))
Aside: Peano arithmetic anyone?
fromInt :: Int -> Fix Maybe
fromInt 0 = nothing
fromInt n = just $ fromInt (n - 1)
toInt :: Fix Maybe -> Int
toInt (In Nothing) = 0
toInt (In (Just x)) = 1 + toInt x
This Fix Maybe type is a bit boring. Here's a type whose fixed-point is a list:
data L a r = Nil | Cons a r
type List a = Fix (L a)
This data type is going to be instrumental in demonstrating some recursion patterns.
Useful Fact: The r in Cons a r is called a recursion site
Catamorphism
A catamorphism is an operation that breaks a structure down. The catamorphism for lists is better known as a fold. Now the type of a catamorphism can be expressed like so:
cata :: (T a -> a) -> Fix T -> a
Which can be written equivalently as:
cata :: (T a -> a) -> (Fix T -> a)
Or in English as:
You give me a function that reduces a data type to a value and I'll give you a function that reduces it's fixed point to a value.
Actually, I lied, the type is really:
cata :: Functor T => (T a -> a) -> Fix T -> a
But the principle is the same. Notice, T is only parameterized over the type of the recursion sites, so the Functor part is really saying "Give me a way of manipulating all the recursion sites".
Then cata can be defined as:
cata f = f . fmap (cata f) . out
This is quite dense, let me elaborate. It's a three step process:
First, We're given a Fix t, which is a difficult type to play with, we can make it easier by applying out (from the definition of Fix) giving us a t (Fix t).
Next we want to convert the t (Fix t) into a t a, which we can do, via wishful thinking, using fmap (cata f); we're assuming we'll be able to construct cata.
Lastly, we have a t a and we want an a, so we just use f.
Earlier I said that the catamorphism for a list is called fold, but cata doesn't look much like a fold at the moment. Let's define a fold function in terms of cata.
Recapping, the list type is:
data L a r = Nil | Cons a r
type List a = Fix (L a)
This needs to be a functor to be useful, which is straight forward:
instance Functor (L a) where
fmap _ Nil = Nil
fmap f (Cons a r) = Cons a (f r)
So specializing cata we get:
cata :: (L x a -> a) -> List x -> a
We're practically there:
construct :: (a -> b -> b) -> b -> L a b -> b
construct _ x (In Nil) = x
construct f _ (In (Cons e n)) = f e n
fold :: (a -> b -> b) -> b -> List a -> b
fold f m = cata (construct f m)
OK, catamorphisms break data structures down one layer at a time.
Anamorphisms
Anamorphisms over lists are unfolds. Unfolds are less commonly known than there fold duals, they have a type like:
unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
As you can see anamorphisms build up data structures. Here's the more general type:
ana :: Functor a => (a -> t a) -> a -> Fix t
This should immediately look quite familiar. The definition is also reminiscent of the catamorphism.
ana f = In . fmap (ana f) . f
It's just the same thing reversed. Constructing unfold from ana is even simpler than constructing fold from cata. Notice the structural similarity between Maybe (a, b) and L a b.
convert :: Maybe (a, b) -> L a b
convert Nothing = Nil
convert (Just (a, b)) = Cons a b
unfold :: (b -> Maybe (a, b)) -> b -> List a
unfold f = ana (convert . f)
Putting theory into practice
filter is an interesting function in that it can be constructed from a catamorphism or from an anamorphism. The other answers to this question (to date) have also used catamorphisms, but I'll define it both ways:
filter p = foldr (\x xs -> if p x then x:xs else xs) []
filter p =
unfoldr (f p)
where
f _ [] =
Nothing
f p (x:xs) =
if p x then
Just (x, xs)
else
f p xs
Yes, yes, I know I used a recursive definition in the unfold version, but forgive me, I taught you lots of theory and anyway filter isn't recursive.
I'd suggest you look at foldr.
Well, are ifs and empty list allowed?
filter = (\f -> (>>= (\x -> if (f x) then return x else [])))
For a list of Integers
filter2::(Int->Bool)->[Int]->[Int]
filter2 f []=[]
filter2 f (hd:tl) = if f hd then hd:filter2 f tl
else filter2 f tl
I couldn't resist answering this question in another way, this time with no recursion at all.
-- This is a type hack to allow the y combinator to be represented
newtype Mu a = Roll { unroll :: Mu a -> a }
-- This is the y combinator
fix f = (\x -> f ((unroll x) x))(Roll (\x -> f ((unroll x) x)))
filter :: (a -> Bool) -> [a] -> [a]
filter =
fix filter'
where
-- This is essentially a recursive definition of filter
-- except instead of calling itself, it calls f, a function that's passed in
filter' _ _ [] = []
filter' f p (x:xs) =
if p x then
(x:f p xs)
else
f p xs