[Haskell-cafe] announce: hgdbmi (GDB/MI interface)

2008-03-30 Thread Evan Martin
Just in case someone else needed this, here you go:

GDB/MI lets programs drive GDB. It can be used, for example, by GDB
frontends. This module wraps attaching GDB to a process and parsing
the (surprisingly complicated) GDB/MI output.
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hgdbmi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] runInteractiveCommand dying uncatchably?

2008-03-01 Thread Evan Martin
If I run the following program, it never prints "done".  If I
uncomment the commented line, it does.

import Prelude hiding (catch)
import Control.Exception
import System.Process
import System.IO

demo = do
  putStrLn "starting"
  (inp,out,err,pid) <- runInteractiveCommand "nonesuchcommand"
  putStrLn "writing to in on bad command"
  hPutStr inp "whatever"
  -- putStr "flushing"
  hFlush inp `catch` \e -> do print e; return ()
  putStrLn "done"

main = demo `catch` \e -> do print e; return ()

On my machine the output is:
$ runhaskell test.hs
starting
writing to in on bad command
$

It appears to exit at the hFlush call.  (hClose has the same behavior.)
I find this surprising -- I'd expect, even if I'm using an API
incorrectly, to get an exception.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] parsing c

2008-02-24 Thread Evan Martin
I'd like to parse some C headers for a toy project.
It seems like c2hs probably has the functionality I want, but it's not
packaged up as a library.

So two questions: Is there an alternative C-parsing library?  Has
anyone looked into librarifying c2hs's parser?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] announce: (preliminary) dbus haskell bindings

2006-07-17 Thread Evan Martin

"D-Bus is a message bus system, a simple way for applications to talk
to one another." [1]
It's particularly popular on free software desktops (Gnome, KDE).
HDBus wraps the DBus APIs so your Haskell code can broadcast messages
and make calls to services.  For example, on my recent Ubuntu system,
these bindings are sufficient to pop up balloon-tip-style
notifications via a daemon I wasn't previously aware of.

Very preliminary code, so please let me know if you find it useful.
(Also, I don't know where it's appropriate to announce this, so please
direct me to other mailing lists.)

Home page: http://neugierig.org/software/hdbus/
Haddock: http://neugierig.org/software/hdbus/doc/
Repository browser:
http://neugierig.org/software/darcs/browse/?r=hdbus;a=summary

[1] http://www.freedesktop.org/wiki/Software/dbus
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] packaging modules with internal-only functions

2006-07-15 Thread Evan Martin

I'm writing an FFI bindings module, and one of the pieces from the
library I want to wrap is their "Error" type.


module Error where


To the user of the module, I'd like to only expose the nicely wrapped
interface:

data Error = Error String String
instance Typeable Error where ... -- for throwDyn


But within the module's implementation, I need to share some other,
internal-only functions:

type ErrorTag = ()
type ErrorP = Ptr ErrorTag
withErrorP :: (ErrorP -> IO a) -> IO a

Where withErrorP potentially throwDyns an Error, so it needs the first module.

What is the proper way to divide these up in terms of package exports?
The best options I can figure out are either to split these into
multiple modules, or to have my "Error" module export them and mark
them not to be documented by haddock...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Windows PowerShell "Monad"

2006-07-15 Thread Evan Martin

On 7/16/06, Chad Scherrer <[EMAIL PROTECTED]> wrote:

On 7/15/06, Krasimir Angelov <[EMAIL PROTECTED]> wrote:
> Mostly coincidence. It isn't a good choice for name, I think but the
> same is true for .NET. Each time when I am googling for .NET I receive
> lots of irrelevant results. The same will happen with Monad now.

It's not even a production release yet, and already the
mainstream-to-be is taking over the google results. Googling for
microsoft monad gives all powershell and no MS Research!


Try: [monad site:research.microsoft.com].
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Filtering on data constructors with TH

2006-06-01 Thread Evan Martin

On 6/1/06, Christophe Poucet <[EMAIL PROTECTED]> wrote:

That's why
today I have created an automated derivation for data constructor
filtering. As I started coding someone mentioned that something similar
can be done with list comprehensions, so I'm not certain about the scope
of usefulness, however personally I have found the need for this at
times.


data T = A Int | B String deriving Show
test1 = [A 3, B "hello", A 5]
test2 = [x | x@(A _) <- test1]

The key here is that pattern match failure in a monad calls fail:
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Afail
and fail in the List monad is [].
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-20 Thread Evan Martin

On 5/21/06, Evan Martin <[EMAIL PROTECTED]> wrote:

Thanks!  I had looked at using the lexeme parser before but it didn't
seem like you can make newlines significant.


Upon further consideration I realized that you can mix lexeme-based
parsers with "plain" parsers.  I think I've mostly figured this out.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] parsing machine-generated natural text

2006-05-20 Thread Evan Martin

On 5/21/06, Udo Stenzel <[EMAIL PROTECTED]> wrote:

do power
   colon
   integer
   reserved "Supply centers,"
   integer
   reserved "Units:"
   ((reserved "Builds" >> return id) <|>
(reserved "Disbands" >> return negate))
`ap` integer
   reserved "units." <|> reserved "unit."

Come on, it isn't nearly as bad as you make it sound.  Use the
combinators, they are far more powerful than ugly never-quite-correct
regexes.


Thanks!  I had looked at using the lexeme parser before but it didn't
seem like you can make newlines significant.  Here's the beginning of
the file, where it's not obvious to me how to distinguish elements in
the "::" section from the rest of the file.
 :: Judge: USDP  Game: dip  Variant: standard
 :: Deadline: F1901M Mon 20 Feb 2006 20:00 PST
 :: URL: http://www.diplom.org/dpjudge?game=dip

 Movement results for Fall of 1901.  (dip.F1901M)
I guess I could make "Movement" a reserved word?


Oh, and drop me a line when your Diplomacy bot is finished.


:)

It's actually just for rendering nicer maps of the game state.
http://neugierig.org/software/hsdip/mapview.html
(It's draggable, too.)

I was trying to do it with Firefox's SVG+XUL but it's terribly slow,
XUL isn't quite there yet, and doing a large app with JavaScript is
painful.
http://neugierig.org/software/darcs/xuldip/dip.xul  (no install
necessary; only works in Firefox)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] parsing machine-generated natural text

2006-05-19 Thread Evan Martin

For a toy project I want to parse the output of a program.  The
program runs on someone else's machine and mails me the results, so I
only have access to the output it generates,

Unfortunately, the output is intended to be human-readable, and this
makes parsing it a bit of a pain.  Here are some sample lines from its
output:

France: Army Marseilles SUPPORT Army Paris -> Burgundy.
Russia: Fleet St Petersburg (south coast) -> Gulf of Bothnia.
England: 4 Supply centers,  3 Units:  Builds   1 unit.
The next phase of 'dip' will be Movement for Fall of 1901.

I've been using Parsec and it's felt rather complicated.  For example,
a "location" is a series of words and possibly parenthesis, except if
the word is SUPPORT.  And that "Supply centers" line ends up being
code filled with stuff lie "char ':'; skipMany space".

I actually have a separate parser that's Javascript with a bunch of
regular expressions and it's far shorter than my Haskell one, which
makes sense as munging this sort of text feels to me more like a
regexp job than a careful parsing job.

I'm considering writing a preprocessing stage in Ruby or Perl that
munges those output lines into something a bit more
"machine-readable", but before I did that I thought I'd ask here if
anyone had any pointers, hints, or better ideas.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [newbie] processing large logs

2006-05-13 Thread Evan Martin

On 5/14/06, Eugene Crosser <[EMAIL PROTECTED]> wrote:

main = printMax . (foldr processLine empty) . lines =<< getContents
[snip]
The thing kinda works on small data sets, but if you feed it with
250,000 lines (1000 distinct), the process size grows to 200 Mb, and on
500,000 lines I get "*** Exception: stack overflow" (using runhaskell
from ghc 6.2.4).


To elaborate on Udo's point:
If you look at the definition of foldr you'll see where the stack
overflow is coming from:  foldr recurses all the way down to the end
of the list, so your stack gets 250k (or attempts 500k) entries deep
so it can process the last line in the file first, then unwinds.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: transactional cache

2006-05-12 Thread Evan Martin

On 5/13/06, Alberto G. Corona <[EMAIL PROTECTED]> wrote:

> notglobal = newIORef True
> main = do a <- notglobal
> b <- notglobal

Thanks. I got the poit more or less; Each invocation creates a new
IORef instance.


Another way of looking at this, that might be more instructive, is
that notglobal is defined to be the action of creating a new IO ref.
You can see that in its type:
 > :t newIORef True
 newIORef True :: IO (IORef Bool)
I read that type as "an IO operation that produces an IORef Bool when executed".

Then the code in main "executes" notglobal twice.

Another way of looking at this is that you can always substitute the
right side of an equals sign in for the left side.  If you do that on
this code this makes it plain that a and b will be different.
(unsafePerformIO breaks this substitution rule.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code review: efficiency question

2006-05-01 Thread Evan Martin

I remember reading a tutorial that pointed out that you can often
avoid explicit recusion in Haskell and instead use higher-level
operators.

For your code, I think
 drawModals = foldr (flip (>>)) (return ()) . map drawModal
works(?).

On 5/2/06, Brian Hulley <[EMAIL PROTECTED]> wrote:

Hi -
I started off writing the following piece of monadic code:

let
  drawModal :: Control -> ManagerM ()
  drawModal c = do -- details omitted

  -- Prolog style coding...
  drawModals :: [Control] -> ManagerM ()
  drawModals [] = return ()
  drawModals (c:cs) = do
   drawModals cs
   drawModal c
drawModals cs

then it struck me that I should have not bothered with drawModals and
instead should just have used:

mapM_ drawModal (reverse cs)

However, while this looks more elegant, it is less efficient?
In other words, how much optimization can one assume when writing Haskell
code?
I'm trying to get a rough idea so I can decide whether to write helper
functions such as drawModals in future or whether I should always just use
the most elegant code instead.

Any ideas?

Thanks, Brian.

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


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


Re: [Haskell-cafe] Newbie "Instance Of Floating Int" Error

2006-04-28 Thread Evan Martin
On 4/28/06, Aditya Siram <[EMAIL PROTECTED]> wrote:
> type Point = (Int,Int)
> distBetween :: Point -> Point -> Float
> >>ERROR - Type error in explicitly typed binding
> *** Term   : distBetween
> *** Type   : Point -> Point -> Int
> *** Does not match : Point -> Point -> Float
>
> distBetween :: Point -> Point -> Int
> >>Instance of Floating Int required for definition of distBetween

It's saying that you explicitly gave the function the type "Point ->
Point -> Int" but that it actually has "Point -> Point -> Int".

If you look at the type of sqrt:
  Prelude> :t sqrt
  sqrt :: (Floating a) => a -> a
You'll see that it returns a floating-point number.

(Also, a minor style point:  you should probably get in the habit of
putting a space between the "sqrt" and its arguments.  It'll make more
sense as you gain more experience.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe