[Haskell-cafe] Functions that return functions

michael rice nowgate at yahoo.com
Sun Apr 12 11:38:53 EDT 2009


The following are exercises 5.10, and 5.11 from the Scheme text "Concrete Abstractions" by Max Hailperin, et al. The text at that point is about writing verifiers to check ID numbers such as ISBNs, credit card numbers, UPCs, etc.

======

Exercise 5.10
Write a predicate that takes a number and determines whether the sum of its digits is divisible by 17.

Exercise 5.11
Write a procedure make-verifier, which takes f and m as its two arguments and returns a procedure capable of checking a number. The argument f is itself a procedure of course. Here is a particularly simple example of a verifier being made and used.

(define check-isbn (make-verifier * 11))

(check-isbn 0262010771)
#t

The value #t is the "true" value; it indicates that the number is a valid ISBN.

As we just saw, for ISBN numbers the divisor is 11 and the function is simply f(i,d(i)) = i * d(i). Other kinds of numbers use slightly more complicated functions, but you will still be able to use make-verifier to make a verifier much more easily than if you had to start from scratch.

=======

Here's the Scheme check-verifier function I wrote, followed by my humble attempt at a Haskell function that does the same thing. Below that are some verifier functions created with the Scheme make-verifier. Admittedly, functions that return functions are Lispy, but perhaps there a Haskelly way to accomplish the same thing?

Michael

===============  


(define (make-verifier f m) ;f is f(i,d) & m is divisor 
  (lambda (n) 
    (let* ((d (digits n))
       (i (index (length d))))   ;(index 3) => (1 2 3) 
      (divides? m (reduce + 0 (map f i d)))))) #f

makeVerifier :: (Int -> Int ->  Int) -> Int -> (Int -> Bool)

makeVerifier f m = \n -> let d = digits n

                             i = [1..(length d)]

                         in \n -> divides m (foldl (+) 0 (map2 f i d))



-- Note: Reduce is just foldl f 0 lst, but map2 is
map2 :: (Int -> Int -> Int) -> [Int] -> [Int] -> [Int]
map2 f m n = [ f i d | (i,d) <- zip m n]

-- And here's my digits function
digits :: Int -> [Int]
digits 0 = []
digits n = rem n 10 : digits (quot n 10)

-- And divides function
divides :: Int -> Int -> Bool
divides divisor n = 0 == rem n divisor 

=====

(define check-isbn ;book number
  (make-verifier
   *
   11))

(define check-upc ;universal product code
  (make-verifier
   (lambda (i d) (if (odd? i) d (* 3 d)))
   10))

(define check-cc ;credit card
  (make-verifier
   (lambda (i d) (if (odd? i) d (if (< d 5) (* 2 d) (+ (* 2 d) 1))))
   10))

(define check-usps ;postal money order
  (make-verifier
   (lambda (i d) (if (= i 1) (- d) d))
   9))




      
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090412/7295b4de/attachment.htm


More information about the Haskell-Cafe mailing list