[Haskell] Re: Going nuts

Alexandre Weffort Thenorio alethenorio at home.se
Thu Apr 21 11:42:10 EDT 2005


Mostly appreciated. It sure fixed the problem. Now for another question

in outputline

outputLine keyno key orgFile = do
    --lineList <- getLines orgFile
    --orgLine <- head (drop 1 lineList)
    let part1 = getLeft keyno (orgFile!!1)
    let part2 = getRight keyno (orgFile!!1)
    let total = part1 ++ (map toUpper key) ++ part2 ++ "\n"
    newHexFile <- openFileEx "newint.hex" (BinaryMode WriteMode)
     hPutStrLn newHexFile (orgFile!!0 ++ "\n" ++ total ++ unlines (drop 2
orgFile))

How can I check whether keyno is either 1 or 0 and give an error that will
quit the program (or return to main and from there jump to catch) and if key
length is 16 returning error otherwise?

I mean probably a catch will do but I don't how to differentiate between the
errors and how to force the error.

Best Regards

Alex

----- Original Message ----- 
From: "Peter Davis" <pediddle at pediddle.net>
To: <haskell at haskell.org>
Sent: Thursday, April 21, 2005 4:51 AM
Subject: [Haskell] Re: Going nuts


On 2005-04-20 19:04:32 -0700, "Alexandre Weffort Thenorio"
<alethenorio at home.se> said:

> As usual a beginner in Haskell. Trying to write a simple program in haskel
> shown below
>
> [snip]
> getLeft :: String -> String -> String
> getRight :: String ->String -> String
>
> outputLine keyno key orgFile = do
>     part1 <- getLeft keyno orgFile
>     part2 <- getRight keyno orgFile
>     total <- part1 ++ (strUpper key) ++ part2 ++ "\n"
>
> [snip]
> And I keep getting the error
>
> changecode.hs:42:
>     Couldn't match `[a]' against `Char'
>         Expected type: [a]
>         Inferred type: Char
>     In the first argument of `(++)', namely `part1'
>     In a 'do' expression:
>         total <- part1 ++ ((strUpper key) ++ (part2 ++ "\n"))

You should be using:

  let part1 = getLeft keyno orgFile
  let part2 = getRight keyno orgFile
  let total = part1 ++ (strUpper key) ++ part2 ++ "\n"

The problem is that the "part1 <- ..." syntax is for extracting the
result from a monadic computation.  When you read from a file like
"hexFile <- readFile "file"", readFile is a computation in the IO
monad, and you extract hexFile from the monad.  The list [] type is
also a monad, and String is really [Char], so "part1 <- getLeft keyno
orgFile" implies that part1 is of type Char, which is a single element
extracted from the list of Chars returned by the monadic computation
(in the [] monad) "getLeft keyno orgFile".

That leads to the error you see.  part1's inferred type is Char, and
the ++ function expects a list of some type ([a]), which Char is
obviously not.

The "let" syntax binds a variable instead of extracting it from a
monadic computation, which is what you want for these three lines.

Hope that helps!

-- 
Peter Davis <pediddle at pediddle.net>
"Furthermore, I believe bacon prevents hair loss!"


_______________________________________________
Haskell mailing list
Haskell at haskell.org
http://www.haskell.org/mailman/listinfo/haskell




More information about the Haskell mailing list