Re: [Haskell-cafe] Haskell as embedded DSL

2006-07-06 Thread Grzegorz ChrupaƂa

Perhaps Functional Morphology http://www.cs.chalmers.se/~markus/FM/,
a toolkit for morphology development would be of interest.
--
Grzegorz

On 7/5/06, Joel Reymont [EMAIL PROTECTED] wrote:

Folks,

Do you have examples of using Haskell as a DSL in an environment NOT
targeted at people who know it already?

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


[Haskell-cafe] RE: Packages and modules

2006-07-06 Thread Simon Peyton-Jones
Brian

| Actually re-reading my post  I realised I may have sounded a bit
negative
| about the hard work you'd done to collate the various responses to
form the
| wiki proposal - my apologies

Thanks -- email is a fragile medium!

| I've followed your suggestion and made a separate page at
|
http://hackage.haskell.org/trac/ghc/wiki/GhcPackagesAlternativeProposal

Jolly good, thank you.  I've looked at it.

Happily, so far as I can see the two proposals are identical!  At least
I cannot identify any points of difference.  If you think they differ,
can you say where?

Your spec is a little unclear about whether the package name is
compulsory in every import.  Under The best of both worlds / Shared
name space you say that plain import A.B.C looks in all exposed
packages and bleats if its ambiguous.  That's what we propose, and it's
satisfactorily backward compatible.  And that is what your syntax
implies too.

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


[Haskell-cafe] Trace parser

2006-07-06 Thread Andy Georges

Hello,

I'm looking for a bit of help (ok, a lot) the speed up my program  
which I use to build a calltree out of an annotated program execution  
trace. To give you an idea about the sluggishness at the moment, for  
a trace containing 70MB, it has been running for about 10 hours  
straight (AMD Athlon XP (Barton) 2600+).


The trace contains lines made up of a number of fields:

C 4 1000 100
C 4 1001 1000200
R 4 1001 1003045
R 4 1000 1003060

C indicates a function entrypoint (call), R indicates a function  
exitpoint (return). The second field indicates which thread is  
executing the function, the third field denotes the function id, the  
last field contains a performance counter value. As you can see,  
numbering each line with a pre-order and a post-order number yields a  
list that can be transformed easily into a tree, which can then be  
manipulated. The first goal is to build the tree. This is done in the  
following code:



data ParserState = ParserState { methodStack :: !ThreadMap
   , methodQueue :: !ThreadMap
   , pre :: !Integer
   , post:: !Integer
   , methodMap   :: !MethodMap
   , currentThread :: !Integer
   } deriving (Show)

initialParserState :: ParserState
initialParserState = ParserState e e 0 0 e 0
  where e = M.empty :: Map Integer a

readInteger :: B.ByteString - Integer
readInteger = fromIntegral . fst . fromJust . B.readInt


parseTraceMonadic :: [B.ByteString] - ParserState
parseTraceMonadic ss = state { methodQueue = M.map reverse  
(methodQueue state) }
  where state = execState (mapM_ (\x - modify (updateState x)   
get = (`seq` return ())) ss) initialParserState



updateState :: B.ByteString - ParserState - ParserState
updateState s state = case (B.unpack $ head fields) of
  M - updateStateMethod fields state
  E - updateStateException  fields state
  C - updateStateEntry  fields state
  R - updateStateExit   fields state
  where fields = B.splitWith (== ' ') s


updateStateMethod :: [B.ByteString] - ParserState - ParserState
updateStateMethod (_:methodId:methodName:_) state = state { methodMap  
= M.insert (readInteger methodId) methodName (methodMap state) }


updateStateException :: [B.ByteString] - ParserState - ParserState
updateStateException _ state = state

updateStateEntry :: [B.ByteString] - ParserState - ParserState
updateStateEntry (_:ss) state = {-Debug.Trace.trace (before:  ++  
(show state) ++ \nafter:  ++ (show newstate)) $-} newstate
  where newstate = state { methodStack = updateMap thread  
(methodStack state) (\x y - Just (x:y)) (pre state, 0, method)

  , pre = ((+1) $! (pre state))
  }
method = mkMethod (Prelude.map B.unpack ss)
thread = Method.thread method

updateStateExit :: [B.ByteString] - ParserState - ParserState
updateStateExit (_:ss) state = {-Debug.Trace.trace (before:  ++  
(show state)) $-} case updateMethod m (Prelude.map B.unpack ss) of
   Just um - state { methodStack =  
M.update (\x - Just (tail x)) thread (methodStack state)
, methodQueue =  
updateMap thread (methodQueue state) (\x y - Just (x:y)) (pre_, post  
state, um)
, post = ((+1)  
$! (post state))

}
   Nothing - error $ Top of the  
stack is mismatching! Expected  ++ (show m) ++  yet got  ++ (show  
ss) ++ \n ++ (show state)

  where method = mkMethod (Prelude.map B.unpack ss)
thread = Method.thread method
(pre_, _, m) = case M.lookup thread (methodStack state) of
  Just stack - head stack
  Nothing- error $ Method stack has  
not been found for thread  ++ (show thread) ++  - fields:  ++  
(show ss)



updateMap key map f value = case M.member key map of
  True  - M.update (f value) key map
  False - M.insert key [value] map

As you can see, the state is updated for each entry, a stack being  
maintained with methods we've seen up to now, and a list with methods  
that have received both pre and post order numbers, and of which both  
the entry and exit point have been parsed. I am using a ByteString,  
because using a plain String is causing the program to grab far too  
much heap.


The mkMethod yields a Method like this:


data Method = Method { mid :: Integer
 , thread :: Integer
 , instruction_entry :: Integer
 , instruction_exit :: Integer
 } deriving (Eq, Show)

eM = Method 0 0 0 0

mkMethod :: [String] - Method
mkMethod s = let [_thread, _id, _entry] = take 3 $ 

Re: [Haskell-cafe] Re: Packages and modules

2006-07-06 Thread Simon Marlow

John Meacham wrote:

Package names should never appear in source files IMHO. if a package
name is in the source file, then you might as well make it part of the
module name. packages exist for 'meta-organization' of code. A way to
deal with mapping code _outside_ of the language itself, putting
packages inside the code will force the creation of yet another level,
meta-packages, or something. packages should not be a language issue,
they are an environment one.


Indeed, that's the principle we've been following with the package 
design up until now.  There are (were) two principles:


  1. packages should stay out of the language
  2. module names should reflect functionality *only*

Sticking to these principles rigidly has left us with a problem, namely 
that packages lack proper abstraction properties.  A hidden module in a 
package is visible externally, because all packages share the module 
namespace.


So how do we fix that?

 a. we could put package names in module names as you suggest.  But
apart from sacrificing the second principle, this doesn't let
you import a module from a package without specifying the exact
version of the package == BAD.

 b. we could add compiler options that let you graft the module
namespace of a package into the global module namespace at
an arbitrary location.

 c. instead of grafting, we add language support to allow importing
modules from a particular package (crucically, you don't have
to specify the version).

We were thinking about (b), when people started suggesting (c). 
Although (c) breaks the first principle, in many ways it's rather nicer 
than (b).  I don't think (a) is a goer at all.


So that's where we are now, if you have a better idea then let's hear it!

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


Re: [Haskell-cafe] Windows Haskell GUI

2006-07-06 Thread Duncan Coutts
On Wed, 2006-07-05 at 17:51 -0700, Jason Dagit wrote:
 On 7/5/06, Duncan Coutts [EMAIL PROTECTED] wrote:
  On Wed, 2006-07-05 at 16:06 -0700, Jason Dagit wrote:
   I can't help with gtk2hs as I haven't tried it yet, but I hear the dev
   community is much more alive and very helpful.  My main concerns with
   gtk2hs were 1) I need a native look 'n feel
 
  This is a common misconception. Gtk+ uses the windows native theming
  dlls so look pretty good. See some of our screen shots:
  http://www.haskell.org/gtk2hs/gallery/HRay
 
  If you do find any places where it doesn't match the native theme then
  please report them in the Gtk+ bugzilla.
 
 What about file dialogs?  Perhaps it's just GIMP but I thought it was
 all gtk programs that used the really out-of-place file dialogs on
 windows (I think gaim uses the same ones).  I looked at some of your
 screenshots.  Looks better overall than I remembered.

Yes, you're right. Gtk+ does a native theme but does not use the native
dialogues (except for printing). I'm not completely sure of the position
of the Gtk+ devs on this one. It's not clear if it's not been done due
to lack of time or because there is some technical difficulty or
objection to it.

See for example:
http://bugzilla.gnome.org/show_bug.cgi?id=337093
http://bugzilla.gnome.org/show_bug.cgi?id=337267

   2) ease of distribution with my application.
 
  Is there something specific we could improve here?
 
 I haven't tried this myself; I was going by word of mouth.  The
 testimonial appears here:
 http://article.gmane.org/gmane.comp.lang.haskell.cafe/13378

The note about installing the Gtk+ dlls being very hard is not quite
true. There are win32 installers for this stuff at
http://gladewin32.sf.net.
Indeed, Gtk2Hs relies on these installers.

What was being referred to in that post is the win32 builds provided by
one of the Gtk+ win32 developers, which indeed are not aimed at end
users. They are however a useful resource for developers putting
together customised or minimal Gtk+ dll sets to bundle with their
application.
http://www.gimp.org/~tml/gimp/win32/downloads.html


Duncan

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


[Haskell-cafe] RE: Packages and modules

2006-07-06 Thread Simon Peyton-Jones
| 1) Qualified names:
| 
|   import A.B.C( T1 ) from foo
|   import A.B.C( T2 ) from bar
|   type S = A.B.C.T1 - A.B.C.T2
| 
| I'd suggest that the above should give a compiler error that A.B.C is
| ambiguous (as a qualifier), rather than allowing T1 to disambiguate
it,
| because otherwise it allows people to write code that could be very
hard to
| understand ie within the code, every occurrence of A.B.C as a
qualifier
| should refer to the same module. (Otherwise the thing qualified
qualifies
| the qualifier that's qualifying it...)

But that's inconsistent with Haskell 98.  In H98 you can say
import M( T1 ) as Q
import N( T2 ) as Q
type S = Q.T1 - Q.T2
and it'll work just fine.  You may think it should not work, but that's
water under the bridge.  We should be consistent here.

| In my spec, if you omit the package name you get an old-style import
using
| the shared namespace, and if you supply a package name you get a
new-style
| import that only searches in the specified package:
| 
| import A.B.C -- search home + exposed as is done at the moment
| import  A.B.C -- search home package only
| import pkg A.B.C -- search pkg only

That's exactly what our spec says too.  (Good news, again.)  Only maybe
not explicitly enough!  See the section Is the frompackage
compulsory.   Perhaps you could improve the wording to make it more
unambiguous?

Indeed, if we've converged, would you like to fold into our draft
whatever you think is useful from yours?

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


[Haskell-cafe] Re: Packages and modules

2006-07-06 Thread Aaron Denney
On 2006-07-06, Simon Marlow [EMAIL PROTECTED] wrote:
   a. we could put package names in module names as you suggest.  But
  apart from sacrificing the second principle, this doesn't let
  you import a module from a package without specifying the exact
  version of the package == BAD.

Right.  There are occasions of course that I do want to specify
exact versions -- such as testing two versions side by side.

   b. we could add compiler options that let you graft the module
  namespace of a package into the global module namespace at
  an arbitrary location.

This seems quite workable.

   c. instead of grafting, we add language support to allow importing
  modules from a particular package (crucically, you don't have
  to specify the version).

The package still needs to be located somehow, and I don't like this
split between tools and language.

-- 
Aaron Denney
--

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


[Haskell-cafe] Haskell performance in heavy numerical computations

2006-07-06 Thread Joel Reymont
Is anyone using Haskell for heavy numerical computations? Could you  
share your experience?


My app will be mostly about running computations over huge amounts of  
stock data (time series)  so I'm thinking I might be better of with  
OCaml.


Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Re: Packages and modules

2006-07-06 Thread Brian Hulley

Brian Hulley wrote:

Simon Peyton-Jones wrote:

compulsory.   Perhaps you could improve the wording to make it more
unambiguous?

Indeed, if we've converged, would you like to fold into our draft
whatever you think is useful from yours?



[snip]

Therefore it seems best to just leave them as they are unless you
want to use my suggested syntax instead.


I've added the point about from being redundant to the syntax section and 
made a new section to summarise the resulting concrete syntax that is 
derived conversationally in the previous section, which might also help to 
clarify the meaning of the different variants of import directive. Please 
feel free to delete it if you think this is too concrete at this stage for 
this draft.


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Haskell performance in heavy numerical computations

2006-07-06 Thread Greg Fitzgerald
I have tried. Using just normal lists, I found it difficult to avoid huge space leaks, but once things are working, the end result is easy to reason about.I'm considering giving it another try using Stream Processors or some form of Arrows instead of lists. I think this strategy might allow me to do several transformations of the same input list in pseudo-parallel, which would allow the GC to collect old data as soon as its not needed by the computation that decides when to buy and sell. The Stream Processor library I was looking at uses Continuation Passing Style, which I don't know too much about, and I'm not sure Arrows will work out.
Generalizing the problem, how does one express: given multiple transformations of an infinite numeric list, perform some IO at the first instance some predicate is met?I feel that Arrows might somehow trivially allow me to compute on huge
lists without leaking, but don't understand them well enough to
apply them.If one could write an arrow that applies the transformations to the input list in parallel, then I'd think you could solve the above example something like this:(f  g)  dropWhile (\(x,y) - x  0  y  0)  performSomeIO 
Maybe + is the arrow operator I'm looking for, not , but to be honest, the documentation for Arrows blows my mind. I think a few examples would go a long way.Thanks,Greg
On 7/6/06, Joel Reymont [EMAIL PROTECTED] wrote:
Is anyone using Haskell for heavy numerical computations? Could youshare your experience?My app will be mostly about running computations over huge amounts ofstock data (time series)so I'm thinking I might be better of with
OCaml.Thanks, Joel--http://wagerlabs.com/___Haskell-Cafe mailing list
Haskell-Cafe@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe