
All I meant was a small change:
makeVerifier :: (Int -> Int -> Int) -> Int -> (Int -> Bool) makeVerifier f m = divides m . foldl (+) 0 . zipWith f [1 .. ] . digits
which make some things simpler:
let checkIsbn = makeVerifier (*) 11 <== I liked this syntax better too, and it's what I had originally.
BTW, here's a sneaky way do define digits:
digits :: Int -> [Int] digits = map digitToInt . show <== I haven't gotten to "show" yet. When needed? When not?
So then you'd have:
makeVerifier :: (Int -> Int -> Int) -> Int -> Int -> Bool makeVerifier f m = (== 0) . (`mod` m) . sum . zipWith f [1 .. ] . map digitToInt . show
Which looks pretty nice, I think.
-- Lennart
========
Very good. I've yet to replace the 'foldl' with 'sum', but will. Eliminating the 'divides' function is also a nice touch. With Haskell it seems there's always a way to make one's code ever briefer, and using built-ins is probably much faster than anything I'd cook up, but it takes time to learn these short-cuts.
Thanks for your comments.
Michael
--- On Mon, 4/13/09, Lennart Augustsson
makeVerifier :: (Int -> Int -> Int) -> Int -> (Int -> Bool) makeVerifier f m = divides m . foldl (+) 0 . zipWith f [1 .. ] . digits
which make some things simpler:
let checkIsbn = makeVerifier (*) 11
BTW, here's a sneaky way do define digits:
digits :: Int -> [Int] digits = map digitToInt . show
So then you'd have:
makeVerifier :: (Int -> Int -> Int) -> Int -> Int -> Bool makeVerifier f m = (== 0) . (`mod` m) . sum . zipWith f [1 .. ] . map digitToInt . show
Which looks pretty nice, I think.
-- Lennart
On Mon, Apr 13, 2009 at 1:09 AM, michael rice
Example please.
Michael
--- On Sun, 4/12/09, Lennart Augustsson
wrote: From: Lennart Augustsson
Subject: Re: [Haskell-cafe] Functions that return functions To: "michael rice" Cc: haskell-cafe@haskell.org, "Daniel Fischer" Date: Sunday, April 12, 2009, 6:59 PM You should use an curried function as f instead of a uncurried one. Uncurried functions are rarely used in Haskell.
-- Lennart
On Sun, Apr 12, 2009 at 10:09 PM, michael rice
wrote: Thanks, guys!
Boy, this bunch of complemented partially applied functions gives a whole new meaning to the term "thinking ahead." And the whole shebang is waiting on that input integer to set everything in motion. Pretty clever.
To generalize, I changed the function to:
makeVerifier :: ((Int,Int) -> Int) -> Int -> (Int -> Bool) makeVerifier f m = divides m . foldl (+) 0 . map f . zip [1 .. ] . digits
so, in Haskell
let checkIsbn = makeVerifier (\ (i,d) -> i * d) 11
let checkUpc = makeVerifier (\ (i,d) -> if odd i then d else 3*d) 10
let checkCc = makeVerifier (\ (i,d) -> if odd i then d else if d < 5 then 2*d else 2*d+1) 10
let checkUsps = makeVerifier (\ (i,d) -> if i == 1 then -d else d) 9
I think I'm catching on.
Michael
--- On Sun, 4/12/09, Daniel Fischer
wrote: From: Daniel Fischer
Subject: Re: [Haskell-cafe] Functions that return functions To: haskell-cafe@haskell.org Cc: "michael rice" Date: Sunday, April 12, 2009, 12:15 PM Am Sonntag 12 April 2009 17:38:53 schrieb michael rice:
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?
Functions returning functions are quite natural in Haskell. Since usually functions are written in curried form, a function returng a function corresponds to a function of multiple arguments applied to only some of them.
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))
makeVerifier f m n = divides m . foldl (+) 0 $ zipWith f [1 .. ] (digits n)
just call makeVerifier f m to get your verification function :)
If you don't want to name the last argument:
makeVerifier f m = divides m . foldl (+) 0 . zipWith f [1 .. ] . digits
more point-freeing would be obfuscation. Instead of foldl (+) 0, you could also just write sum.
-- 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]
map2 is zipWith, already in the Prelude.
-- And here's my digits function digits :: Int -> [Int] digits 0 = [] digits n = rem n 10 : digits (quot n 10)
Unless you are desperate for speed and sure you deal only with positive numbers (or know that you really want quot and rem), better use div and mod. Those give the commonly expected (unless your expectation has been ruined by the behaviour of % in C, Java...) results.
-- 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))
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe