Re: problems figuring out what the type system is telling me

2002-06-08 Thread John Hughes

On Fri, 7 Jun 2002, Chris Moline wrote:
 ...
 two. i have also read what the hell are monads and monads for the working
 haskell programmer. i still do not get what i am doing wrong.

 getDepends :: String - [String]
 getDepends p = do
 handle - openFile (portsDir ++ p ++ /+CONTENTS) ReadMode
 fetchDepends handle

 to my brain this takes a string, concatenates it with portsDir and
 +/CONTENTS, and passes it to openfile. openFile then returns a handle and
 this handle and passes it to fetchDepends. getDepends will return whatever
 fetchDepends returns, assuming openFile succeeds. however ghc says

 Phoebe.hs:19:
 Couldn't match `[]' against `IO'
 Expected type: [t]
 Inferred type: IO Handle
 In the application `openFile (portsDir ++ (p ++ /+CONTENTS))
  ReadMode'
 In a 'do' expression pattern binding:
 handle - openFile (portsDir ++ (p ++ /+CONTENTS)) ReadMode

 i do not know what this [t] is and i do not know why it is expected. my theory
 is it is being caused by something in fetchDepends.

[t] is a list type: GHC is expecting the call of openFile to return a list
(of t, but t is just a type variable so tells us nothing). Why is it
expecting a list? BECAUSE OF YOUR TYPE SIGNATURE!

You wrote a type signature specifying that getDepends (and fetchDepends,
for that matter), returns a list. You should have given the result an IO
type, since these functions do IO. I haven't checked, but probably the
type of getDepends should be

getDepends :: String - IO [String]

rather than the type you wrote. So your mistake is just forgetting to
include the monad in your type signature.

Now, the error message you got maybe isn't the very clearest, but it is
logical. Remember that the do syntax that you used in getDepends is
OVERLOADED -- it can be used with any monad, not just with IO. In
particular, it can be used with the list type, which is itself a monad.
For example, we could, if we wished, define the ordinary list map function
like this:

map :: (a-b) - [a] - [b]
map f xs = do x - xs
  return (f x)

That's an example of using do with the list monad. Of course, since the do
is working over lists, then when we write x - xs, the xs must also have a
list type. We have to be consistent, and use the same monad throughout the
do. This is just like when we use do to write an IO computation: in that
case, when we write x - f y or whatever, the f y has to have an IO type.

Now, in your code for getDepends, GHC sees your type signature and says
Aha! This function returns a list. So the do in the body must be working
over the list monad. In that case, when we see

handle - openFile...

then the openFile must have a list type. Oh dear, it's type isn't a list,
it's IO! Better complain that [] (the name of the list type, not
the empty list) doesn't match IO!

Hence the error message you got.

And now to a thorny and controversial question: should one write type
signatures, or not? In particular, what advice should one give less
experienced Haskell programmers?

In this case, your CODE is probably quite correct. If you hadn't written
the type signatures, then GHC would just have inferred the correct types
and everything would have worked. Good advice for you might be to leave
type signatures out, compile your code, and then look at the types that
functions actually get (using ghci). You can always paste the types back
into your code, and this way, they will be correct.

On the other hand, if you omit type signatures, then when you DO get a
type error it will be in terms of type variables and classes, rather than
types such as Int or String which you would probably be expecting. There
is a trade off here.

One way to approach it is to write type signatures, but when a definition
doesn't type check, remove the signature on that one and see whether it
then typechecks. If so, the definition is right, but your type signature
is wrong. Use ghci to find out the correct type signature, and insert it.

You also mentioned layout problems when you used if in a do. I'm assuming
you tried writing something like

do 
   if ... then ...
   else ...
   ...

If you write this, then because the else appears in the same column as the
if, it's taken to be the start of a new element in the do -- with a syntax
error as the result. You just have to indent the else further than the if.
I use an indentation like this:

do ...
   if ...
 then ...
 else ...
   ...

which lets GHC see that the entire if-then-else makes up just one element
in the enclosing do. This is a classic gotcha of the layout rule: the
first layout is quite natural, but you just can't write it.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: problems figuring out what the type system is telling me

2002-06-08 Thread Alastair Reid


John Hughes writes:
 One way to approach it is to write type signatures, but when a
 definition doesn't type check, remove the signature on that one and
 see whether it then typechecks. If so, the definition is right, but
 your type signature is wrong. Use ghci to find out the correct type
 signature, and insert it.

Another useful trick when chasing type errors is to stub out a few
functions or cases of functions with 'undefined'.  At first sight,
'undefined' is a fairly useless function since it always fails.  But
undefined has one great property: it's type is 'forall a. a' which
means you can use it absolutely anywhere.

