Re: [Haskell-cafe] Re: [Haskell] ANN: HLint 1.0

2008-12-20 Thread Niklas Broberg
> It seems like the line numbers could be a bit more accurate:
>
> ./Network/Yogurt/IO.hs:54:3: Use liftM
> Found:
>  rec >>= return . (c :)
> Why not:
>  liftM (c :) rec
>
> Where the code is:
>
> 50 -- Waits for input, but once the first character is read, waits
> 51 -- no longer than the specified number of ms before giving up.
> 52 hGetImpatientLine :: Handle -> Int -> IO String
> 53 hGetImpatientLine h patience = rec where
> 54   rec = do
> 55 c <- hGetChar h
> 56 if c == '\n'
> 57   then return [c]
> 58   else do
> 59 b <- hWaitForInput h patience
> 60 if b
> 61   then rec >>= return . (c:)
> 62   else return [c]
>
> I imagine it could have told me to look at line 61 right away.

You can blame HSE in this case, it only stores line numbers for
certain constructs, and expressions are not among them. The closest
predictable construct for this case is the RHS of the function
definition, which is why you get line 54. This is something I hope to
improve in HSE over time.

Cheers,

/Niklas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANN: HLint 1.0

2008-12-20 Thread Niklas Broberg
> . some parser errors I encountered: import Data.Generics hiding ((:*:))
> type instance Rep Id x = x

The first is due to a bug in HSE which I've now fixed, thanks a lot
for reporting! The second is parsed just fine by HSE so I don't know
what's up there.

Cheers,

/Niklas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANN: HLint 1.0

2008-12-20 Thread Martijn van Steenbergen

Hi Neil,

Another question:

Darcs/Commands/Optimize.lhs:110:1: Use isPrefixOf, and then remove the 
(==) test

Found:
take 4 (just_name pinfo) == "TAG "
Why not:
(4 == length "TAG ") && ("TAG " `isPrefixOf` just_name pinfo)

I assume the (==) referred to in the name of the fix is the one in the 
suggestion. Why doesn't the suggestion come with the check removed? I.e.:


Why not:
("TAG " `isPrefixOf` just_name pinfo)

Thanks,

Martijn.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANN: HLint 1.0

2008-12-20 Thread Niklas Broberg
Hi Gwern,

> 2) I think I found a parsing bug. One line in Mueval/Interpreter.hs runs:
>
>> fmap (take n exceptionMsg ++) $ render' (n-length exceptionMsg) s
>
> which gives the error:
>
>> Mueval/Interpreter.hs:145:59: Parse failure, Parse error
>> No relevant suggestions
>
> Adding spaces between 'n' and 'length', so it reads:
>
>> fmap (take n exceptionMsg ++) $ render' (n - length exceptionMsg) s
>
> lets hlint parse and suggest for it.

This is clearly a HSE bug, and seeing your example I know exactly the
oversight I've made. Unfortunately I don't see immediately how to fix
it so I'll have to think on it for a while. Thanks for reporting it!

Cheers,

/Niklas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANN: HLint 1.0

2008-12-22 Thread Claus Reinke

Well, sort of. Ok, we can parse that. Let's assume a variable x holds
the output of :show modules as a String. We call lines on it, then map
words on it, do a !! 2 on it, and we get ["Util.hs,", "Recorder.hs,",
"Game.hs,", "Monadius.hs,", "Demo.hs,"]. Chuck in a map (filter (\=
',')), and we get a good list. We can turn the list into a string
suitable for hlint with a quick unwords.

So our long sought after command becomes ':def hoogle (\_ -> return $
":! " ++ (unwords $ map (filter (\= ',')) $ (map words $ lines x) !!
2))'. But wait, how do we get 'x'? How do we call :show modules inside
a Haskell expression? I have carefully looked over
http://haskell.org/haskellwiki/GHC/GHCi#Using_GHCi and
http://www.haskell.org/ghc/docs/latest/html/users_guide/ghci-commands.html
and my conclusion is that you can't. You can't do a let x = :show
modules, there is no function which will take ":show modules", and so
on. :functions can accept Haskell output, but it's a one-way barrier.
It's no good writing Haskell functions which need information from the
:functions.


The first url includes a link to a .ghci mini-tutorial (section 4) that, 
among other things, implements 


   :redir-- execute , redirecting stdout to 

Happy Holidays!-)
Claus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANN: HLint 1.0

2008-12-23 Thread Claus Reinke

Well, sort of. Ok, we can parse that. Let's assume a variable x holds
the output of :show modules as a String. We call lines on it, then map
words on it, do a !! 2 on it, and we get ["Util.hs,", "Recorder.hs,",
"Game.hs,", "Monadius.hs,", "Demo.hs,"]. Chuck in a map (filter (\=
',')), and we get a good list. We can turn the list into a string
suitable for hlint with a quick unwords.

So our long sought after command becomes ':def hoogle (\_ -> return $
":! " ++ (unwords $ map (filter (\= ',')) $ (map words $ lines x) !!
2))'. But wait, how do we get 'x'? How do we call :show modules inside
a Haskell expression? 



The first url includes a link to a .ghci mini-tutorial (section 4) that,
among other things, implements
  :redir-- execute , redirecting stdout to 



Perhaps my cold has fogged my head too much, but I'm not sure how
:redir would help. I could do :redir var "hlint .", but that's as
unsatisfactory as :! "hlint ."


You were asking about getting the output of ':show modules' into a
variable 'x', so that you can process it further. ':redir x :show modules'
should do just that. There is another example command for implementing
':edit' this way (by now a native ghci command).

Claus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANN: HLint 1.0

2008-12-27 Thread Claus Reinke

You were asking about getting the output of ':show modules' into a
variable 'x', so that you can process it further. ':redir x :show modules'
should do just that. There is another example command for implementing
':edit' this way (by now a native ghci command).


I think I'm seeing your meaning. So that brings me up to this:

let hlint _ = return $ unlines [":redir hlintvar1 :show modules", "let
hlintvar2 = map (fst . break (==',') . drop 2 . snd . break (== '('))
$ lines hlintvar1", ":! hlint (concat $ intersperse \" \" hlintvar2"]
:def hlint hlint

This doesn't work. The issue is that :! is weird; for it to work, one
need to pass each argument as a separate string, and it won't evaluate
a variable.


It isn't just ':!', quoting/variable interpretation is generally rather
uncomfortable in GHCi scripting (so much so that I originally submitted
output redirection as a patch before figuring out that it could be done 
without patching GHCi - that surprise find was the motivation for posting
my findings as an email). Have you tried reading the mini tutorial that 
I keep mentioning and which the "using GHCi" page is pointing to? 
Here's the direct link:


http://www.haskell.org/pipermail/haskell-cafe/2007-September/032260.html

The discussion is rather brief, but that tutorial has several examples
that need to work around issues like this, ranging from simple but
tedious construct-the-command-string to extra levels of ':cmd' in
order to get extra levels of interpretation (when you need to construct
a command string from a variable that will be bound via a constructed
command string (see the definitions of ':find', ':le' or ':b(rowse)' - the 
latter is an example of using the info from ':show modules').


Claus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANN: HLint 1.0

2008-12-27 Thread Gwern Branwen
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA512

On Fri, Dec 26, 2008 at 5:22 PM, Claus Reinke  wrote:
>>> You were asking about getting the output of ':show modules' into a
>>> variable 'x', so that you can process it further. ':redir x :show
>>> modules'
>>> should do just that. There is another example command for implementing
>>> ':edit' this way (by now a native ghci command).
>>
>> I think I'm seeing your meaning. So that brings me up to this:
>>
>> let hlint _ = return $ unlines [":redir hlintvar1 :show modules", "let
>> hlintvar2 = map (fst . break (==',') . drop 2 . snd . break (== '('))
>> $ lines hlintvar1", ":! hlint (concat $ intersperse \" \" hlintvar2"]
>> :def hlint hlint
>>
>> This doesn't work. The issue is that :! is weird; for it to work, one
>> need to pass each argument as a separate string, and it won't evaluate
>> a variable.
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.9 (GNU/Linux)

iEYEAREKAAYFAklW2+4ACgkQvpDo5Pfl1oJlnACdGLV9HyfyyBu3goNG9dTqC0ha
dFQAn0kzcIcMhSQ4tniurBTZHmQ6zBhC
=YVir
-END PGP SIGNATURE-

>
> It isn't just ':!', quoting/variable interpretation is generally rather
> uncomfortable in GHCi scripting (so much so that I originally submitted
> output redirection as a patch before figuring out that it could be done
> without patching GHCi - that surprise find was the motivation for posting
> my findings as an email).

No kidding. I find ghci scripting pretty awkward. Maybe things would
be better if all the :commands had exposed and easily used Haskell
function equivalents so you could stay on the Haskell level and only
deal with the :commands at the last second.

> Have you tried reading the mini tutorial that I
> keep mentioning and which the "using GHCi" page is pointing to? Here's the
> direct link:
>
> http://www.haskell.org/pipermail/haskell-cafe/2007-September/032260.html
>
> The discussion is rather brief, but that tutorial has several examples
> that need to work around issues like this, ranging from simple but
> tedious construct-the-command-string to extra levels of ':cmd' in
> order to get extra levels of interpretation (when you need to construct
> a command string from a variable that will be bound via a constructed
> command string (see the definitions of ':find', ':le' or ':b(rowse)' - the
> latter is an example of using the info from ':show modules').
>
> Claus

Yes, I have read all that, but I find it difficult to understand. In
some places, there are more levels of quoting and indirection than I
can keep track of (I swear in one place the code must've been 4 levels
deep). But on re-reading, I think :cmd solves my problem. So my
solution looks like this:

let hlint _ = return $ unlines [":redir hlintvar1 :show modules", "let
hlintvar2 = map (fst . break (==',') . drop 2 . snd . br
eak (== '(')) $ lines hlintvar1", ":cmd return (\":! hlint \" ++
(concat $ intersperse \" \" hlintvar2))"]
:def hlint hlint

(:redir obviously coming from your .ghci code.)

This doesn't integrate with :load or anything, but it does let you
just blindly go ':hlint' and get the suggestions.

--
gwern
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe