Haskell Quiz/Posix Pangrams/Solution Burton
This is a naive solution - it works by taking the sortest subsequence of the original list which is a pangram then trying to replace words in it with shorter, unused ones. The pangrams it produces aren't very short.
module Main
where
import IO
import Char
import List
{--
*Main> main
pangram: admin bc ex fg lp sh tr zcat yacc write who vi uux unlink uniq join
wordcount: 16, total chars: 52, repeated chars: 41
--}
makePangram :: [String] -> String -> [String] -> Int -> IO String
makePangram [] pg rejects pass | isPangram pg = return pg
| pass == 0 = makePangram rejects pg [] 1
| otherwise = return ("ran out of words! " ++ pg)
makePangram (w:ws) pg rejects pass | isPangram pg = return pg
| hasNew w (nub pg) = handleDupes
| otherwise = makePangram ws pg rejects pass
where handleDupes | not (hasDupes (filter isAlpha w) (nub pg))
|| pass == 1 = makePangram ws (pg ++ " " ++ w) rejects pass
| otherwise = makePangram ws pg (w:rejects) pass
hasNew :: String -> String -> Bool
hasNew x [] = True
hasNew [] _ = False
hasNew (x:xs) w | not $ isAlpha x = hasNew xs w
| x `notElem` w = True
| otherwise = hasNew xs w
hasDupes :: String -> String -> Bool
hasDupes _ [] = False
hasDupes [] _ = False
hasDupes (x:xs) w = x `elem` w || hasDupes xs w
numDupes :: String -> Int
numDupes s = numDupes' s 0
where numDupes' [] c = c
numDupes' (x:xs) c = if x `elem` xs then numDupes' xs (c+1) else numDupes' xs c
isPangram :: String -> Bool
isPangram = (==26) . length . nub . filter isAlpha
stats :: String -> String
stats s = "wordcount: "
++ (show (length (words s)))
++ ", total chars: "
++ (show (length (filter isAlpha s)))
++ ", repeated chars: " ++ (show (numDupes s))
main = do cs <- readFile "posix-utils.txt"
pg <- makePangram (lines cs) "" [] 0
putStrLn ("pangram: " ++ pg)
putStrLn (stats pg)