Suppose I have 10 mutually recursive functions (e.g., an interpreter
for a language) and I'm chasing a type error.  I might comment out
the real definition of some of the functions and replace them with
definitions like:

  evalExpression :: whatever type it should have
  evalExpression = undefined
  {-
  real but possibly buggy definition goes here
  -}

or I might comment out just some cases of a function while I figure
out which branch is really causing the problem:

  evalExpression :: Env - Expr - Value
  evalExpression env (Int i) = IntValue i
  evalExpression env (Str s) = StringValue i
  evalExpression env (Apply f e) = undefined -- app (evalFunction env f) 
(evalExpression env e)
  evalExpression env (Var v) = undefined  -- fromJust (lookup env v)


-- 
Alastair Reid[EMAIL PROTECTED]http://www.cs.utah.edu/~reid/
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



problems figuring out what the type system is telling me

2002-06-07 Thread Chris Moline

hi. i am really stuck on this problem and i cant seem to figure it out and so 
i am posting this in the hopes someone will help me. i realize you prolly get 
this kind of question alot but the wiki and the papers i have been reading 
arent helping to clarify things.

i am trying to write a little utility to make it easier to get rid of ports on 
my machine. the function that is giving me trouble is getDepends. it takes the 
name of a port and opens the appropriate +CONTENTS file and returns the 
dependencies it finds.

here is the function and its helper.

getDepends :: String - [String]
getDepends p = do
handle - openFile (portsDir ++ p) ReadMode
fetchDepends handle

fetchDepends :: Handle - [String]
fetchDepends handle = do
l - hGetLine handle
e - hIsEOF handle
case (not e) of -- ifs keep giving indent errors so ill just use case
True -
case (matchRegex (mkRegex ^@pkgdep) l) of
Just [a] - [drop 8 l] ++ (fetchDepends handle)
_ - fetchDepends handle
False - 

here is ghci's error messages.

Compiling Pheobe   ( Phoebe.hs, interpreted )

Phoebe.hs:19:
Couldn't match `[]' against `IO'
Expected type: [t]
Inferred type: IO Handle
In the application `openFile (portsDir ++ p) ReadMode'
In a 'do' expression pattern binding:
handle - openFile (portsDir ++ p) ReadMode

Phoebe.hs:24:
Couldn't match `[]' against `IO'
Expected type: [t]
Inferred type: IO String
In the application `hGetLine handle'
In a 'do' expression pattern binding: l - hGetLine handle
Failed, modules loaded: none.

could someone be so kind as to explain what the problem is?

sincerly,
chris moline
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: problems figuring out what the type system is telling me

2002-06-07 Thread Hal Daume III

see http://haskell.org/wiki/wiki?ThatAnnoyingIoType and
http://haskell.org/wiki/wiki?UsingIo

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 7 Jun 2002, Chris Moline wrote:

 hi. i am really stuck on this problem and i cant seem to figure it out and so 
 i am posting this in the hopes someone will help me. i realize you prolly get 
 this kind of question alot but the wiki and the papers i have been reading 
 arent helping to clarify things.
 
 i am trying to write a little utility to make it easier to get rid of ports on 
 my machine. the function that is giving me trouble is getDepends. it takes the 
 name of a port and opens the appropriate +CONTENTS file and returns the 
 dependencies it finds.
 
 here is the function and its helper.
 
 getDepends :: String - [String]
 getDepends p = do
 handle - openFile (portsDir ++ p) ReadMode
 fetchDepends handle
 
 fetchDepends :: Handle - [String]
 fetchDepends handle = do
 l - hGetLine handle
 e - hIsEOF handle
 case (not e) of   -- ifs keep giving indent errors so ill just use case
 True -
 case (matchRegex (mkRegex ^@pkgdep) l) of
 Just [a] - [drop 8 l] ++ (fetchDepends handle)
 _ - fetchDepends handle
 False - 
 
 here is ghci's error messages.
 
 Compiling Pheobe   ( Phoebe.hs, interpreted )
 
 Phoebe.hs:19:
 Couldn't match `[]' against `IO'
 Expected type: [t]
 Inferred type: IO Handle
 In the application `openFile (portsDir ++ p) ReadMode'
 In a 'do' expression pattern binding:
 handle - openFile (portsDir ++ p) ReadMode
 
 Phoebe.hs:24:
 Couldn't match `[]' against `IO'
 Expected type: [t]
 Inferred type: IO String
 In the application `hGetLine handle'
 In a 'do' expression pattern binding: l - hGetLine handle
 Failed, modules loaded: none.
 
 could someone be so kind as to explain what the problem is?
 
 sincerly,
 chris moline
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: problems figuring out what the type system is telling me

