Repetitions as an Hylomorphism - haskell

So I've been trying to convert this Haskell function thats checks if a list doesn't have any repetitions into an Hylomorphism, but there's something odd about it.
valid :: [a] -> Bool
valid [] = True
valid (h:t) = if (not (elem h t)) then valid t else False
I'll be glad if anyone can help! Thx

Well a hylomoprhism is a function h : A → C that can be defined in an anamoprhism (g and p) and catamorphism (c and ⊕) part.
The anamorphism part consists of a function g : A → B × A that "unfolds" the object into smaller parts, and p : A → Bool a predicate that determines if we are done unfolding.
The catamorphism part consists of a value c ∈ C and an operator ⊕ : B × C → C.
(this text is a slightly modified version of the Wikipedia page)
In your case the unfolding means that we unfold a list in some value (of type B, and a recursive part, that is here the tail of the list.
The predicate p can be derived out of your definition: if the list is empty, then we have terminated. It is clear that in that case we return True, so that means c is True.
So now what would the B part be? Well if we look at your function we need access to both the head and the tail of the list, so B can be seen as a 2-tuple containing the head (as first element), and a tail (as second element).
So now the remaining question is what ⊕ does? It takes as input a 2-tuple of type E×[E] (pseudo-Haskell notation), and a boolean (type C which is a Bool). As we can see, it checks if the head is en element of the tail. If that is the case, it returns False, and ignores the recursive part, otherwise it returns the recursive part.
So we can write this in Haskell like:
-- types
type A e = [e]
type B e = (e, [e])
type C = Bool
-- functions
p :: A e -> Bool
p [] = True
p (_:_) = False
g :: A e -> (B e, A e)
g (h:t) = ((h, t), t)
c :: C
c = True
plus :: Eq e => B e -> C -> C
plus (h, t) r | elem h t = False
| otherwise = r
hylo :: Eq e => A e -> C
hylo a | p a = c
| otherwise = plus b (hylo a')
where (b, a') = g a
hylo is thus a straighforward implementation based on the definition where we thus take the functions p, c, plus and g as "building blocks".

Related

Understanding Haskell Type Signature

I have to convert a Haskell type signature into a term.
The type signature is :
f :: (a -> b -> c) -> (d -> b) -> (d -> a) -> d -> c
The correct resulting term is :
f g h j x = g (j x) (h x)
and here lies my problem as I understand it g is a function which returns a function which returns c and c is function which returns a function d which returns b and b is a function which returns itself which then returns itself again which then returns c.
Correct me if i am wrong.
What I don't get is why is g taking (j x) as first argument and (h x) as second argument. Shouldn't it be the other way around? Haskell is right associative and h is the secound parameter given to the function f and not j.
g :: a -> b -> c, h :: d -> b, j :: d -> a, and x :: d are all independent arguments to f; their order implies nothing about how we might end up using them in the definition of f.
To start, we know that f uses its arguments to return a value of type c. But none of the arguments have a value of type c; the only way to get a value of type c is to use g. But in order to use g, you need arguments of type a and type b, and none of f's arguments have those types. But we could use h and j to get them, if we had an argument of type d to apply them to, and lo and behold, we do have a value of type d: the argument x!.
f g h j x = let aValue = j x
bValue = h x
cValue = g aValue bValue
in cValue
which can be flattened to the original answer of
f g h j x = g (j x) (h x)
If you want to think of the return value of f as being d -> c, rather than just c, you can eliminate x from the definition with some point-free trickery.
f g h j = g <$> j <*> h -- liftA2 g j h
You can even go a little further to remove h and j as arguments, but the result, though simple, is even more incomprehensible:
f = flip . liftA2
Moral of the story: sometimes point-free style abstracts away distracting details, other times it completely obscures the meaning of the function.

Syntax of where block

I'm reading Programming in Haskell by Graham Hutton and it gives the following code in Chapter 13:
import Control.Applicative
import Data.Char
{- some code omitted -}
newtype Parser a = P (String -> [(a, String)])
item :: Parser Char
item = P (\ input -> case input of
[] -> []
x:xs -> [(x,xs)])
three :: Parser (Char,Char)
three = pure g <*> item <*> item <*> item
where g a b c = (a,c)
I'm having a hard time understanding the last line
where g a b c = (a,c)
I understand that this line exists because three has type Parser(Char, Char) but what does g a b c represent? How is g a b c syntactically valid? I'm used to seeing where in cases like
f :: s -> (a,s)
f x = y
where y = ... x ...
where each symbol x and y appear before the where declaration.
It is the syntax to declare a function. It is the equivalent to
where g = \a b c -> (a,c)
g is a function which takes 3 arguments and returns a tuple
How is g a b c syntactically valid?
It's valid for the same reason same definition on the top-level of the module would be valid. The difference between definitions in where and top level is just that you have variables bound in function's head (e.g. x in your last example) in scope and can use them on the right side, but this doesn't mean you have to use them.

Why are these functions differently evaluated

I was experimenting with haskell, and while trying to improve the readability of my code I suddenly changed the behaviour of it. I would have thought these two variants would be equivalent.
Original:
f :: Eq c => c -> c -> [[c]] -> [[c]]
f d c acc
| c == d = [] : acc
| otherwise = ([c] ++ (head acc)) : tail acc
split :: Eq a => a -> [a] -> [[a]]
split delim = foldr (f delim) [[]]
Here is the second one:
f' :: Eq c => c -> c -> [[c]] -> [[c]]
f' d c (currentWord:wordsSoFar)
| c == d = [] : currentWord : wordsSoFar
| otherwise = (c : currentWord) : wordsSoFar
split' :: Eq a => a -> [a] -> [[a]]
split' delim = foldr (f' delim) [[]]
Here are the results of running the two:
*Main> take 1 (split 5 [1..])
[[1,2,3,4]]
*Main> take 1 (split' 5 [1..])
*** Exception: stack overflow
Your first version only needs to evaluate acc when you call head and tail on it, so no evaluation takes place when c == d.
The second version needs to know whether acc is empty or not before it does anything else as none of the other code must execute if the pattern does not match. This means that acc has to be evaluated even if c == d. This leads to an infinite loop.
You can make the second version work by using an irrefutable pattern like this:
f' d c ~(currentWord:wordsSoFar) =
By making the pattern irrefutable, you're saying that you know that the pattern will match, so no check is necessary. If acc were empty, this would cause an error to happen when (and if) you used currentWord and wordsSoFar instead of a non-exhaustive pattern error happening right away (and regardless of whether currentWord and wordsSoFar are actually used).
I think this should be equivalent:
f d c acc | c == d = [] : acc
f d c (currentWord:wordsSoFar) = (c : currentWord) : wordsSoFar
Notice that if c == d then we don't attempt to determine whether acc is empty or not. (All versions of your code will actually fail if c == d and acc == []; I presume this never happens.)

Church style lists: infinite type error when compiling but not interactively

I'm just starting to learn haskell and I'm trying to implement lists in a pure lambda calculus way (such as described in the wikipedia page for Church encoding).
The following function produces a "cannot construct the infinite type" at compile time. However, when I execute the code of the function interactively, it works. This is the code of the function:
showl l = isempty' l 0 (head' l)
And here is how I run it interactively (it works):
let l = (cons' 7 empty') in isempty' l 0 (head' l)
With the function showl, I want to get the first element of a list (not a haskell list, but a list as defined in Church encoding) if it is not empty, and 0 otherwise. In details, isempty' l returns a Church boolean, namely the function \ a b -> a if the list l is empty (True), and \ a b -> b otherwise (False). This way, if True, showl returns 0, and `(head' l)' otherwise (the first element of the list).
I suppose it's a problem with type inference, as suggested by the other questions about infinit type errors. But I don't see it, and since it works interactively, it must be fine... I'm confused.
Thanks
(the exact compiler output:
Occurs check: cannot construct the infinite type: t = t1 -> t -> t2
Probable cause: `isempty'' is applied to too many arguments
In the expression: isempty' l 0 (head' l)
In the definition of `showl': showl l = isempty' l 0 (head' l)
Failed, modules loaded: none.
and the functions I wrote to define Church style lists:
-- True and False
t a b = a
f a b = b
-- pairs
pair a b z = z a b
fst' p = p t
snd' p = p f
-- lists
empty' f x = x
isempty' l = l (\ a b -> f) t
cons' a l f x = f a (l f x)
head' l = l t 0
tail' l = fst' (l (\x p -> pair (snd' p) (cons' x (snd' p))) (pair empty' empty'))
)
It seems the compiler is getting confused here. Given an explicit type signature for your function (using Rank2Types), it compiles nicely and works just fine.
{-# LANGUAGE Rank2Types #-}
type List a = forall b. (a -> b -> b) -> b -> b
showl :: Num a => List a -> a
showl l = isempty' l 0 (head' l)
When running it interactively it works because the concrete types are available.

How can I check if a BST is valid?

How can I check if a BST is a valid one, given its definition and using a generalized version of fold for BST?
data(Ord a, Show a, Read a) => BST a = Void | Node {
val :: a,
left, right :: BST a
} deriving (Eq, Ord, Read, Show)
fold :: (Read a, Show a, Ord a) => (a -> b -> b -> b) -> b -> BST a -> b
fold _ z Void = z
fold f z (Node x l r) = f x (fold f z l) (fold f z r)
The idea is to check that a node value is greater then all values in left-subtree and smaller than all values in its right-subtree. This must be True for all nodes in the tree. A function bstList simply output the list of (ordered) values in the BST.
Of course something like this won't work:
--isBST :: (Read a, Show a, Ord a) => BST a -> Bool
isBST t = fold (\x l r -> all (<x) (bstList l) && all (>x) (bstList r)) (True) t
because, for example, applying the fold function to the node 19 ends up all (<19) (bstList True) && all (>19) (bstList True).
Your problem seems to be that you lose information because your function only returns a boolean when it examines the left and right subtrees. So change it to also return the minimum and maximum values of the subtrees. (This is probably more efficient as well, since you don't need to used bslist to check all elements anymore)
And make a wrapper function to ignore these "auxiliary" values after you are done, of course.
(Please don't put typeclass constraints on the data type.)
A BST is valid iff an in-order traversal is monotonically increasing.
flatten tree = fold (\a l r -> l . (a:) . r) id tree []
ordered list#(_:rest) = and $ zipWith (<) list rest
ordered _ = True
isBST = ordered . flatten
A nice way of encoding this is to lean on the traversal provided by Data.Foldable.
{-# LANGUAGE DeriveFunctor, DeriveFoldable #-}
import Data.Foldable
import Data.Monoid
We can derive an instance of it automatically using an extension, but we need to reorder the fields of the Node constructor to provide us an in-order traversal.
While we're at it, we should eliminate the constraints on the data type itself. They actually provide no benefit, and has been removed from the language as of Haskell 2011. (When you want to use such constraints you should put them on instances of classes, not on the data type.)
data BST a
= Void
| Node
{ left :: BST a
, val :: a
, right :: BST a
} deriving (Eq, Ord, Read, Show, Foldable)
First we define what it means for a list to be strictly sorted.
sorted :: Ord a => [a] -> Bool
sorted [] = True
sorted [x] = True
sorted (x:xs) = x < head xs && sorted xs
-- head is safe because of the preceeding match.
Then we can use the toList method provided by Data.Foldable and the above helper.
isBST :: Ord a => BST a -> Bool
isBST = sorted . toList
We can also implement this more directly, like you asked. Since we removed the spurious constraints on the data type, we can simplify the definition of your fold.
cata :: (b -> a -> b -> b) -> b -> BST a -> b
cata _ z Void = z
cata f z (Node l x r) = f (cata f z l) x (cata f z r)
Now we need a data type to model the result of our catamorphism, which is that we either have no nodes (Z), or a range of strictly increasing nodes (T) or have failed (X)
data T a = Z | T a a | X deriving Eq
And we can then implement isBST directly
isBST' :: Ord a => BST a -> Bool
isBST' b = cata phi Z b /= X where
phi X _ _ = X
phi _ _ X = X
phi Z a Z = T a a
phi Z a (T b c) = if a < b then T a c else X
phi (T a b) c Z = if b < c then T a c else X
phi (T a b) c (T d e) = if b < c && c < d then T a e else X
This is a bit tedious, so perhaps it would be better to decompose the way we compose the interim states a bit:
cons :: Ord a => a -> T a -> T a
cons _ X = X
cons a Z = T a a
cons a (T b c) = if a < b then T a c else X
instance Ord a => Monoid (T a) where
mempty = Z
Z `mappend` a = a
a `mappend` Z = a
X `mappend` _ = X
_ `mappend` X = X
T a b `mappend` T c d = if b < c then T a d else X
isBST'' :: Ord a => BST a -> Bool
isBST'' b = cata phi Z b /= X where
phi l a r = l `mappend` cons a r
Personally, I'd probably just use the Foldable instance.
If you don't insist on using a fold you can do it like this:
ord Void = True
ord (Node v l r) = every (< v) l && every (> v) r && ord l && ord r where
every p Void = True
every p (Node v l r) = p v && every p l && every p r

Resources