Re: [Haskell-cafe] LL(1) parsing of declarators

2007-04-15 Thread Lennart Augustsson

But the qualifiers aren't arbitrary names, are they?

On Apr 15, 2007, at 04:52 , Stefan O'Rear wrote:


I'm writing a code generator for C, and I'm trying to parse a C-like
input language using LL(1) (parsec specifically).  The syntax of
declarators is giving me trouble: (simplified)

declaration = qualifiers  (declarator `sepBy1` char ',')
qualifiers = many1 name
declarator = name

now if we have name name, they are both parsed by the greedy
many1 in qualifiers!  I can make this work with some ugly rearranging:

declaration = fdeclarator  many (char ','  declarator)
fdeclarator = name  many1 name
declarator = name

is there a more elegant way?

Stefan
___
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: [Haskell-cafe] LL(1) parsing of declarators

2007-04-15 Thread Stefan O'Rear
On Sun, Apr 15, 2007 at 07:42:02AM +0100, Lennart Augustsson wrote:
 But the qualifiers aren't arbitrary names, are they?

Yes they are.  I don't have knowledge of typedefs used :)

Nice try though, I toyed with that idea for a long while.  Ultimately
I decided that it would complicate the lexer too much to add knowledge
of C's keywords.  Then I thought of the typedef problem. 

 On Apr 15, 2007, at 04:52 , Stefan O'Rear wrote:
 
 I'm writing a code generator for C, and I'm trying to parse a C-like
 input language using LL(1) (parsec specifically).  The syntax of
 declarators is giving me trouble: (simplified)
 
 declaration = qualifiers  (declarator `sepBy1` char ',')
 qualifiers = many1 name
 declarator = name
 
 now if we have name name, they are both parsed by the greedy
 many1 in qualifiers!  I can make this work with some ugly rearranging:
 
 declaration = fdeclarator  many (char ','  declarator)
 fdeclarator = name  many1 name
 declarator = name
 
 is there a more elegant way?

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


Re: [Haskell-cafe] Calling C function in Mac OS X

2007-04-15 Thread Sergey Perminov

Thank you, Stefan!

Your information really helped (saved hours).

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


Re: [Haskell-cafe] Weaving fun

2007-04-15 Thread Yitzchak Gale

Back to the original problem for a moment.

\begin{code}

import qualified Data.Sequence as Seq
import Data.Sequence ((|), ViewL((:)))

weave :: [[a]] - [a]
weave = weaveSeqL . Seq.viewl . Seq.fromList
 where
   weaveSeqL ((x:xs) : s) = x : weaveSeqL (Seq.viewl $ s | xs)
   weaveSeqL _ = []

\end{code}

Yes, it also weaves infinite lists.

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


[Haskell-cafe] darcs error

2007-04-15 Thread Ruben Zilibowitz
What does it mean if I'm trying to check out a darcs repository and I  
get the following error?


darcs: ./.DS_Store: openBinaryFile: does not exist (No such file or  
directory)


.DS_Store files ought to be filtered out by the default boring file.  
I don't know how one got into the repository and started causing this  
error.


Is there some way to repair the repository?
darcs repair doesn't seem to help.

Regards,

Ruben

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


Re: [Haskell-cafe] darcs error

2007-04-15 Thread Yitzchak Gale

Ruben Zilibowitz wrote:

What does it mean if I'm trying to check out a darcs repository and I
get the following error?

darcs: ./.DS_Store: openBinaryFile: does not exist (No such file or
directory)


If you are doing darcs get from a partial repo and you
did not use --partial, then this sounds like:

http://bugs.darcs.net/issue145

The darcs users list would be more appropriate
for this question.

http://lists.osuosl.org/mailman/listinfo/darcs-users

More info about darcs on www.darcs.net.

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


Re: [Haskell-cafe] Re: Translating perl - haskell, string fill ins with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-15 Thread Thomas Hartman

Claus and Evan ++; that was very helpful.

FWIW, my gut feeling is that Claus's first version was easier to
understand than the revision with printf, which seems to me to involve
a lot more monadic wizardry (Functor, MonadError, fmap, mapm). The
first version, which just used maybe, was clear to me within seconds.

But again, I learned a lot. Thanks.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] darcs error

