
Michal Wallace
module Main where alphabet = "abcdefghijklmnopqrstuvwxyz"
in haskell you can do alphabet = ['a'..'z']
count ch str = length [c | c <- str , c == ch]
can do count c s = length (filter (c ==) s) or more cryptic: count c = length . (filter (c==))
hist str = [count letter str | letter <- alphabet] oneline ch str = [ch] ++ " " ++ stars (count ch str) stars x = if x == 0 then "" else "*" ++ stars ( x - 1 )
stars n = replicate n '*'
report str ch = do putStrLn ( oneline ch str ) loop f (h:t) = if t == [] then f h else do f h loop f t
you can use mapM_ main = do content <- getContents mapM_ (\a -> report content a) alphabet
main = do content <- getContents let rpt letter = report content letter loop rpt alphabet """
you dont choose the more efficient strategy cos you parse 26 times the contents of the file, it is better to do (as you did in python) parse 1 and remember the number of occurence.
Other than ignoring upper case letters, and being really really slow, it seems to work fine in hugs....
One thing I really missed was a hash / dictionary. I tried for about an hour to use Assoc following the examples from PLEAC:
http://pleac.sourceforge.net/pleac_haskell/hashes.html
... But I never got it working:
that's because i dont really use standard haskell library, i redefine a library in a file named Common.hs where there is a constructor AssocDefault. So if you want use AssocDefault, they you have to do: module Main where import Prelude hiding (($),(^),(.),(!!),map,take,lookup,.... AS in the example in the pleac section* import Common Put your code here. so it becomes: #!/usr/bin/runhugs -98 module Main where import Prelude hiding (($),(^),(.),(!!),map,take,lookup,drop,splitAt,reverse,filter,takeWhile,dropWhile,null,foldl,length) import Common main = do s <- getContents s.downcase .foldl(\h c -> if isAlpha c then h.update c (+1) else h) (empty::AssocDefault Char Int) .(\h -> ['a'..'z'].each (\c -> putStrLn (c^replicate (h!c) '*'))) or in more standard haskell, i will do: #!/usr/bin/runhugs -98 module Main where import Prelude hiding ((.)) (.) o f = f o update k f xs = xs.map (\ (k2,v) -> if k == k2 then (k,f v) else (k2,v)) each:: (e -> IO ()) -> [e] -> IO () each = mapM_ main :: IO () main = do s <- getContents s.map toLower .foldl(\h c -> if isAlpha c then h.update c (+1) else h) [(c, 0::Int) | c <- ['a'..'z']] .each (\ (c,n) -> putStrLn (show c ++ (replicate n '*' )))
:> module Main where :> import Assoc (empty) :> main :: IO() :> main = do line <- getContents :> let w = length line :> count:: AssocDefault String Int :> count = w.foldl (\a s -> a.update s (+1)) empty :> print x
-> ERROR "alphahist.hs":6 - Undefined type constructor "AssocDefault"
that's because AssocDefault is a constructor that standard haskell does not define.
Also, I'd really like to here anyone's thoughts on the code I have above, especially concercing what I could have done better. :)
Thanks!
Cheers,
- Michal http://www.sabren.net/ sabren@manifestation.com ------------------------------------------------------------ Give your ideas the perfect home: http://www.cornerhost.com/ cvs - weblogs - php - linux shell - perl/python/cgi - java ------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Yoann Padioleau, INSA de Rennes, France, Opinions expressed here are only mine. Je n'écris qu'à titre personnel. **____ Get Free. Be Smart. Simply use Linux and Free Software. ____**