More type errors I'm having trouble with

I'm continuing my now-and-then exploration of Haskell. I'm getting a new crop of type errors that I'm pulling my hair out over. The errors I'm getting are: $ make below cmd output started 2015 Tue Dec 01 04:05:17 PM PST # --make will go out and find what to build ghc -Wall --make -o dph dph.hs Split0.hs [1 of 3] Compiling Split0 ( Split0.hs, Split0.o ) [2 of 3] Compiling Md5s ( Md5s.hs, Md5s.o ) [3 of 3] Compiling Main ( dph.hs, dph.o ) dph.hs:13:13: Couldn't match type `IO' with `(,) (IO String)' Expected type: (IO String, String) Actual type: IO String In a stmt of a 'do' block: hash <- prefix_md5 filename :: IO String In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) } In an equation for `do_prefix_hash': do_prefix_hash filename = do { hash <- prefix_md5 filename :: IO String; (hash, filename) } dph.hs:14:6: Couldn't match type `[Char]' with `IO String' Expected type: IO String Actual type: String In the expression: hash In a stmt of a 'do' block: (hash, filename) In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) } dph.hs:24:23: Couldn't match type `[]' with `IO' Expected type: IO (IO String, String) Actual type: [(IO String, String)] In a stmt of a 'do' block: io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... } dph.hs:25:20: Couldn't match type `[a0]' with `(String, String)' Expected type: [(String, String)] Actual type: [[a0]] In the return type of a call of `sequence' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } dph.hs:25:20: Couldn't match type `[]' with `IO' Expected type: IO (String, String) Actual type: [(String, String)] In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... } dph.hs:25:29: Couldn't match expected type `[[a0]]' with actual type `(IO String, String)' In the first argument of `sequence', namely `io_hash_tuples' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } dph.hs:26:39: Couldn't match expected type `[(String, String)]' with actual type `(String, String)' In the second argument of `map', namely `hash_tuples' In the expression: map tuple_to_string hash_tuples :: [String] In an equation for `strings': strings = map tuple_to_string hash_tuples :: [String] make: *** [dph] Error 1 above cmd output done 2015 Tue Dec 01 04:05:18 PM PST dph.hs looks like: import Md5s import Split0 import System.IO get_filenames :: String -> [String] get_filenames buffer = do -- Let's hope this doesn't give locale-related roundtrip problems. Split0.split0 '\0' buffer :: [String] do_prefix_hash :: String -> (IO String, String) do_prefix_hash filename = do hash <- Md5s.prefix_md5 filename :: (IO String) (hash, filename) tuple_to_string :: (String, String) -> String tuple_to_string (first, second) = do (show first) ++ " " ++ (show second) main :: IO () main = do buffer <- (System.IO.hGetContents System.IO.stdin) :: IO String let filenames = (get_filenames buffer) :: [String] io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] hash_tuples <- sequence io_hash_tuples :: [(String, String)] let strings = map tuple_to_string hash_tuples :: [String] mapM_ putStrLn strings And Md5s.hs looks like: module Md5s where import qualified System.IO import qualified Text.Printf -- cabal install cryptohash import qualified Crypto.Hash.MD5 import qualified Data.ByteString import qualified Data.ByteString.Lazy -- http://stackoverflow.com/questions/10099921/efficiently-turn-a-bytestring-in... byte_string_to_hex :: Data.ByteString.ByteString -> String byte_string_to_hex = concatMap (Text.Printf.printf "%02x") . Data.ByteString.unpack prefix_md5 :: String -> IO String prefix_md5 filename = do let prefix_length = 1024 file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.hGet file prefix_length :: IO Data.ByteString.ByteString _ <- System.IO.hClose file let hasher = Crypto.Hash.MD5.init :: Crypto.Hash.MD5.Ctx let hasher2 = Crypto.Hash.MD5.update hasher data_read :: Crypto.Hash.MD5.Ctx let binary_digest = Crypto.Hash.MD5.finalize hasher2 :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String return hex_digest :: IO String full_md5 :: String -> IO String full_md5 filename = do file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.Lazy.hGetContents file :: IO Data.ByteString.Lazy.ByteString let binary_digest = Crypto.Hash.MD5.hashlazy data_read :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String -- Does this get closed for us later? -- strace shows the file getting closed without our explicit close. -- _ <- System.IO.hClose file return hex_digest :: IO String It might be easier to view these at http://stromberg.dnsalias.org/svn/equivalence-classes/trunk/equivs3-haskell/ , so the line numbers are precise. What is the deal? Can anyone tell me what should be running through my head to fix this kind of problem on my own in the future? Thanks! -- Dan Stromberg

