Comparison chain

From HaskellWiki
Revision as of 13:35, 21 November 2006 by Lemming (talk | contribs) (initialized)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Problem

Question: The compiler doesn't accept a <= x <= b. Why?

Answer: The expression cannot be parsed, because the infix symbol <= has no (left or right) associativity.

In languages like C the expression is parsed as (a <= x) <= b which is even worse. The first part is evaluated to a boolean value, which is then compared with b. (For C "boolean" and "integer" are the same type.)

Solutions

simple

  • You must be aware, that the mathematical notation is shorthand for . Consequently a possible Haskell solution is a <= x && x <= b.
  • Another fine mathematical notation is . You can roll your own function
isInRange :: Ord a => a -> a -> a -> Bool
isInRange lower upper x = lower <= x && x <= upper
to capture this notation (isInRange a b x), or
(<?) :: Ord a => a -> (a,a) -> Bool
(<?) = flip (uncurry isInRange)
(x <? (a,b)). In case of integers you can use the inRange function from Ix class.
  • You can easily write a function, which checks if a list of numbers increases monotonicly.
monotonicIncreasing :: Ord a => [a] -> Bool
monotonicIncreasing xs = and (zipWith (<=) xs (tail xs))
You can use that for the initial problem by monotonicIncreasing [a,x,b].


complex

  • For more complex checks of whether an element is contained in some ranges, you should have a look at the ranged sets library.
  • If you want to program more complex chains with different kinds of comparisons, try the following code.
module ChainRelation where

{- * chains of relations (comparison, subsets, logical implications etc.) -}

infixr 4 &-, -&

type Rel   a = (a -> a -> Bool)
type Chain a = [(Rel a, a)]

endChain :: Chain a
endChain = []

-- separate comparison and operand
(&-) :: Rel a -> (a, Chain a) -> Chain a
rel &- (x,xs) = (rel,x):xs

-- separate operand and comparison
(-&) :: a -> Chain a -> (a, Chain a)
(-&) = (,)

-- check if all comparisons are true
check :: (a, Chain a) -> Bool
check (x,chain) =
   let (rels,xs) = unzip chain
   in  and (zipWith3 id rels (x:xs) xs)


example1 :: Bool
example1 =
   check (1 -& (<) &- 5 -& (==) &- 5 -& (<=) &- 10 -&
      (endChain :: Chain Integer))


{- * specialised infix operators for comparison -}

infixr 4 ==:, /=:, <:, >:, <=:, >=:

(==:), (/=:), (<:), (>:), (<=:), (>=:) :: Ord a =>
   a -> (a, Chain a) -> (a, Chain a)
(==:) = lift (==)
(/=:) = lift (/=)
(<:)  = lift (<)
(>:)  = lift (>)
(<=:) = lift (<=)
(>=:) = lift (>=)

lift :: Rel a -> a -> (a, Chain a) -> (a, Chain a)
lift f x (y,chain) = (x, (f,y):chain)

example2 :: Bool
example2 =
   check (1 <: 5 ==: 5 <=: 10
             -& (endChain :: Chain Integer))