[Haskell-beginners] problems using bytestrings

Joe Van Dyk joe at fixieconsulting.com
Tue Jan 19 14:40:38 EST 2010


Hello,

I wrote a function that finds anagrams in a file.  It worked great.
Until I tried to use Bytestrings to get better performance.

Here's the code:
(http://github.com/joevandyk/haskell/blob/aa61a58e6a027dda60a32ae64ec99f92d00ae5ed/pearls/anagrams/anagram.hs)
import qualified Data.Map as Map
import Data.Ord
import Data.List
import qualified Data.ByteString.Char8 as BS

-- what's the type here?  I get an infinite type error
anagrams :: Ord a => [a] -> [a]
anagrams words =
  sorted_anagrams
  where
    sorted_anagrams      = sortBy (flip $ comparing length) get_anagrams
    get_anagrams         = Map.elems $ foldl' insert_word Map.empty words
    insert_word map word = Map.insertWith' (++) (sort word) [word] map

main = do
  -- original code, worked fine:
  -- input <- getContents
  -- print $ take 3 $ anagrams $ lines input
  -- new code with bytestring has errors
  input <- BS.getContents
  print $ take 3 $ anagrams $ BS.lines input


There are two errors.  One:
anagram.hs:7:0:
    Occurs check: cannot construct the infinite type: a = [a]
    When generalising the type(s) for `anagrams'


That happens when I add the type to the anagrams method.

If I don't have a type specified, then I get this error:
anagram.hs:21:30:
    Couldn't match expected type `[a]'
           against inferred type `BS.ByteString'
      Expected type: [[a]]
      Inferred type: [BS.ByteString]
    In the second argument of `($)', namely `BS.lines input'
    In the second argument of `($)', namely `anagrams $ BS.lines input'


I'm lost here.  Help!
-- 
Joe Van Dyk
http://fixieconsulting.com


More information about the Beginners mailing list