2002-06-07 Thread Chris Moline

On Fri, Jun 07, 2002 at 09:54:16PM -0700, Hal Daume III wrote:
 see http://haskell.org/wiki/wiki?ThatAnnoyingIoType and
 http://haskell.org/wiki/wiki?UsingIo

my apologies. please assume that i am really stupid. i have already read those 
two. i have also read what the hell are monads and monads for the working 
haskell programmer. i still do not get what i am doing wrong.

getDepends :: String - [String]
getDepends p = do
handle - openFile (portsDir ++ p ++ /+CONTENTS) ReadMode
fetchDepends handle

to my brain this takes a string, concatenates it with portsDir and 
+/CONTENTS, and passes it to openfile. openFile then returns a handle and 
this handle and passes it to fetchDepends. getDepends will return whatever 
fetchDepends returns, assuming openFile succeeds. however ghc says

Phoebe.hs:19:
Couldn't match `[]' against `IO'
Expected type: [t]
Inferred type: IO Handle
In the application `openFile (portsDir ++ (p ++ /+CONTENTS))
 ReadMode'
In a 'do' expression pattern binding:
handle - openFile (portsDir ++ (p ++ /+CONTENTS)) ReadMode

i do not know what this [t] is and i do not know why it is expected. my theory 
is it is being caused by something in fetchDepends.

fetchDepends :: Handle - [String]
fetchDepends handle = do
l - hGetLine handle
e - hIsEOF handle
case (not e) of
True -
case (matchRegex (mkRegex ^@pkgdep) l) of
Just [a] - [drop 8 l] ++ (fetchDepends handle)
_ - fetchDepends handle
False - []

here ghc reports

Phoebe.hs:24:
Couldn't match `[]' against `IO'
Expected type: [t]
Inferred type: IO String
In the application `hGetLine handle'
In a 'do' expression pattern binding: l - hGetLine handle

i am thinking that this has something to do with l. but i cant think of 
anything beyond that.

here a couple of other attempts to show that i am trying and that i have no 
clue what i am doing.

-- put a return around everything that might need it
getDepends :: String - [String]
getDepends p = do
handle - openFile (portsDir ++ p ++ /+CONTENTS) ReadMode
return (fetchDepends handle)

fetchDepends :: Handle - [String]
fetchDepends handle = do
l - hGetLine handle
e - hIsEOF handle
case (not e) of
True -
case (matchRegex (mkRegex ^@pkgdep) l) of
Just _ - return ([drop 8 l] ++
(fetchDepends handle))
_ - return (fetchDepends handle)
False - return []

-- try making l into a string by show'ing it
getDepends :: String - [String]
getDepends p = do
handle - openFile (portsDir ++ p ++ /+CONTENTS) ReadMode
fetchDepends handle

fetchDepends :: Handle - [String]
fetchDepends handle = do
l - hGetLine handle
e - hIsEOF handle
case (not e) of
True -
case (matchRegex (mkRegex ^@pkgdep) (show l)) of
Just _ - [drop 8 (show l)] ++ (fetchDepends handle)
_ - fetchDepends handle
False - []

-- try removing the type declarations
getDepends p = do
handle - openFile (portsDir ++ p ++ /+CONTENTS) ReadMode
fetchDepends handle

fetchDepends handle = do
l - hGetLine handle
e - hIsEOF handle
case (not e) of
True -
case (matchRegex (mkRegex ^@pkgdep) l) of
Just _ - [drop 8 l] ++ (fetchDepends handle)
 _ - fetchDepends handle
False - []

Phoebe.hs:27:
Couldn't match `[[Char]]' against `IO [[Char]]'
Expected type: [[Char]]
Inferred type: IO [[Char]]
In the application `fetchDepends handle'
In the second argument of `(++)', namely `(fetchDepends handle)'
Failed, modules loaded: none.

ok. a different error message. it still makes no sense. i will try a couple 
more times before i finish this message.

-- try show'ing (fetchDepends handle)
getDepends p = do
handle - openFile (portsDir ++ p ++ /+CONTENTS) ReadMode
fetchDepends handle

fetchDepends handle = do
l - hGetLine handle
e - hIsEOF handle
case (not e) of
True -
case (matchRegex (mkRegex ^@pkgdep) l) of
Just _ - [drop 8 l] ++
(show (fetchDepends handle))
_ - fetchDepends handle
False - []

error message is

Phoebe.hs:27:
Couldn't match `IO' against `[]'
Expected type: IO t
Inferred type: [a]
In the application `(++) [drop 8 l] (show (fetchDepends handle))'
In a case