Function composition in boolean operators - haskell

I don't have much FP experience and I think I'm just missing a key insight from someone more versed. I'm writing a small, embedded, functional, strictly- and invariantly-typed language.
I'll be using Haskell-like syntax in this question.
The following signatures are for predefined functions with types that are what you'd expect:
and :: bool -> bool -> bool -- boolean and
lt :: int -> int -> bool -- less than
gt :: int -> int -> bool -- greater than
len :: list -> int -- list length
My job is to compose these functions (and constants) to form an expression which has the following signature:
λ :: list -> bool
The result of which is whether a list has a length between 1 and 99.
Constraints: This language (currently) only supports function application and function composition. No lambda expressions, no higher-order functions.
This is how far I've gotten:
and . ((gt 0) . len) :: list -> bool -> bool
This takes a list, checks if it's length is greater than 0, then a boolean and returns the "and" of both arguments.
But now I'm stuck. How would you continue from here in traditional functional languages? Is there a way to express a solution without lambdas/closures?
I'm open to add new features to the language, as long as it remains underpowered and simple.

This is called pointfree style and there is a nice tool on the web for transforming Haskell code to it. Converting f xs = (length xs > 0) && (length xs < 100) gives f = ap ((&&) . (> 0) . length) ((< 100) . length). So you are just missing the ap function (see also Understanding `ap` in a point-free function in Haskell). For your application it should have type (a -> b -> c) -> (a -> b) -> (a -> c) and be built-in along with ..

Related

Meaning of `$` when used as argument to map

I understand that the $ operator is for avoiding parentheses. Anything appearing after it will take precedence over anything that comes before.
I am trying to understand what it means in this context:
map ($ 3) [(+),(-),(/),(*)]
With the following code:
instance Show (a -> b) where
show a = function
main = putStrLn $ show $ map ($ 3) [(+),(-),(/),(*)]
The output is
["function", "function", "function", "function"]
This doesn't help me understand the meaning of the $ here.
How can I display more helpful output?
($) :: (a -> b) -> a -> b is a function that takes a function as first parameter, and a value as second and returns the value applied to that function.
For example:
Prelude> (1+) $ 2
3
The expression ($ 3) is an example of infix operator sectioning [Haskell-wiki]. ($ 3) is short for \f -> f $ 3, or simpler \f -> f 3. It thus is a function that takes a function and applies 3 to that function.
For your expression:
map ($ 3) [(+),(-),(/),(*)]
the output is thus equivalent to:
[(3+), (3-), (3/), (3*)] :: Fractional a => [a -> a]
Since (+), (-), (*) :: Num a => a -> a -> a work with types that are members of the Num typeclass, and (/) :: Fractional a => a -> a -> a works with types that are members of the Fractional type class, and all Fractional types are num types as well, 3 is here a Fractional type, and the list thus contains functions that are all of the type a -> a with a a member of Fractional.
How can I display more helpful output?
The compiler does not keep track of the expressions, as specified in the Haskell wiki page on Show instance for functions [Haskell-wiki].
The Haskell compiler doesn't maintain the expressions as they are, but translates them to machine code or some other low-level representation. The function \x -> x - x + x :: Int -> Int might have been optimized to \x -> x :: Int -> Int. If it's used anywhere, it might have been inlined and optimized to nothing. The variable name x is not stored anywhere. (...)
So we can not "look inside" the function and derive an expression that is human-readable.

Re-write 'map intToDigit' with a fold...

So this one seems like it should be super-simple... but I'm not sure where to stick the 'fold' in (obviously you could fold either way)...
It says "write a function ( intToString :: [Int] -> [Char] ) using a fold, that mimics this map:
map intToDigit [5,2,8,3,4] == "52834"
And then says, "For the conversion, use intToDigit :: Int -> Char from Data.Char."
I'm not entirely sure I get the point... but yet it doesn't seem like it should be that hard -- you're just reading in the list (folding it in, I get how folds work in general) from either the left or right and doing the conversion... but I'm not sure how to set it up.
It is not difficult, think about the definition foldr (or foldl) of List:
foldr::(a -> b -> b) -> b -> [a] -> b
Here (a->b->b) is the step function which will be applied on each element of list [a], b is your target.
Now, you have a list of Int ([Int]), and need to convert to [Char] (or String).
Relpace [a] by [5,2,8,3,4], b by []::[Char] (your target) and (a->b->b) by step function :
foldr step ([]::[Char]) [5,2,8,3,4]
We have known that step function has type (a->b->b), specifically, (Int->[Char]->[Char]), the job need to do just convert Int to [Char], as mentioned in question: intToDigit can be helped to convert Int to Char and (:) operator can append element at the head of List so:
step x s = intToDigit x : s
where s is [Char] (or String), put them all:
foldr (\x s->intToDigit x : s) [] [5,2,8,3,4]