Hi Dan,
I'm having a hard time understanding those error messages too. It
seems to me that part of the problem is that GHC is confused by some
incorrect type annotations of yours.
I suggest that you delete or at least comment out your own type
annotations and then either work with the hopefully simpler error-messages
from GHC or use the `:load` and `:type` commands in ghci to discover
the inferred
types for your functions.
Depending on how close the inferred type is to the intended type, you
may have to adjust the definitions.
Also note that you sometimes incorrectly and unnecessarily use
do-notation in "non-monadic"/plain functions, for example in
tuple_to_string and get_filenames.
You could also consider following a book or a course until you feel
more comfortable trying things on your own:
Take a look at learnyouahaskell.com or github.com/bitemyapp/learnhaskell.
Good luck!
Simon
2015-12-02 1:12 GMT+01:00, Dan Stromberg
I'm continuing my now-and-then exploration of Haskell.
I'm getting a new crop of type errors that I'm pulling my hair out over.
The errors I'm getting are:
$ make below cmd output started 2015 Tue Dec 01 04:05:17 PM PST # --make will go out and find what to build ghc -Wall --make -o dph dph.hs Split0.hs [1 of 3] Compiling Split0 ( Split0.hs, Split0.o ) [2 of 3] Compiling Md5s ( Md5s.hs, Md5s.o ) [3 of 3] Compiling Main ( dph.hs, dph.o )
dph.hs:13:13: Couldn't match type `IO' with `(,) (IO String)' Expected type: (IO String, String) Actual type: IO String In a stmt of a 'do' block: hash <- prefix_md5 filename :: IO String In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) } In an equation for `do_prefix_hash': do_prefix_hash filename = do { hash <- prefix_md5 filename :: IO String; (hash, filename) }
dph.hs:14:6: Couldn't match type `[Char]' with `IO String' Expected type: IO String Actual type: String In the expression: hash In a stmt of a 'do' block: (hash, filename) In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) }
dph.hs:24:23: Couldn't match type `[]' with `IO' Expected type: IO (IO String, String) Actual type: [(IO String, String)] In a stmt of a 'do' block: io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... }
dph.hs:25:20: Couldn't match type `[a0]' with `(String, String)' Expected type: [(String, String)] Actual type: [[a0]] In the return type of a call of `sequence' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... }
dph.hs:25:20: Couldn't match type `[]' with `IO' Expected type: IO (String, String) Actual type: [(String, String)] In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... }
dph.hs:25:29: Couldn't match expected type `[[a0]]' with actual type `(IO String, String)' In the first argument of `sequence', namely `io_hash_tuples' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... }
dph.hs:26:39: Couldn't match expected type `[(String, String)]' with actual type `(String, String)' In the second argument of `map', namely `hash_tuples' In the expression: map tuple_to_string hash_tuples :: [String] In an equation for `strings': strings = map tuple_to_string hash_tuples :: [String] make: *** [dph] Error 1 above cmd output done 2015 Tue Dec 01 04:05:18 PM PST
dph.hs looks like: import Md5s import Split0 import System.IO
get_filenames :: String -> [String] get_filenames buffer = do -- Let's hope this doesn't give locale-related roundtrip problems. Split0.split0 '\0' buffer :: [String]
do_prefix_hash :: String -> (IO String, String) do_prefix_hash filename = do hash <- Md5s.prefix_md5 filename :: (IO String) (hash, filename)
tuple_to_string :: (String, String) -> String tuple_to_string (first, second) = do (show first) ++ " " ++ (show second)
main :: IO () main = do buffer <- (System.IO.hGetContents System.IO.stdin) :: IO String let filenames = (get_filenames buffer) :: [String] io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] hash_tuples <- sequence io_hash_tuples :: [(String, String)] let strings = map tuple_to_string hash_tuples :: [String] mapM_ putStrLn strings
And Md5s.hs looks like: module Md5s where
import qualified System.IO import qualified Text.Printf -- cabal install cryptohash import qualified Crypto.Hash.MD5 import qualified Data.ByteString import qualified Data.ByteString.Lazy
-- http://stackoverflow.com/questions/10099921/efficiently-turn-a-bytestring-in... byte_string_to_hex :: Data.ByteString.ByteString -> String byte_string_to_hex = concatMap (Text.Printf.printf "%02x") . Data.ByteString.unpack
prefix_md5 :: String -> IO String prefix_md5 filename = do let prefix_length = 1024 file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.hGet file prefix_length :: IO Data.ByteString.ByteString _ <- System.IO.hClose file let hasher = Crypto.Hash.MD5.init :: Crypto.Hash.MD5.Ctx let hasher2 = Crypto.Hash.MD5.update hasher data_read :: Crypto.Hash.MD5.Ctx let binary_digest = Crypto.Hash.MD5.finalize hasher2 :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String return hex_digest :: IO String
full_md5 :: String -> IO String full_md5 filename = do file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.Lazy.hGetContents file :: IO Data.ByteString.Lazy.ByteString let binary_digest = Crypto.Hash.MD5.hashlazy data_read :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String -- Does this get closed for us later? -- strace shows the file getting closed without our explicit close. -- _ <- System.IO.hClose file return hex_digest :: IO String
It might be easier to view these at http://stromberg.dnsalias.org/svn/equivalence-classes/trunk/equivs3-haskell/ , so the line numbers are precise.
What is the deal?
Can anyone tell me what should be running through my head to fix this kind of problem on my own in the future?
Thanks!
-- Dan Stromberg

I read somewhere (probably Learn You a Haskell or Real-World Haskell) that
beginners should use a lot of type declarations, but perhaps that's not a
great idea after all.
Here's dph.hs without the type declarations and some abuses of do cleaned
up:
import Md5s
import Split0
import System.IO
get_filenames :: String -> [String]
-- Let's hope this doesn't give locale-related roundtrip problems.
get_filenames buffer = Split0.split0 '\0' buffer
do_prefix_hash :: String -> (IO String, String)
do_prefix_hash filename = let hash = Md5s.prefix_md5 filename
in (hash, filename)
tuple_to_string :: (String, String) -> String
tuple_to_string (first, second) = (show first) ++ " " ++ (show second)
main :: IO ()
main = do
buffer <- (System.IO.hGetContents System.IO.stdin)
let filenames = (get_filenames buffer)
io_hash_tuples <- map do_prefix_hash filenames
hash_tuples <- sequence io_hash_tuples
let strings = map tuple_to_string hash_tuples
mapM_ putStrLn strings
The (far fewer) errors I get now are:
dph.hs:21:23:
Couldn't match type `[]' with `IO'
Expected type: IO (IO String, String)
Actual type: [(IO String, String)]
In the return type of a call of `map'
In a stmt of a 'do' block:
io_hash_tuples <- map do_prefix_hash filenames
In the expression:
do { buffer <- (hGetContents stdin);
let filenames = (get_filenames buffer);
io_hash_tuples <- map do_prefix_hash filenames;
hash_tuples <- sequence io_hash_tuples;
.... }
dph.hs:22:29:
Couldn't match expected type `[IO (String, String)]'
with actual type `(IO String, String)'
In the first argument of `sequence', namely `io_hash_tuples'
In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples
In the expression:
do { buffer <- (hGetContents stdin);
let filenames = (get_filenames buffer);
io_hash_tuples <- map do_prefix_hash filenames;
hash_tuples <- sequence io_hash_tuples;
.... }
I'm continuing to study Learn You a Haskell, though I'd kinda like to
continue coding on this project in parallel.
On Tue, Dec 1, 2015 at 7:47 PM, Simon Jakobi
Hi Dan,
I'm having a hard time understanding those error messages too. It seems to me that part of the problem is that GHC is confused by some incorrect type annotations of yours.
I suggest that you delete or at least comment out your own type annotations and then either work with the hopefully simpler error-messages from GHC or use the `:load` and `:type` commands in ghci to discover the inferred types for your functions.
Depending on how close the inferred type is to the intended type, you may have to adjust the definitions.
Also note that you sometimes incorrectly and unnecessarily use do-notation in "non-monadic"/plain functions, for example in tuple_to_string and get_filenames.
You could also consider following a book or a course until you feel more comfortable trying things on your own: Take a look at learnyouahaskell.com or github.com/bitemyapp/learnhaskell.
Good luck! Simon
2015-12-02 1:12 GMT+01:00, Dan Stromberg
: I'm continuing my now-and-then exploration of Haskell.
I'm getting a new crop of type errors that I'm pulling my hair out over.
The errors I'm getting are:
$ make below cmd output started 2015 Tue Dec 01 04:05:17 PM PST # --make will go out and find what to build ghc -Wall --make -o dph dph.hs Split0.hs [1 of 3] Compiling Split0 ( Split0.hs, Split0.o ) [2 of 3] Compiling Md5s ( Md5s.hs, Md5s.o ) [3 of 3] Compiling Main ( dph.hs, dph.o )
dph.hs:13:13: Couldn't match type `IO' with `(,) (IO String)' Expected type: (IO String, String) Actual type: IO String In a stmt of a 'do' block: hash <- prefix_md5 filename :: IO String In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) } In an equation for `do_prefix_hash': do_prefix_hash filename = do { hash <- prefix_md5 filename :: IO String; (hash, filename) }
dph.hs:14:6: Couldn't match type `[Char]' with `IO String' Expected type: IO String Actual type: String In the expression: hash In a stmt of a 'do' block: (hash, filename) In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) }
dph.hs:24:23: Couldn't match type `[]' with `IO' Expected type: IO (IO String, String) Actual type: [(IO String, String)] In a stmt of a 'do' block: io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... }
dph.hs:25:20: Couldn't match type `[a0]' with `(String, String)' Expected type: [(String, String)] Actual type: [[a0]] In the return type of a call of `sequence' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... }
dph.hs:25:20: Couldn't match type `[]' with `IO' Expected type: IO (String, String) Actual type: [(String, String)] In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... }
dph.hs:25:29: Couldn't match expected type `[[a0]]' with actual type `(IO String, String)' In the first argument of `sequence', namely `io_hash_tuples' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... }
dph.hs:26:39: Couldn't match expected type `[(String, String)]' with actual type `(String, String)' In the second argument of `map', namely `hash_tuples' In the expression: map tuple_to_string hash_tuples :: [String] In an equation for `strings': strings = map tuple_to_string hash_tuples :: [String] make: *** [dph] Error 1 above cmd output done 2015 Tue Dec 01 04:05:18 PM PST
dph.hs looks like: import Md5s import Split0 import System.IO
get_filenames :: String -> [String] get_filenames buffer = do -- Let's hope this doesn't give locale-related roundtrip problems. Split0.split0 '\0' buffer :: [String]
do_prefix_hash :: String -> (IO String, String) do_prefix_hash filename = do hash <- Md5s.prefix_md5 filename :: (IO String) (hash, filename)
tuple_to_string :: (String, String) -> String tuple_to_string (first, second) = do (show first) ++ " " ++ (show second)
main :: IO () main = do buffer <- (System.IO.hGetContents System.IO.stdin) :: IO String let filenames = (get_filenames buffer) :: [String] io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] hash_tuples <- sequence io_hash_tuples :: [(String, String)] let strings = map tuple_to_string hash_tuples :: [String] mapM_ putStrLn strings
And Md5s.hs looks like: module Md5s where
import qualified System.IO import qualified Text.Printf -- cabal install cryptohash import qualified Crypto.Hash.MD5 import qualified Data.ByteString import qualified Data.ByteString.Lazy
--
http://stackoverflow.com/questions/10099921/efficiently-turn-a-bytestring-in...
byte_string_to_hex :: Data.ByteString.ByteString -> String byte_string_to_hex = concatMap (Text.Printf.printf "%02x") . Data.ByteString.unpack
prefix_md5 :: String -> IO String prefix_md5 filename = do let prefix_length = 1024 file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.hGet file prefix_length :: IO Data.ByteString.ByteString _ <- System.IO.hClose file let hasher = Crypto.Hash.MD5.init :: Crypto.Hash.MD5.Ctx let hasher2 = Crypto.Hash.MD5.update hasher data_read :: Crypto.Hash.MD5.Ctx let binary_digest = Crypto.Hash.MD5.finalize hasher2 :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String return hex_digest :: IO String
full_md5 :: String -> IO String full_md5 filename = do file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.Lazy.hGetContents file :: IO Data.ByteString.Lazy.ByteString let binary_digest = Crypto.Hash.MD5.hashlazy data_read :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String -- Does this get closed for us later? -- strace shows the file getting closed without our explicit close. -- _ <- System.IO.hClose file return hex_digest :: IO String
It might be easier to view these at
http://stromberg.dnsalias.org/svn/equivalence-classes/trunk/equivs3-haskell/
, so the line numbers are precise.
What is the deal?
Can anyone tell me what should be running through my head to fix this kind of problem on my own in the future?
Thanks!
-- Dan Stromberg
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Dan Stromberg

Hi Dan,
io_hash_tuples <- map do_prefix_hash filenames
You're operating inside of the IO monad, so anything on the right hand side of the `<-` has to have the type `IO`. If you're looking up the type of `map`, you will see that it doesn't return the right type. Most likely you just wanted to create a binding like: let io_hash_tuples = map do_prefix_hash filenames
hash_tuples <- sequence io_hash_tuples
`io_hash_tuples` is of type `[(IO String, String)]`, but `sequence` expects a `[IO a]`. Looking at your code, it's easier not to put the `IO String` computation of the hash into a tuple, but first compute all hashes: hashes <- sequence (map Md5s.prefix_md5 filenames) And if you want the hash and the filename grouped in a tuple: zip filenames hashes Greetings, Daniel

Hi. On Fri, Dec 4, 2015 at 12:35 AM, Daniel Trstenjak < daniel.trstenjak@gmail.com> wrote:
Looking at your code, it's easier not to put the `IO String` computation of the hash into a tuple, but first compute all hashes:
hashes <- sequence (map Md5s.prefix_md5 filenames)
And if you want the hash and the filename grouped in a tuple:
zip filenames hashes
What if I want to be able to deal gracefully with files that aren't readable, whether due to permissions issues or I/O errors? I agree that zip'ing is easier, but is it as robust? Thanks. -- Dan Stromberg

On Thu, Dec 10, 2015 at 4:19 AM, Dan Stromberg
readable, whether due to permissions issues or I/O errors? I agree that zip'ing is easier, but is it as robust?
Making sense of this question requires an apples-to-apples comparison. Observe that the original code doesn't deal with read errors either. In fact, the replies in this thread have done only two things. They've fixed the typecheck error. And they've offered idiomatic -- but semantically identical -- rewritings that read-fault in the exact same way as the original code. -- Kim-Ee

On Wed, Dec 9, 2015 at 4:57 PM, Kim-Ee Yeoh
On Thu, Dec 10, 2015 at 4:19 AM, Dan Stromberg
wrote: What if I want to be able to deal gracefully with files that aren't
readable, whether due to permissions issues or I/O errors? I agree that zip'ing is easier, but is it as robust?
Making sense of this question requires an apples-to-apples comparison. Observe that the original code doesn't deal with read errors either.
In fact, the replies in this thread have done only two things.
They've fixed the typecheck error.
And they've offered idiomatic -- but semantically identical -- rewritings that read-fault in the exact same way as the original code.
Yes, sure. My thought was that going over the list of filenames+sizes and adding prefix hashes where available, would be easier to make robust, than attempting to get prefix hashes for all and zipping the results. Is that not correct? Should I use a Maybe to deal with files that don't hash, so there will always be a one-to-one correspondence, allowing a zip? Thanks. -- Dan Stromberg

On Thu, Dec 10, 2015 at 8:35 AM, Dan Stromberg
prefix hashes where available, would be easier to make robust, than attempting to get prefix hashes for all and zipping the results.
Is that not correct?
No, that's not correct. And the reason is that zipping is a pure computation (to use the jargon). The errors can only come from file I/O. Tupling incrementally and tupling all at once (namely, zipping) result in identical values. Neither can fault unless the code goes out of its way into un-idiomatic, un-Haskelly territory.
Should I use a Maybe to deal with files that don't hash, so there will always be a one-to-one correspondence, allowing a zip?
Yes, to be precise, instead of a function :: FilePath -> IO String that could possibly throw IO exceptions, you'd write a FilePath -> IO (Maybe String) that's exception-free because it catches them. Thanks.
Anytime.
-- Dan Stromberg
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

On 4 December 2015 at 08:58, Dan Stromberg
I read somewhere (probably Learn You a Haskell or Real-World Haskell) that beginners should use a lot of type declarations, but perhaps that's not a great idea after all.
I agree. Excessive type signatures makes code harder to read, less "beautiful" (yes, Haskell code can be beautiful), and increases the surface area for bugs, typos and other mistakes. Type inference in Haskell is an excellent aid for beginners and pros alike, and beginners should learn to feel comfortable with it. Haskell style commentators generally agree that type signatures for top-level bindings are a good thing, but they should be used sparingly everywhere else. If you are using GHC, I have also found that temporarily removing some top-level type signatures and compiling with -Wall may give you some new insights into your functions. GHC warns you about the missing signatures and tells you what it infers, which may be more general/polymorphic than the type you originally entered. This can help greatly to spot polymorphic functions, reduce code duplication and find places where you can use folds and traversals from the standard library (Data.Foldable, Data.Traversable, etc.). -- Thomas Koster

You seem to be having some problems understanding how Monads and do
notation work.
do_prefix_hash :: String -> (IO String, String)
do_prefix_hash filename = do
hash <- Md5s.prefix_md5 filename :: (IO String)
(hash, filename)
The above is ill typed. When you open with a do, from that point on the
type will be Monad m => String -> m Something. But what you intended to
return is a tuple, which is not an instance of monad. Don't use do in this
case, just return a tuple.
do_prefix_hash :: String -> (IO String, String)
do_prefix_hash filename = (Md5s.prefix_md5 filename, filename)
Just look closely at what the error is telling you. Is it expecting a type
that you told it it returns but it is detecting that your code would return
something else.
On Tue, Dec 1, 2015 at 7:12 PM, Dan Stromberg
I'm continuing my now-and-then exploration of Haskell.
I'm getting a new crop of type errors that I'm pulling my hair out over.
The errors I'm getting are:
$ make below cmd output started 2015 Tue Dec 01 04:05:17 PM PST # --make will go out and find what to build ghc -Wall --make -o dph dph.hs Split0.hs [1 of 3] Compiling Split0 ( Split0.hs, Split0.o ) [2 of 3] Compiling Md5s ( Md5s.hs, Md5s.o ) [3 of 3] Compiling Main ( dph.hs, dph.o )
dph.hs:13:13: Couldn't match type `IO' with `(,) (IO String)' Expected type: (IO String, String) Actual type: IO String In a stmt of a 'do' block: hash <- prefix_md5 filename :: IO String In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) } In an equation for `do_prefix_hash': do_prefix_hash filename = do { hash <- prefix_md5 filename :: IO String; (hash, filename) }
dph.hs:14:6: Couldn't match type `[Char]' with `IO String' Expected type: IO String Actual type: String In the expression: hash In a stmt of a 'do' block: (hash, filename) In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) }
dph.hs:24:23: Couldn't match type `[]' with `IO' Expected type: IO (IO String, String) Actual type: [(IO String, String)] In a stmt of a 'do' block: io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... }
dph.hs:25:20: Couldn't match type `[a0]' with `(String, String)' Expected type: [(String, String)] Actual type: [[a0]] In the return type of a call of `sequence' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... }
dph.hs:25:20: Couldn't match type `[]' with `IO' Expected type: IO (String, String) Actual type: [(String, String)] In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... }
dph.hs:25:29: Couldn't match expected type `[[a0]]' with actual type `(IO String, String)' In the first argument of `sequence', namely `io_hash_tuples' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... }
dph.hs:26:39: Couldn't match expected type `[(String, String)]' with actual type `(String, String)' In the second argument of `map', namely `hash_tuples' In the expression: map tuple_to_string hash_tuples :: [String] In an equation for `strings': strings = map tuple_to_string hash_tuples :: [String] make: *** [dph] Error 1 above cmd output done 2015 Tue Dec 01 04:05:18 PM PST
dph.hs looks like: import Md5s import Split0 import System.IO
get_filenames :: String -> [String] get_filenames buffer = do -- Let's hope this doesn't give locale-related roundtrip problems. Split0.split0 '\0' buffer :: [String]
do_prefix_hash :: String -> (IO String, String) do_prefix_hash filename = do hash <- Md5s.prefix_md5 filename :: (IO String) (hash, filename)
tuple_to_string :: (String, String) -> String tuple_to_string (first, second) = do (show first) ++ " " ++ (show second)
main :: IO () main = do buffer <- (System.IO.hGetContents System.IO.stdin) :: IO String let filenames = (get_filenames buffer) :: [String] io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] hash_tuples <- sequence io_hash_tuples :: [(String, String)] let strings = map tuple_to_string hash_tuples :: [String] mapM_ putStrLn strings
And Md5s.hs looks like: module Md5s where
import qualified System.IO import qualified Text.Printf -- cabal install cryptohash import qualified Crypto.Hash.MD5 import qualified Data.ByteString import qualified Data.ByteString.Lazy
-- http://stackoverflow.com/questions/10099921/efficiently-turn-a-bytestring-in... byte_string_to_hex :: Data.ByteString.ByteString -> String byte_string_to_hex = concatMap (Text.Printf.printf "%02x") . Data.ByteString.unpack
prefix_md5 :: String -> IO String prefix_md5 filename = do let prefix_length = 1024 file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.hGet file prefix_length :: IO Data.ByteString.ByteString _ <- System.IO.hClose file let hasher = Crypto.Hash.MD5.init :: Crypto.Hash.MD5.Ctx let hasher2 = Crypto.Hash.MD5.update hasher data_read :: Crypto.Hash.MD5.Ctx let binary_digest = Crypto.Hash.MD5.finalize hasher2 :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String return hex_digest :: IO String
full_md5 :: String -> IO String full_md5 filename = do file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.Lazy.hGetContents file :: IO Data.ByteString.Lazy.ByteString let binary_digest = Crypto.Hash.MD5.hashlazy data_read :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String -- Does this get closed for us later? -- strace shows the file getting closed without our explicit close. -- _ <- System.IO.hClose file return hex_digest :: IO String
It might be easier to view these at http://stromberg.dnsalias.org/svn/equivalence-classes/trunk/equivs3-haskell/ , so the line numbers are precise.
What is the deal?
Can anyone tell me what should be running through my head to fix this kind of problem on my own in the future?
Thanks!
-- Dan Stromberg
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Thank you!
You're correct; I had been thinking of do notation as a "multistatement"
thing rather than as a monad thing.
On Wed, Dec 2, 2015 at 5:05 AM, David McBride
You seem to be having some problems understanding how Monads and do notation work.
do_prefix_hash :: String -> (IO String, String) do_prefix_hash filename = do hash <- Md5s.prefix_md5 filename :: (IO String) (hash, filename)
The above is ill typed. When you open with a do, from that point on the type will be Monad m => String -> m Something. But what you intended to return is a tuple, which is not an instance of monad. Don't use do in this case, just return a tuple.
do_prefix_hash :: String -> (IO String, String) do_prefix_hash filename = (Md5s.prefix_md5 filename, filename)
Just look closely at what the error is telling you. Is it expecting a type that you told it it returns but it is detecting that your code would return something else.
On Tue, Dec 1, 2015 at 7:12 PM, Dan Stromberg
wrote: I'm continuing my now-and-then exploration of Haskell.
I'm getting a new crop of type errors that I'm pulling my hair out over.
The errors I'm getting are:
$ make below cmd output started 2015 Tue Dec 01 04:05:17 PM PST # --make will go out and find what to build ghc -Wall --make -o dph dph.hs Split0.hs [1 of 3] Compiling Split0 ( Split0.hs, Split0.o ) [2 of 3] Compiling Md5s ( Md5s.hs, Md5s.o ) [3 of 3] Compiling Main ( dph.hs, dph.o )
dph.hs:13:13: Couldn't match type `IO' with `(,) (IO String)' Expected type: (IO String, String) Actual type: IO String In a stmt of a 'do' block: hash <- prefix_md5 filename :: IO String In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) } In an equation for `do_prefix_hash': do_prefix_hash filename = do { hash <- prefix_md5 filename :: IO String; (hash, filename) }
dph.hs:14:6: Couldn't match type `[Char]' with `IO String' Expected type: IO String Actual type: String In the expression: hash In a stmt of a 'do' block: (hash, filename) In the expression: do { hash <- prefix_md5 filename :: IO String; (hash, filename) }
dph.hs:24:23: Couldn't match type `[]' with `IO' Expected type: IO (IO String, String) Actual type: [(IO String, String)] In a stmt of a 'do' block: io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... }
dph.hs:25:20: Couldn't match type `[a0]' with `(String, String)' Expected type: [(String, String)] Actual type: [[a0]] In the return type of a call of `sequence' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... }
dph.hs:25:20: Couldn't match type `[]' with `IO' Expected type: IO (String, String) Actual type: [(String, String)] In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... } In an equation for `main': main = do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; .... }
dph.hs:25:29: Couldn't match expected type `[[a0]]' with actual type `(IO String, String)' In the first argument of `sequence', namely `io_hash_tuples' In a stmt of a 'do' block: hash_tuples <- sequence io_hash_tuples :: [(String, String)] In the expression: do { buffer <- (hGetContents stdin) :: IO String; let filenames = ...; io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)]; hash_tuples <- sequence io_hash_tuples :: [(String, String)]; .... }
dph.hs:26:39: Couldn't match expected type `[(String, String)]' with actual type `(String, String)' In the second argument of `map', namely `hash_tuples' In the expression: map tuple_to_string hash_tuples :: [String] In an equation for `strings': strings = map tuple_to_string hash_tuples :: [String] make: *** [dph] Error 1 above cmd output done 2015 Tue Dec 01 04:05:18 PM PST
dph.hs looks like: import Md5s import Split0 import System.IO
get_filenames :: String -> [String] get_filenames buffer = do -- Let's hope this doesn't give locale-related roundtrip problems. Split0.split0 '\0' buffer :: [String]
do_prefix_hash :: String -> (IO String, String) do_prefix_hash filename = do hash <- Md5s.prefix_md5 filename :: (IO String) (hash, filename)
tuple_to_string :: (String, String) -> String tuple_to_string (first, second) = do (show first) ++ " " ++ (show second)
main :: IO () main = do buffer <- (System.IO.hGetContents System.IO.stdin) :: IO String let filenames = (get_filenames buffer) :: [String] io_hash_tuples <- map do_prefix_hash filenames :: [(IO String, String)] hash_tuples <- sequence io_hash_tuples :: [(String, String)] let strings = map tuple_to_string hash_tuples :: [String] mapM_ putStrLn strings
And Md5s.hs looks like: module Md5s where
import qualified System.IO import qualified Text.Printf -- cabal install cryptohash import qualified Crypto.Hash.MD5 import qualified Data.ByteString import qualified Data.ByteString.Lazy
-- http://stackoverflow.com/questions/10099921/efficiently-turn-a-bytestring-in... byte_string_to_hex :: Data.ByteString.ByteString -> String byte_string_to_hex = concatMap (Text.Printf.printf "%02x") . Data.ByteString.unpack
prefix_md5 :: String -> IO String prefix_md5 filename = do let prefix_length = 1024 file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.hGet file prefix_length :: IO Data.ByteString.ByteString _ <- System.IO.hClose file let hasher = Crypto.Hash.MD5.init :: Crypto.Hash.MD5.Ctx let hasher2 = Crypto.Hash.MD5.update hasher data_read :: Crypto.Hash.MD5.Ctx let binary_digest = Crypto.Hash.MD5.finalize hasher2 :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String return hex_digest :: IO String
full_md5 :: String -> IO String full_md5 filename = do file <- System.IO.openBinaryFile filename System.IO.ReadMode :: IO System.IO.Handle data_read <- Data.ByteString.Lazy.hGetContents file :: IO Data.ByteString.Lazy.ByteString let binary_digest = Crypto.Hash.MD5.hashlazy data_read :: Data.ByteString.ByteString let hex_digest = byte_string_to_hex binary_digest :: String -- Does this get closed for us later? -- strace shows the file getting closed without our explicit close. -- _ <- System.IO.hClose file return hex_digest :: IO String
It might be easier to view these at http://stromberg.dnsalias.org/svn/equivalence-classes/trunk/equivs3-haskell/ , so the line numbers are precise.
What is the deal?
Can anyone tell me what should be running through my head to fix this kind of problem on my own in the future?
Thanks!
-- Dan Stromberg
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Dan Stromberg
participants (6)
-
Dan Stromberg
-
Daniel Trstenjak
-
David McBride
-
Kim-Ee Yeoh
-
Simon Jakobi
-
Thomas Koster