Use fold with a function that does not have the correct signature - haskell

I have the following function:
brace_it :: a -> b -> (a, b)
brace_it a b = (a, b)
I can do brace_it (brace_it (brace_it 1 2) 3) 4 with it an correctly get (((1,2),3),4).
But I'd like to do foldl brace_it 0 [1,2,3,4]. This is not possible however, as brace_it does not have the correct signature (it needs b -> a -> b). However conceptually it makes sense to fold a list with it, I think, to get the same result as manually applying it to 1,...,4. Is it possible to build something to plug in-between foldl/ foldr and a function that does not actually have the correct type but still would in a way make sense to apply folds to?

The issue here is to do with types, namely that this leads to conflicting type signatures.
Let's take an example. If we take this:
foldl brace_it 0 [1] = (0,1) --(Not correct Haskell)
So, clearly, foldl brace_it 0 :: [Int] -> (Int, Int). However:
foldl brace_it 0 [1,2] = ((0,1),2) --(Not correct Haskell)
So, clearly, foldl brace_it 0 :: [Int] -> ((Int, Int), Int). This is spurious.
So, why isn't this theoretically possible? Because Haskell programs require you to know all types at compile time - you can't make a function that could construct an (Int, Int) or and ((Int, Int), Int) - you need to do some acrobatics with types. For instance, you might construct a type that allows you to pair arbitrarily many things together:
data Pairs a = None | Pair a (Pairs a)
Then your brace_it function would become brace_it a b = Pair a (Pair b None).
However, this is exactly equivalent to a normal Haskell list. So use a list.

Related

(Haskell) Can't understand error : No instance for (Ord a) arising from a use of ‘’

