Pattern matching on functions (>), (==), (<)

I want to compare the length of a potentially inifinite list with a number.
Given that this doesn’t terminate:

if length [1..] < 10 
then ... 
else ...

I wrote this function:

-- compare (length l) n
-- (compareLengthN [1..] 10) == GT
compareLengthN :: [a] -> Int -> Ordering
compareLengthN l n 
    | n < 0     = GT
    | null e    = if length f == n then EQ else LT
    | otherwise = GT
    where (f, e) = splitAt n l

I would like to write this but I can’t use pattern matching with functions.

-- (length l) (operator like <, <=, ==, >=, >) n
-- (length [1..]) <  10 --> False
-- (length [1..]) == 10 --> False
-- (length [1..]) >  10 --> True
listLengthN l (>)  n = GT == compareLengthN l n 
listLengthN l (==) n = EQ == compareLengthN l n
listLengthN l (<)  n = LT == compareLengthN l n

Suggestions?


PS: Why can’t the compiler recognize the first pattern and terminate when the list length is greater than 10? You don’t need to calculate the entire length of the list to know that: length [1..] < 10 == False

TL;DR I think the best way to do that is like this:

if null (drop 10 [1..])
then ...
else ...

This is not really true, length [1..] is not a normal number (technically it is “bottom”, the same as undefined). Moreover, length returns Int, which wraps around to negative numbers if you increment it too many times. So there is no way for the compiler to tell whether the check should be true or false.

You can define a lazier number type:

data Nat = Zero | Succ Nat deriving (Eq, Ord)
instance Num Nat where
  fromInteger 0 = Zero
  fromInteger n = Succ (fromInteger (n - 1))
  ...

Then you can write your own length function:

length' [] = Zero
length' (_:xs) = Succ (length' xs)

That works as you expect:

ghci> length' [1..] < 10
False

But of course this number type is much less efficient for most purposes.

7 Likes

You know, I wonder why not instead

listLengthN l GT n = GT == compareLengthN l n 
listLengthN l EQ n = EQ == compareLengthN l n
listLengthN l LT n = LT == compareLengthN l n

And therefore the logical slippery slope conclusion:

listLengthN l c n = c == compareLengthN l n 

There is also a sequel! In idomatic Haskell, listLengthN is almost never used, compareLengthN is almost always preferred.

main = do
    putStrLn "Please enter input:"
    xs <- getLine
    case compareLengthN xs 10 of
        LT -> fooShort
        EQ -> fooMiddle
        GT -> fooLong

When do you even need listLengthN?

1 Like

‘Drop the “N”. Just compareLength. It’s cleaner.’

1 Like

Instead of defining length', it should also be possible to use genericLength which is already in base:

genericLength []        =  0
genericLength (_:l)     =  1 + genericLength l

And inductively defined natural numbers with a Num instance are available from the fin package:

data Nat = Z | S Nat

So it seems all the pieces are already there, although I haven’t tested how well it works if you combine them.

1 Like

compareLength is now in Data.List, pending release of base-4.21: Data.List

(See Add Data.List.compareLength · Issue #257 · haskell/core-libraries-committee · GitHub for more context)

4 Likes