2007-04-15 Thread Ruben Zilibowitz
I don't think the repository is partial. The error is similar to the  
one in that bug report, but it is a bit different. I'm not sure that  
is the problem. I've posted this to darcs-users now; sorry, I  
should've sent it there originally.


Ruben

On 15/04/2007, at 9:03 PM, Yitzchak Gale wrote:


Ruben Zilibowitz wrote:

What does it mean if I'm trying to check out a darcs repository and I
get the following error?

darcs: ./.DS_Store: openBinaryFile: does not exist (No such file or
directory)


If you are doing darcs get from a partial repo and you
did not use --partial, then this sounds like:

http://bugs.darcs.net/issue145

The darcs users list would be more appropriate
for this question.

http://lists.osuosl.org/mailman/listinfo/darcs-users

More info about darcs on www.darcs.net.

Regards,
Yitz


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


[Haskell-cafe] Parallel executing of actions

2007-04-15 Thread Mitar

Hi!

Is there a parallel version of mapM_? Like it is for map (parMap)?

I would like to execute actions in parallel as the computation of
necessary data for actions is quite computational heavy. But it does
not matter in which order those actions are executed. (I am rendering
pixels with OpenGL and it does not matter in which order I draw them,
but it matters that for one pixel it takes some time to calculate its
color.)

The example would be:

main :: IO ()
main = do
 -- the order of printed characters is not important
 -- instead of putStrLn there will be a computationally big function
 -- so it would be great if those computations would be done in parallel
 -- and results printed out as they come
 mapM_ rwhnf (putStrLn) [a,b,c,d]

Is this possible? Without unsafe functions? And without changing the
semantics of the program.


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


[Haskell-cafe] GADTs and Typeclasses

2007-04-15 Thread Dominic Steinitz
Will I run into problems using typeclasses with GADTs? I've come up with this 
to model a fragment of ASN.1. I'd hate to spend a lot of time on this only to 
find out it's well known that these two features don't mix very well.

Thanks, Dominic.

data Type :: * - * where
   INTEGER :: Type Int
   BOOLEAN :: Type Bool
   BITSTRING   :: Type BitString
   NUMERICSTRING   :: Type NumericString
   ReferencedType  :: Type () -- for now
   ConstrainedType :: Type a - Constraint a - Type a
   SizeConstrainedType :: Size a = Type a - Constraint Int - Type a
   FromConstrainedType :: From a = Type a - Constraint a - Type a

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


Re: [Haskell-cafe] LL(1) parsing of declarators

2007-04-15 Thread Lennart Augustsson
Oh, but C parsers often do a trick like extending the lexer when  
typedefs are encountered.
Typedefs part of the challange of parsing C correctly.  And the lexer  
should definitely know about C's keywords.  That's what the lexer is  
for.


-- Lennart

On Apr 15, 2007, at 07:46 , Stefan O'Rear wrote:


On Sun, Apr 15, 2007 at 07:42:02AM +0100, Lennart Augustsson wrote:

But the qualifiers aren't arbitrary names, are they?


Yes they are.  I don't have knowledge of typedefs used :)

Nice try though, I toyed with that idea for a long while.  Ultimately
I decided that it would complicate the lexer too much to add knowledge
of C's keywords.  Then I thought of the typedef problem.


On Apr 15, 2007, at 04:52 , Stefan O'Rear wrote:


I'm writing a code generator for C, and I'm trying to parse a C-like
input language using LL(1) (parsec specifically).  The syntax of
declarators is giving me trouble: (simplified)

declaration = qualifiers  (declarator `sepBy1` char ',')
qualifiers = many1 name
declarator = name

now if we have name name, they are both parsed by the greedy
many1 in qualifiers!  I can make this work with some ugly  
rearranging:


declaration = fdeclarator  many (char ','  declarator)
fdeclarator = name  many1 name
declarator = name

is there a more elegant way?


Stefan


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


Re: [Haskell-cafe] Parallel executing of actions

2007-04-15 Thread Spencer Janssen
On Sun, 15 Apr 2007 18:01:44 +0200
Mitar [EMAIL PROTECTED] wrote:

 Hi!
 
 Is there a parallel version of mapM_? Like it is for map (parMap)?

This version will fork a new thread for each action:

\begin{code}
import Control.Concurrent
import Control.Monad

parSequence_ xs = do
m - newEmptyMVar
mapM_ (\x - forkIO x  putMVar m ()) xs
replicateM_ (length xs) (takeMVar m)

