Haskell Quiz/Credit Cards/Solution Dolio

From HaskellWiki
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.


This solution does nothing particularly special. The constraints on each type of card are expressed as guards in some MonadPlus, which allows the results of those functions to be summed to get a result. The Luhn algorithm is fairly straight forward list processing.

The program expects command line arguments consisting only of the credit card number. The arguments are concatenated into a single string, so one can use as many or as few spaces to break it up as they wish.

import Control.Monad
import Data.Char
import Data.List
import Data.Maybe
import System.Environment

luhn :: [Int] -> Bool
luhn = (==0) . (`mod` 10) . sum . foldr split [] . zipWith ($) (cycle [id, (*2)]) . reverse

split n l
    | n > 9     = split d (m:l)
    | otherwise = n:l
 where (d, m) = divMod n 10

amex l@(x:y:_) = do guard $ length l == 15
                    guard $ x == 3
                    guard $ y `elem` [4, 7]
                    return "AMEX"

discover l = do guard $ length l == 16
                guard $ [6,0,1,1] `isPrefixOf` l
                return "Discover"

visa l@(x:_) = do guard $ length l `elem` [13, 16]
                  guard $ x == 4
                  return "Visa"

mastercard l@(x:y:_) = do guard $ length l == 16
                          guard $ x == 5
                          guard $ y `elem` [1..5]
                          return "Mastercard"

unknown l = return "Unknown"

cardType l = fromJust . msum . map ($ l) $ [amex, discover, visa, mastercard, unknown]

main = putStrLn . unwords
        . (\l -> [if luhn l then "Valid" else "Invalid", cardType l, "card"])
        . map (digitToInt) . concat =<< getArgs
</hasekll>