Getting all function arguments in haskel as list

Is there a way in haskell to get all function arguments as a list.
Let's supose we have the following program, where we want to add the two smaller numbers and then subtract the largest. Suppose, we can't change the function definition of foo :: Int -> Int -> Int -> Int. Is there a way to get all function arguments as a list, other than constructing a new list and add all arguments as an element of said list? More importantly, is there a general way of doing this independent of the number of arguments?
Example:
module Foo where
import Data.List
foo :: Int -> Int -> Int -> Int
foo a b c = result!!0 + result!!1 - result!!2 where result = sort ([a, b, c])
is there a general way of doing this independent of the number of arguments?
Not really; at least it's not worth it. First off, this entire idea isn't very useful because lists are homogeneous: all elements must have the same type, so it only works for the rather unusual special case of functions which only take arguments of a single type.
Even then, the problem is that “number of arguments” isn't really a sensible concept in Haskell, because as Willem Van Onsem commented, all functions really only have one argument (further arguments are actually only given to the result of the first application, which has again function type).
That said, at least for a single argument- and final-result type, it is quite easy to pack any number of arguments into a list:
{-# LANGUAGE FlexibleInstances #-}
class UsingList f where
usingList :: ([Int] -> Int) -> f
instance UsingList Int where
usingList f = f []
instance UsingList r => UsingList (Int -> r) where
usingList f a = usingList (f . (a:))
foo :: Int -> Int -> Int -> Int
foo = usingList $ (\[α,β,γ] -> α + β - γ) . sort
It's also possible to make this work for any type of the arguments, using type families or a multi-param type class. What's not so simple though is to write it once and for all with variable type of the final result. The reason being, that would also have to handle a function as the type of final result. But then, that could also be intepreted as “we still need to add one more argument to the list”!
With all respect, I would disagree with #leftaroundabout's answer above. Something being
unusual is not a reason to shun it as unworthy.
It is correct that you would not be able to define a polymorphic variadic list constructor
without type annotations. However, we're not usually dealing with Haskell 98, where type
annotations were never required. With Dependent Haskell just around the corner, some
familiarity with non-trivial type annotations is becoming vital.
So, let's take a shot at this, disregarding worthiness considerations.
One way to define a function that does not seem to admit a single type is to make it a method of a
suitably constructed class. Many a trick involving type classes were devised by cunning
Haskellers, starting at least as early as 15 years ago. Even if we don't understand their
type wizardry in all its depth, we may still try our hand with a similar approach.
Let us first try to obtain a method for summing any number of Integers. That means repeatedly
applying a function like (+), with a uniform type such as a -> a -> a. Here's one way to do
it:
class Eval a where
eval :: Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval i = \y -> eval (i + y)
instance Eval Integer where
eval i = i
And this is the extract from repl:
λ eval 1 2 3 :: Integer
6
Notice that we can't do without explicit type annotation, because the very idea of our approach is
that an expression eval x1 ... xn may either be a function that waits for yet another argument,
or a final value.
One generalization now is to actually make a list of values. The science tells us that
we may derive any monoid from a list. Indeed, insofar as sum is a monoid, we may turn arguments to
a list, then sum it and obtain the same result as above.
Here's how we can go about turning arguments of our method to a list:
class Eval a where
eval2 :: [Integer] -> Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [Integer] where
eval2 is i = i:is
This is how it would work:
λ eval2 [] 1 2 3 4 5 :: [Integer]
[5,4,3,2,1]
Unfortunately, we have to make eval binary, rather than unary, because it now has to compose two
different things: a (possibly empty) list of values and the next value to put in. Notice how it's
similar to the usual foldr:
λ foldr (:) [] [1,2,3,4,5]
[1,2,3,4,5]
The next generalization we'd like to have is allowing arbitrary types inside the list. It's a bit
tricky, as we have to make Eval a 2-parameter type class:
class Eval a i where
eval2 :: [i] -> i -> a
instance (Eval a i) => Eval (i -> a) i where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [i] i where
eval2 is i = i:is
It works as the previous with Integers, but it can also carry any other type, even a function:
(I'm sorry for the messy example. I had to show a function somehow.)
λ ($ 10) <$> (eval2 [] (+1) (subtract 2) (*3) (^4) :: [Integer -> Integer])
[10000,30,8,11]
So far so good: we can convert any number of arguments into a list. However, it will be hard to
compose this function with the one that would do useful work with the resulting list, because
composition only admits unary functions − with some trickery, binary ones, but in no way the
variadic. Seems like we'll have to define our own way to compose functions. That's how I see it:
class Ap a i r where
apply :: ([i] -> r) -> [i] -> i -> a
apply', ($...) :: ([i] -> r) -> i -> a
($...) = apply'
instance Ap a i r => Ap (i -> a) i r where
apply f xs x = \y -> apply f (x:xs) y
apply' f x = \y -> apply f [x] y
instance Ap r i r where
apply f xs x = f $ x:xs
apply' f x = f [x]
Now we can write our desired function as an application of a list-admitting function to any number
of arguments:
foo' :: (Num r, Ord r, Ap a r r) => r -> a
foo' = (g $...)
where f = (\result -> (result !! 0) + (result !! 1) - (result !! 2))
g = f . sort
You'll still have to type annotate it at every call site, like this:
λ foo' 4 5 10 :: Integer
-1
− But so far, that's the best I can do.
The more I study Haskell, the more I am certain that nothing is impossible.

Point Free Style Required for Optimized Curry

Say we have a (contrived) function like so:
import Data.List (sort)
contrived :: Ord a => [a] -> [a] -> [a]
contrived a b = (sort a) ++ b
And we partially apply it to use elsewhere, eg:
map (contrived [3,2,1]) [[4],[5],[6]]
On the surface, this works as one would expect:
[[1,2,3,4],[1,2,3,5],[1,2,3,6]]
However, if we throw some traces in:
import Debug.Trace (trace)
contrived :: Ord a => [a] -> [a] -> [a]
contrived a b = (trace "sorted" $ sort a) ++ b
map (contrived $ trace "a value" [3,2,1]) [[4],[5],[6]]
We see that the first list passed into contrived is evaluated only once, but it is sorted for each item in [4,5,6]:
[sorted
a value
[1,2,3,4],sorted
[1,2,3,5],sorted
[1,2,3,6]]
Now, contrived can be rather simply translated to point-free style:
contrived :: Ord a => [a] -> [a] -> [a]
contrived a = (++) (sort a)
Which when partially applied:
map (contrived [3,2,1]) [4,5,6]
Still works as we expect:
[[1,2,3,4],[1,2,3,5],[1,2,3,6]]
But if we again add traces:
contrived :: Ord a => [a] -> [a] -> [a]
contrived a = (++) (trace "sorted" $ sort a)
map (contrived $ trace "a value" [3,2,1]) [[4],[5],[6]]
We see that now the first list passed into contrived is evaluated and sorted only once:
[sorted
a value
[1,2,3,4],[1,2,3,5],[1,2,3,6]]
Why is this so? Since the translation into pointfree style is so trivial, why can't GHC deduce that it only needs to sort a once in the first version of contrived?
Note: I know that for this rather trivial example, it's probably preferable to use pointfree style. This is a contrived example that I've simplified quite a bit. The real function that I'm having the issue with is less clear (in my opinion) when expressed in pointfree style:
realFunction a b = conditionOne && conditionTwo
where conditionOne = map (something a) b
conditionTwo = somethingElse a b
In pointfree style, this requires writing an ugly wrapper (both) around (&&):
realFunction a = both conditionOne conditionTwo
where conditionOne = map (something a)
conditionTwo = somethingElse a
both f g x = (f x) && (g x)
As an aside, I'm also not sure why the both wrapper works; the pointfree style of realFunction behaves like the pointfree style version of contrived in that the partial application is only evaluated once (ie. if something sorted a it would only do so once). It appears that since both is not pointfree, Haskell should have the same issue that it had with the non-pointfree contrived.
If I understand correctly, you are looking for this:
contrived :: Ord a => [a] -> [a] -> [a]
contrived a = let a' = sort a in \b -> a' ++ b
-- or ... in (a' ++)
If you want the sort to be computed only once, it has to be done before the \b.
You are correct in that a compiler could optimize this. This is known as the "full laziness" optimization.
If I remember correctly, GHC does not always do it because it's not always an actual optimization, in the general case. Consider the contrived example
foo :: Int -> Int -> Int
foo x y = let a = [1..x] in length a + y
When passing both arguments, the above code works in constant space: the list elements are immediately garbage collected as they are produced.
When partially applying x, the closure for foo x only requires O(1) memory, since the list is not yet generated. Code like
let f = foo 1000 in f 10 + f 20 -- (*)
still run in constant space.
Instead, if we wrote
foo :: Int -> Int -> Int
foo x = let a = [1..x] in (length a +)
then (*) would no longer run in constant space. The first call f 10 would allocate a 1000-long list, and keep it in memory for the second call f 20.
Note that your partial application
... = (++) (sort a)
essentially means
... = let a' = sort a in \b -> a' ++ b
since argument passing involves a binding, as in let. So, the result of your sort a is kept around for all the future calls.

Cleanest way to apply a list of boolean functions to a list?

Consider this:
ruleset = [rule0, rule1, rule2, rule3, rule4, rule5]
where rule0, rule1, etc. are boolean functions that take one argument. What is the cleanest way to find if all elements of a particular list satisfy all the rules in the ruleset?
Obviously, a loop would work, but Haskell folks always seem to have clever one-liners for these types of problems.
The all function seems appropriate (eg. all (== check_one_element) ruleset) or nested maps. Also, map ($ anElement) ruleset is roughly what I want, but for all elements.
I'm a novice at Haskell and the many ways one could approach this problem are overwhelming.
If you require all the functions to be true for each argument, then it's just
and (ruleset <*> list)
(You'll need to import Control.Applicative to use <*>.)
Explanation:
When <*> is given a pair of lists, it applies each function from the list on the left to each argument from the list on the right, and gives back a list containing all the results.
A one-liner:
import Control.Monad.Reader
-- sample data
rulesetL = [ (== 1), (>= 2), (<= 3) ]
list = [1..10]
result = and $ concatMap (sequence rulesetL) list
(The type we're working on here is Integer, but it could be anything else.)
Let me explain what's happening: rulesetL is of type [Integer -> Bool]. By realizing that (->) e is a monad, we can use
sequence :: Monad m => [m a] -> m [a]
which in our case will get specialized to type [Integer -> Bool] -> (Integer -> [Bool]). So
sequence rulesetL :: Integer -> [Bool]
will pass a value to all the rules in the list. Next, we use concatMap to apply this function to list and collect all results into a single list. Finally, calling
and :: [Bool] -> Bool
will check that all combinations returned True.
Edit: Check out dave4420's answer, it's nicer and more concise. Mine answer could help if you'd need to combine rules and apply them later on some lists. In particular
liftM and . sequence :: [a -> Bool] -> (a -> Bool)
combines several rules into one. You can also extend it to other similar combinators like using or etc. Realizing that rules are values of (->) a monad can give you other useful combinators, such as:
andRules = liftM2 (&&) :: (a -> Bool) -> (a -> Bool) -> (a -> Bool)
orRules = liftM2 (||) :: (a -> Bool) -> (a -> Bool) -> (a -> Bool)
notRule = liftM not :: (a -> Bool) -> (a -> Bool)
-- or just (not .)
etc. (don't forget to import Control.Monad.Reader).
An easier-to-understand version (without using Control.Applicative):
satisfyAll elems ruleset = and $ map (\x -> all ($ x) ruleset) elems
Personally, I like this way of writing the function, as the only combinator it uses explicitly is and:
allOkay ruleset items = and [rule item | rule <- ruleset, item <- items]

Resources