parMapM_ f xs = parSequence_ $ map f xs
\end{code}

 I would like to execute actions in parallel as the computation of
 necessary data for actions is quite computational heavy. But it does
 not matter in which order those actions are executed. (I am rendering
 pixels with OpenGL and it does not matter in which order I draw them,
 but it matters that for one pixel it takes some time to calculate its
 color.)
 
 The example would be:
 
 main :: IO ()
 main = do
   -- the order of printed characters is not important
   -- instead of putStrLn there will be a computationally big function
   -- so it would be great if those computations would be done in
 parallel -- and results printed out as they come
   mapM_ rwhnf (putStrLn) [a,b,c,d]
 
 Is this possible? Without unsafe functions? And without changing the
 semantics of the program.

Of course the semantics of the program will change, the order in which
the actions are executed is unknown!


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


Re: [Haskell-cafe] Parallel executing of actions

2007-04-15 Thread Mitar

Hi!

On 4/15/07, Spencer Janssen [EMAIL PROTECTED] wrote:

This version will fork a new thread for each action:

\begin{code}
import Control.Concurrent
import Control.Monad

parSequence_ xs = do
m - newEmptyMVar
mapM_ (\x - forkIO x  putMVar m ()) xs
replicateM_ (length xs) (takeMVar m)

parMapM_ f xs = parSequence_ $ map f xs
\end{code}


OpenGL bindings successfully crash. The functional calculations in f
should be done in parallel, but those few OpenGL actions should still
be done sequentially. I am attaching the code in question. It is a
simple voxel raycasting engine.

(Any suggestions on other memory/performance improvements are more
than welcome.)


Mitar


Main.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parallel executing of actions

2007-04-15 Thread Joel Reymont


On Apr 15, 2007, at 8:23 PM, Spencer Janssen wrote:


parSequence_ xs = do
m - newEmptyMVar
mapM_ (\x - forkIO x  putMVar m ()) xs
replicateM_ (length xs) (takeMVar m)


mapM_ above spawns (length xs) threads blocking on a single lock,  
right?


replicateM_ then makes sure that the lock is unlocked as many times  
as threads spawned, right?


Since all the threads block on a single MVar how do they run in  
parallel?


Thanks, Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] and sequencing [newbie]

2007-04-15 Thread David Powers

so... this is likely a question based on serious misunderstandings, but can
anyone help me understand the exact mechanism by which monads enforce
sequencing?  Specifically, I'm confused by the  operator.  If I understand
things properly f a  g expands to something like:

f = \_ - g