I'm trying to code a function that takes a list of string (containing actions to do on the lists inside the tuple) and a tuple of 2 lists of Int as parameters (testReturn).
The function is supposed to execute an action on the Int lists, checks if the first list in the tuple is in ascending order, and then returns a boolean depending on the result.
This code doesn't compile, and I'm not sure about a few things.
My code :
testReturn :: [[Char]] -> ([a], [b]) -> Bool
testReturn [] b = orderedCheck $ fst b
testReturn (a:as) b
| a == "sa" = testReturn as (saFunc $ fst b, snd b)
orderedCheck :: (Ord a) => [a] -> Bool
orderedCheck [] = True
orderedCheck [x] = True
orderedCheck (x:y:xs) = x <= y && orderedCheck (y:xs)
saFunc :: [a] -> [a]
saFunc x
| length x <= 1 = x
saFunc (x:y:xs) = (y:x:xs)
I know that the orderedCheck and saFunc functions work
I'm concerned about :
[[Char]] : Not sure if writing this is right or not, and not sure if it really means a list of strings.
orderedCheck $ fst b : this is the part where I have a GHC error : "No instance for (Ord a) arising from a use of ‘orderedCheck’ ",I looked around and I can't understand what does it mean.
I heard somewhere else that the use of fst and snd may be a bit edgy (is it?), but I don't know how to do without it.
Could you guys please help me understand my errors in order to fix my code?
Thanks!
[[Char]] : Not sure if writing this is right or not, and not sure if it really means a list of strings.
Yes, it does mean a list of strings - that is, the type [String]. This is the same as [[Char]] because in Haskell String and [Char] are type synonyms, literally different ways of referring to the exact same thing. So putting a pair of square brackets round each (to denote a list of that type) also leads to two equivalent types.
String is usually considered more idiomatic than [Char] when writing Haskell code, but it's not a big deal. (Even if you use String everywhere, the compiler might still use [Char] when reporting errors, so it's important to know about this equivalence.)
orderedCheck $ fst b : this is the part where I have a GHC error : "No instance for (Ord a) arising from a use of ‘orderedCheck’ ",I looked around and I can't understand what does it mean.
It's exactly as #Ismor said in the comments - but as I have a little more space in an answer I'll try to give a slightly longer, clearer explanation.
You are calling orderedCheck with the value fst b. And orderedCheck, by your own (correct) type signature, has type (Ord a) => [a] -> Bool. That means its argument must be a list, whose elements are of a type a which satisfies the constraint Ord a.
But you are using it on fst b in testReturn. b is the second argument to the function, which from its type signature must be of type ([a], [b]). This means fst b must be of type [a] - which is a list, so so far so good. But as just mentioned, that type a must have an instance of Ord. And unfortunately we can't guarantee that, because your type signature - [[Char]] -> ([a], [b]) -> Bool - allows both a and b to be absolutely anything. If this code compiled, that type signature would allow me to call that function as, for example, testReturn ["Example"] ([putStrLn "foo"], []) - but putStrLn "foo" has type IO (), which certainly has no Ord instance. (Unless you provide one in your code, which doesn't sound like a great idea - but even if you did, you could easily find another type with no Ord instance which would lead to the same problem.)
The only way to fix this is to fix the type signature of testReturn - it can't actually accept any type as a, because that type must have an Ord instance. So include that requirement, and you'll be fine:
testReturn :: (Ord a) => [[Char]] -> ([a], [b]) -> Bool
(As #MarkSeemann notes, that's exactly the signature GHC would have inferred for you if you'd left out any type signature. I certainly don't recommend leaving off type signatures for top-level functions, but if you're ever not sure of what the signature should be, this technique of leaving it out and then asking GHCi to infer it for you with :t is almost guaranteed to give you what you want.)
I heard somewhere else that the use of fst and snd may be a bit edgy (is it?), but I don't know how to do without it.
I'm not sure what "edgy" means in this context. It's certainly not "wrong", nor is it dangerous in the same way that head and tail are for lists - those functions will crash (at runtime) when given an empty list, whereas fst and snd will work fine for any 2-tuple (and if given a value that's not a 2-tuple, your code will fail to compile - so there is zero risk of a runtime crash).
However, it's not very elegant compared to pattern-matching, which here is rather like "destructuring" in other languages. I think most Haskellers would write your function like this instead, which is equivalent to your code and hopefully self-explanatory:
testReturn [] (b, _) = orderedCheck b
testReturn (a:as) (b, c)
| a == "sa" = testReturn as (saFunc b, c)
(Note that this function appears incomplete, and will crash if called with a non-empty first argument whose first element is anything other than "sa".)

How to create a base case for a tuple in Haskell?

I have the following function:
encode_single :: (Eq a) => [a] -> (Int, a)
encode_single (x:xs) = (count xs + 1, x)
However, Haskell complained about needing a base case, but I don't know how to do this because of the generic a type.
Thanks!
First of all, what you received is only a warning, not an error. Haskell does not need the base case of the empty list, it just suggests it.
Partial functions are most often an anti-pattern in functional programming so it just points out something that may be wrong. You can avoid the warning in different ways.
The first one is to make your function safe: if it cannot always return a value it's return type shouldn't be (Int, a) but Maybe (Int, a), so you could do:
encode_single :: (Eq a) => [a] -> Maybe (Int, a)
encode_single [] = Nothing
encode_single (x:xs) = Just (count xs + 1, x)
Otherwise you'd have to return a meaningful value for the empty case (just returning undefined isn't better than not defining that case). It might be appropriate to do somethign like:
encode_single [] = (0, undefined)
However this assumes that any code that uses the result of encode_single will not evaluate the second element of the tuple if the first element is zero (note that if the list isn't empty the first element is always positive, so 0 can be used as a sentinel value).
This may or may not be the case. However one thing is sure: this is not compile-time safe so you may receive some run-time errors when calling such a function.
Simply enough: at the type you desire you cannot write a total function of that specification. You need to change the type.
You can either add a default a or indicate partiality using Maybe.
encode_single :: a -> [a] -> (Int, a)
encode_single :: [a] -> Maybe (Int, a)
if you cannot change the type signature, you can piggyback on head i.e.
encode_single :: [a] -> (Int, a)
encode_single a = (length a, head a)
obviously, empty list input is not handled properly.

Understanding Haskell Type Signatures

I am in the process of teaching myself Haskell and I was wondering about the following type signatures:
Prelude> :t ($)
($) :: (a -> b) -> a -> b
Prelude>
How should I interpret (no pun intended) that?
A semi-similar result is also proving to be puzzling:
Prelude> :t map
map :: (a -> b) -> [a] -> [b]
Prelude>
I'll start with map. The map function applies an operation to every element in a list. If I had
add3 :: Int -> Int
add3 x = x + 3
Then I could apply this to a whole list of Ints using map:
> map add3 [1, 2, 3, 4]
[4, 5, 6, 7]
So if you look at the type signature
map :: (a -> b) -> [a] -> [b]
You'll see that the first argument is (a -> b), which is just a function that takes an a and returns a b. The second argument is [a], which is a list of values of type a, and the return type [b], a list of values of type b. So in plain english, the map function applies a function to each element in a list of values, then returns the those values as a list.
This is what makes map a higher order function, it takes a function as an argument and does stuff with it. Another way to look at map is to add some parentheses to the type signature to make it
map :: (a -> b) -> ([a] -> [b])
So you can also think of it as a function that transforms a function from a to b into a function from [a] to [b].
The function ($) has the type
($) :: (a -> b) -> a -> b
And is used like
> add3 $ 1 + 1
5
All it does is take what's to the right, in this case 1 + 1, and passes it to the function on the left, here add3. Why is this important? It has a handy fixity, or operator precedence, that makes it equivalent to
> add3 (1 + 1)
So whatever to the right gets essentially wrapped in parentheses before being passed to the left. This just makes it useful for chaining several functions together:
> add3 $ add3 $ add3 $ add3 $ 1 + 1
is nicer than
> add3 (add3 (add3 (add3 (1 + 1))))
because you don't have to close parentheses.
Well, as said already, $ can be easily understood if you just forget about currying and see it like, say, in C++
template<typename A, typename B>
B dollar(std::function<B(A)> f, A x) {
return f(x);
}
But actually, there is more to this than just applying a function to a value! The apparent similarity between the signatures of $ and map has in fact a pretty deep category-theory meaning: both are examples of the morphism-action of a functor!
In the category Hask that we work with all the time, objects are types. (That is a bit confusionsome, but don't worry). The morphisms are functions.
The most well-known (endo-)functors are those which have an instance of the eponymous type class. But actually, mathematically, a functor is only something that maps both objects to objects and morphisms to morphisms1. map (pun intended, I suppose!) is an example: it takes an object (i.e. type) A and maps it to a type [A]. And, for any two types A and B, it takes a morphism (i.e. function) A -> B, and maps it to the corresponding list-function of type [A] -> [B].
This is just a special case of the functor class signature operation:
fmap :: Functor f => (a->b) -> (f a->f b)
Mathematics doesn't require this fmap to have a name though. And so there can be also the identity functor, which simply assigns any type to itself. And, every morphism to itself:
($) :: (a->b) -> (a->b)
"Identity" exists obviously more generally, you can also map values of any type to themselves.
id :: a -> a
id x = x
And sure enough, a possible implementation is then
($) = id
1Mind, not anything that maps objects and morphisms is a functor... it does need to satisfy the functor laws.
($) is just function application. It gets a function of type a->b, an argument of type a, applies the function and returns a value of type b.
map is a wonderful example for how reading a function type signature helps understanding it. map's first argument is a function that takes a and returns b, and its second argument is a list of type [a].
So map applies a function of type a->b to a list of a values. And the result type is indeed of type [b] - a list of b values!
(a->b)->[a]->[b] can be interpreted as "Accepts a function and a list and returns another list", and also as "Accepts a function of type a->b and returns another function of type [a]->[b]".
When you look at it this way, map "upgrade" f (the term "lift" is often used in this context) to work on lists: if double is a function that doubles an integer, then map double is a function that double every integer in a list.

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]

Creating a list type using functions

For a silly challenge I am trying to implement a list type using as little of the prelude as possible and without using any custom types (the data keyword).
I can construct an modify a list using tuples like so:
import Prelude (Int(..), Num(..), Eq(..))
cons x = (x, ())
prepend x xs = (x, xs)
head (x, _) = x
tail (_, x) = x
at xs n = if n == 0 then xs else at (tail xs) (n-1)
I cannot think of how to write an at (!!) function. Is this even possible in a static language?
If it is possible could you try to nudge me in the right direction without telling me the answer.
There is a standard trick known as Church encoding that makes this easy. Here's a generic example to get you started:
data Foo = A Int Bool | B String
fooValue1 = A 3 False
fooValue2 = B "hello!"
Now, a function that wants to use this piece of data must know what to do with each of the constructors. So, assuming it wants to produce some result of type r, it must at the very least have two functions, one of type Int -> Bool -> r (to handle the A constructor), and the other of type String -> r (to handle the B constructor). In fact, we could write the type that way instead:
type Foo r = (Int -> Bool -> r) -> (String -> r) -> r
You should read the type Foo r here as saying "a function that consumes a Foo and produces an r". The type itself "stores" a Foo inside a closure -- so that it will effectively apply one or the other of its arguments to the value it closed over. Using this idea, we can rewrite fooValue1 and fooValue2:
fooValue1 = \consumeA consumeB -> consumeA 3 False
fooValue2 = \consumeA consumeB -> consumeB "hello!"
Now, let's try applying this trick to real lists (though not using Haskell's fancy syntax sugar).
data List a = Nil | Cons a (List a)
Following the same format as before, consuming a list like this involves either giving a value of type r (in case the constructor was Nil) or telling what to do with an a and another List a, so. At first, this seems problematic, since:
type List a r = (r) -> (a -> List a -> r) -> r
isn't really a good type (it's recursive!). But we can instead demand that we first reduce all the recursive arguments to r first... then we can adjust this type to make something more reasonable.
type List a r = (r) -> (a -> r -> r) -> r
(Again, we should read the type List a r as being "a thing that consumes a list of as and produces an r".)
There's one final trick that's necessary. What we would like to do is to enforce the requirement that the r that our List a r returns is actually constructed from the arguments we pass. That's a little abstract, so let's give an example of a bad value that happens to have type List a r, but which we'd like to rule out.
badList = \consumeNil consumeCons -> False
Now, badList has type List a Bool, but it's not really a function that consumes a list and produces a Bool, since in some sense there's no list being consumed. We can rule this out by demanding that the type work for any r, no matter what the user wants r to be:
type List a = forall r. (r) -> (a -> r -> r) -> r
This enforces the idea that the only way to get an r that gets us off the ground is to use the (user-supplied) consumeNil function. Can you see how to make this same refinement for our original Foo type?
If it is possible could you try and nudge me in the right direction without telling me the answer.
It's possible, in more than one way. But your main problem here is that you've not implemented lists. You've implemented fixed-size vectors whose length is encoded in the type.
Compare the types from adding an element to the head of a list vs. your implementation:
(:) :: a -> [a] -> [a]
prepend :: a -> b -> (a, b)
To construct an equivalent of the built-in list type, you'd need a function like prepend with a type resembling a -> b -> b. And if you want your lists to be parameterized by element type in a straightforward way, you need the type to further resemble a -> f a -> f a.
Is this even possible in a static language?
You're also on to something here, in that the encoding you're using works fine in something like Scheme. Languages with "dynamic" systems can be regarded as having a single static type with implicit conversions and metadata attached, which obviously solves the type mismatch problem in a very extreme way!
I cannot think of how to write an at (!!) function.
Recalling that your "lists" actually encode their length in their type, it should be easy to see why it's difficult to write functions that do anything other than increment/decrement the length. You can actually do this, but it requires elaborate encoding and more advanced type system features. A hint in this direction is that you'll need to use type-level numbers as well. You'd probably enjoy doing this as an exercise as well, but it's much more advanced than encoding lists.
Solution A - nested tuples:
Your lists are really nested tuples - for example, they can hold items of different types, and their type reveals their length.
It is possible to write indexing-like function for nested tuples, but it is ugly, and it won't correspond to Prelude's lists. Something like this:
class List a b where ...
instance List () b where ...
instance List a b => List (b,a) b where ...
Solution B - use data
I recommend using data construct. Tuples are internally something like this:
data (,) a b = Pair a b
so you aren't avoiding data. The division between "custom types" and "primitive types" is rather artificial in Haskell, as opposed to C.
Solution C - use newtype:
If you are fine with newtype but not data:
newtype List a = List (Maybe (a, List a))
Solution D - rank-2-types:
Use rank-2-types:
type List a = forall b. b -> (a -> b -> b) -> b
list :: List Int
list = \n c -> c 1 (c 2 n) -- [1,2]
and write functions for them. I think this is closest to your goal. Google for "Church encoding" if you need more hints.
Let's set aside at, and just think about your first four functions for the moment. You haven't given them type signatures, so let's look at those; they'll make things much clearer. The types are
cons :: a -> (a, ())
prepend :: a -> b -> (a, b)
head :: (a, b) -> a
tail :: (a, b) -> b
Hmmm. Compare these to the types of the corresponding Prelude functions1:
return :: a -> [a]
(:) :: a -> [a] -> [a]
head :: [a] -> a
tail :: [a] -> [a]
The big difference is that, in your code, there's nothing that corresponds to the list type, []. What would such a type be? Well, let's compare, function by function.
cons/return: here, (a,()) corresponds to [a]
prepend/(:): here, both b and (a,b) correspond to [a]
head: here, (a,b) corresponds to [a]
tail: here, (a,b) corresponds to [a]
It's clear, then, that what you're trying to say is that a list is a pair. And prepend indicates that you then expect the tail of the list to be another list. So what would that make the list type? You'd want to write type List a = (a,List a) (although this would leave out (), your empty list, but I'll get to that later), but you can't do this—type synonyms can't be recursive. After all, think about what the type of at/!! would be. In the prelude, you have (!!) :: [a] -> Int -> a. Here, you might try at :: (a,b) -> Int -> a, but this won't work; you have no way to convert a b into an a. So you really ought to have at :: (a,(a,b)) -> Int -> a, but of course this won't work either. You'll never be able to work with the structure of the list (neatly), because you'd need an infinite type. Now, you might argue that your type does stop, because () will finish a list. But then you run into a related problem: now, a length-zero list has type (), a length-one list has type (a,()), a length-two list has type (a,(a,())), etc. This is the problem: there is no single "list type" in your implementation, and so at can't have a well-typed first parameter.
You have hit on something, though; consider the definition of lists:
data List a = []
| a : [a]
Here, [] :: [a], and (:) :: a -> [a] -> [a]. In other words, a list is isomorphic to something which is either a singleton value, or a pair of a value and a list:
newtype List' a = List' (Either () (a,List' a))
You were trying to use the same trick without creating a type, but it's this creation of a new type which allows you to get the recursion. And it's exactly your missing recursion which allows lists to have a single type.
1: On a related note, cons should be called something like singleton, and prepend should be cons, but that's not important right now.
You can implement the datatype List a as a pair (f, n) where f :: Nat -> a and n :: Nat, where n is the length of the list:
type List a = (Int -> a, Int)
Implementing the empty list, the list operations cons, head, tail, and null, and a function convert :: List a -> [a] is left as an easy exercise.
(Disclaimer: stole this from Bird's Introduction to Functional Programming in Haskell.)
Of course, you could represent tuples via functions as well. And then True and False and the natural numbers ...

Resources