What I'm missing is how the expansion of f is ever forced under lazy
evaluation.  Since the result is never used, doesn't it just stay as a
completely unevaluated thunk?  Come to think of it... how is it that some IO
actions sequence completely, while others manage to work in a lazy manner?
My suspicion is that somehow the order of evaluation in Haskell gives the
outermost expression a first crack at evaluation in all circumstances (e.g.
http://users.aber.ac.uk/afc/stricthaskell.html#cps) , but that it somehow
stops short of a forced deep sequencing...  Which is all to say, I have no
idea how the magic happens.

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


Re: [Haskell-cafe] and sequencing [newbie]

2007-04-15 Thread Stefan O'Rear
On Sun, Apr 15, 2007 at 08:04:41PM -0400, David Powers wrote:
 so... this is likely a question based on serious misunderstandings, but can
 anyone help me understand the exact mechanism by which monads enforce
 sequencing?  Specifically, I'm confused by the  operator.  If I understand
 things properly f a  g expands to something like:
 
 f = \_ - g
 
 What I'm missing is how the expansion of f is ever forced under lazy
 evaluation.  Since the result is never used, doesn't it just stay as a
 completely unevaluated thunk?  Come to think of it... how is it that some IO
 actions sequence completely, while others manage to work in a lazy manner?
 My suspicion is that somehow the order of evaluation in Haskell gives the
 outermost expression a first crack at evaluation in all circumstances 
 (e.g.
 http://users.aber.ac.uk/afc/stricthaskell.html#cps) , but that it somehow
 stops short of a forced deep sequencing...  Which is all to say, I have no
 idea how the magic happens.

The values that are passed around monadically aren't the whole story.
EG, in the GHC implementation, we have: (slightly simplified)

newtype IO a = IO (Thread - ( Thread, a ))

So even though you throw away the a, the Thread *is* demanded.

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


Re: [Haskell-cafe] and sequencing [newbie]

2007-04-15 Thread jeff p

Hello,

On 4/15/07, David Powers [EMAIL PROTECTED] wrote:

so... this is likely a question based on serious misunderstandings, but can
anyone help me understand the exact mechanism by which monads enforce
sequencing?


Monads do not enforce sequencing.

In general, data dependencies enforce sequencing (i.e. if expression x
depends upon expression y then expression y will have to be evaluated
first). Consider:

   let x = case y of Just y' - f y'
Nothing - g
y = some code
   in more stuff

Here y must be evaluated before x because x needs to look at y in
order to compute.


Specifically, I'm confused by the  operator.  If I understand
things properly f a  g expands to something like:

f = \_ - g

What I'm missing is how the expansion of f is ever forced under lazy
evaluation.  Since the result is never used, doesn't it just stay as a
completely unevaluated thunk?


(=) is an overloaded function. Some instances of it will cause f to
be evaluated, others won't. Consider the State monad:

   instance Monad (State s) where
   return a = State $ \s - (a, s)
   m = k  = State $ \s - case runState m s of
(a, s') - runState (k a) s'

Note that (=)  causes m to be evaluated (up to a pair) before
evaluating k because (=) needs to look at the result of m.

An example of a monad in which (=) doesn't force evaluation of the
first argument before the second is the Identity monad:

   instance Monad Identity where
   return a = Identity a
   m = k  = k (runIdentity m)

Note that (=) actually forces the evaluation of k before m.

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


Re: [Haskell-cafe] Efficient use of ByteString and type classes in template system

2007-04-15 Thread Donald Bruce Stewart
johan.tibell:
 Hi Haskell Caf?!
 
 I'm writing a perl/python like string templating system which I plan
 to release soon:
 
 darcs get http://darcs.johantibell.com/template
 
 The goal is to provide simple string templating; no inline code, etc..
 An alternative to printf and ++.

Ok. You might also want to briefly look at the other templating system I
know of in Haskell, this small module by Stefan Wehr,


http://www.cse.unsw.edu.au/~dons/code/icfp05/tests/unit-tests/VariableExpansion.hs

Just a quick thing he did for the ICFP contest, but does indicate one
way to do it (i.e. via pretty printing).

 
 Example usage:
 
 import qualified Data.ByteString as B
 import Text.Template
 
 helloTemplate = Hello, $name! Would you like some ${fruit}s?
 helloContext = [(name, Johan), (fruit, banana)]
 
 test1 = B.putStrLn $ substitute (B.pack helloTemplate) helloContext
 
 I want to make it perform well, especially when creating a template
 once and then rendering it multiple times. Compiling the template is
 a separate step from rendering in this use case:
 
 compiledTemplate = template $ B.pack helloTemplate
 
 test2 = B.putStrLn $ render compiledTemplate helloContext
 
 A template is represented by a list of template fragments, each
 fragment is either a ByteString literal or a variable which is looked
 up in the context when rendered.
 
 data Frag = Lit ByteString | Var ByteString
 newtype Template = Template [Frag]
 
 This leads me to my first question. Would a lazy ByteString be better
 or worse here? The templates are of limited length. I would say the
 length is usually between one paragraph and a whole HTML page. The
 Template data type already acts a bit like a lazy ByteString since it
 consists of several chunks (although the chunck size is not adjusted
 to the CPU cache size like with the lazy ByteString).

Probably lazy bytestrings are better here, since you get O(n/k) append
cost, rather than O(n).  If most strings are small, it mightn't be
noticeable.

 Currently the context in which a template is rendered is represented
 by a type class.
 
 class Context c where
 lookup :: ByteString - c - Maybe ByteString
 
 instance Context (Map String String) where
 lookup k c = liftM B.pack (Map.lookup (B.unpack k) c)
 
 instance Context (Map ByteString ByteString) where
 lookup = Map.lookup
 
 -- More instance, for [(String, String)], etc.
 
 I added this as a convenience for the user, mainly to work around the
 problem of not having ByteString literals. A typical usage would have
 the keys in the context being literals and the values some variables:

note sure if it is relevant, but:

pack Foo

will be converted via rewrite rules to a bytestring literal at compile
time. So there's no overhead for having String literals.

 
 someContext = Map.fromList [(name, name), (fruit, fruit)]
 
 I'm not sure if this was a good decision, With this I'm halfway to the
 (in)famous Stringable class and it seems like many smarter people than

Yes, seems a little worrying.

 me have avoided introducing such a class. How will this affect
 performace? Take for example the rendering function:
 
 render :: Context c = Template - c - ByteString
 render (Template frags) ctx = B.concat $ map (renderFrag ctx) frags
 
 renderFrag :: Context c = c - Frag - ByteString
 renderFrag ctx (Lit s) = s
 renderFrag ctx (Var x) = case Text.Template.lookup x ctx of
Just v  - v
Nothing - error $ Key not found:  ++ 
(B.unpack x)
 
 How will the type dictionary 'c' hurt performance here? Would
 specializing the function directly in render help?

Hmm. Hard to say: look at the Core code and we will know.

Really though, you'll need some stress test cases to be able to make
resonable conclusions about performance.

 
 render (Template frags) ctx = B.concat $ map (renderFrag f) frags
 where f = flip Text.Template.lookup ctx
 
 renderFrag f (Var x) = case f x of
 
 I can see the implementation taking one of the following routes:
 - Go full Stringable, including for the Template
 - Revert to Context = Map ByteString ByteString which was the original
 implementation.
 - Some middle road, without MPTC, for example:
 class Context c where
 lookup :: ByteString - c ByteString ByteString - Maybe ByteString
 This would allow the user to supply some more efficient data type for
 lookup but not change the string type. Having a type class would allow
 me to provide things like the possibility to create a Context from a
 record where each record accessor function would server as key.
 Something like:
 
 data Person { personName :: String, personAge :: Int }
 would get converted (using Data?) to:
 personContext = [(personName, show $ personName aPerson),
  (personAge, show $ personAge aPerson)]
 but not actually using a Map but the record itself.
 
 I guess my more general question is: how do I reason about the
 performance of my code or any 

Re: [Haskell-cafe] Re: Translating perl - haskell, string fill ins with an error on invalid inputseems awfullycomplex. Is there a way to simplify?

2007-04-15 Thread jeff p

{

Hello,

 Here is a variation on Claus' code which returns an Either type
rather than fails with error. This could be further generalized to use
any instance of MonadError, rather than Either.

-Jeff

}

import Control.Monad.Error

financial_output :: String - String - String - String - Either String String
financial_output company displaymode startDate endDate = financial_script
   where
 financial_script = gnuplot_timeseries_settings ++ \n
++ plot [\ ++ startDate ++ \:\
++ endDate ++ \]
++  ' ++ companyFile ++ ' ++ modeString
++  title \ ++ company ++   ++
titleEnd ++ \

 companyFile = lookupWith (no company file for  ++ company)
   company company_to_companyfile

 modeString  = lookupWith (no mode string for  ++ displaymode)
   displaymode displaymode_to_modestring

 titleEnd= lookupWith (no title end for  ++ displaymode)
   displaymode displaymode_to_titleend

lookupWith :: (Eq a) = String - a - [(a,String)] - Either String String
lookupWith error key assocs = maybe (Left error) Right $ lookup key assocs

class MyString a
   where mystr :: a - Either String String
instance MyString (Either String String)
   where mystr = id
instance MyString String
   where mystr = Right

x ++ y = do xv - mystr x
 yv - mystr y
 return $ xv ++ yv
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parallel executing of actions

2007-04-15 Thread Bertram Felgenhauer
Joel Reymont wrote:
 
 On Apr 15, 2007, at 8:23 PM, Spencer Janssen wrote:
 
 parSequence_ xs = do
 m - newEmptyMVar
 mapM_ (\x - forkIO x  putMVar m ()) xs

should be

   mapM_ (\x - forkIO (x  putMVar m ())) xs

 replicateM_ (length xs) (takeMVar m)
 
 mapM_ above spawns (length xs) threads blocking on a single lock,  
 right?

yes.

 replicateM_ then makes sure that the lock is unlocked as many times  
 as threads spawned, right?

right.

 Since all the threads block on a single MVar how do they run in  
 parallel?

The idea is that before the threads block on the MVar, they run their
action x to completion.

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