[Haskell-cafe] Re: What I learned from my first serious attempt low-level Haskell programming

2007-04-05 Thread Simon Marlow

Stefan O'Rear wrote:
 2. Parameters are very expensive.  Our type of functions that build
(ignoring CPS for the time being) was MBA# - Int# - [ByteString],
where the Int# is the current write pointer.  Adding an extra Int#
to cache the size of the array (rather than calling sMBA# each
time) slowed the code down ~2x.  Conversely, moving the write
pointer into the byte array (storing it in bytes 0#, 1#, 2#, and
3#) sped the code by 4x.

If you were measuring on x86 then parameters are passed on the stack, which may 
be expensive.  On x86_64 the first 3 arguments are passed in registers, which is 
usually a win, but if the function immediately does an eval they need to be 
saved on the stack anyway.  Still, 4x sounds like a lot, perhaps you managed to 
avoid a stack check in the inner loop or something.


 3. MBA# is just as fast as Addr#, and garbage collected to boot.

Not really surprising, that.

 4. You can't keep track of which version of the code is which, what is
a regression, and what is an enhancement.  Don't even try.  Next
time I try something like this I will make as much use of darcs as
possible.

Absolutely - if you'd used darcs, then we could peer in more detail at changes 
that you thought gave counter-intuitive results.


Simon Peyton-Jones wrote:

| 5. State# threads clog the optimizer quite effectively.  Replacing
|st(n-1)# with realWorld# everywhere I could count on data
|dependencies to do the same job doubled performance.

The idea is that the optimiser should allow you to write at a high level, and 
do the book keeping for you.  When it doesn't, I like to know, and preferably 
fix.

If you had a moment to boil out a small, reproducible example of this kind of 
optimisation failure (with as few dependencies as poss), then I'll look to see 
if the optimiser can be cleverer.


Yes, and *please* add some of this folklore to the performance wiki at 
http://haskell.org/haskellwiki/Performance, if you have the time.


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


[Haskell-cafe] RE: What I learned from my first serious attempt low-level Haskell programming

2007-04-05 Thread Simon Peyton-Jones
| 5. State# threads clog the optimizer quite effectively.  Replacing
|st(n-1)# with realWorld# everywhere I could count on data
|dependencies to do the same job doubled performance.

The idea is that the optimiser should allow you to write at a high level, and 
do the book keeping for you.  When it doesn't, I like to know, and preferably 
fix.

If you had a moment to boil out a small, reproducible example of this kind of 
optimisation failure (with as few dependencies as poss), then I'll look to see 
if the optimiser can be cleverer.

|
| 6. The inliner is a bit too greedy.  Removing the slow-path code from
|singleton doesn't help because popSingleton is only used once; but
|if I explicitly {-# NOINLINE popSingleton #-}, the code for
|singleton itself becomes much smaller, and inlinable (15% perf
|gain).  Plus the new singleton doesn't allocate memory, so I can
|use even MORE realWorld#s.

That's a hard one!  Inlining functions that are called just once is a huge win 
usually. I don't know how to spot what you did in an automated way.

thanks

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


Re: [Haskell-cafe] 25k lines of ASP to 4.2k lines of Haskell, with considerably more functionality

2007-04-05 Thread Bulat Ziganshin
Hello Adam,

Thursday, April 5, 2007, 7:04:32 AM, you wrote:

 Haskell in the real world: http://braintreehemp.com.au/

in the shopping section, there are choice between men, women and
special creatures. doesn't slave-trade prohibited by civil laws?

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont

Stefan,

Data.Derive is a most awesome piece of code!

Is there soemething in DrIFT that you did not like that made you  
write it?


Thanks a lot!

On Apr 5, 2007, at 12:48 AM, Stefan O'Rear wrote:


Data.Derive can do this.  In an attempt to avoid munging the relevent
files they are attached.


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Re: Trouble trying to find packages for ubuntu linux

2007-04-05 Thread Thomas Hartman

In the spirit of...

 I hate package chasing, cabal doesn't do this automatically (yet),
and hard disk space is cheap...

 Here is a script to just hit the deb/ubuntu repos and install as
much haskell-loooking stuff as possible.

 If you're going to do this, I would recommend pulling at least from
the feisty repo, as described in pupeno's blog, and in more detail in
my other post linked above.

 Basically, this installs all ghc6* packages, with ad-hoc blocking of
packages that cause aptitude to complain.

 The basic approach seems sound though. If it gets stuck at some
point, I'll just add the offending package to the filter list.  (I
suspect there's a more intelligent way to do this if you know debian
package management better than I do.)

The script below has been cranking away for a pretty long time now --
so not only may your mileage vary, mine isnt' even yet.

 I also wouldn't recommend doing this on a production server.
(When/if I hose my system, I can reload a virgin ubuntu in under five
minutes using my linode control panel.)

*

apt-cache search libghc6 | ghc -e 'interact $ unlines . map (\l -
head $ words l ) . lines' \
 | grep -ivE \(ghc6-hopengl\|libghc6-c2hs-dev\) \
 | xargs apt-get -y install


2007/3/16, Chad Scherrer [EMAIL PROTECTED]:

Brian,

I had this exact problem, and I found this approach to work wonderfully:

http://pupeno.com/2006/12/17/unstable-packages-on-ubuntu/


Chad
___
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] Re: Trouble trying to find packages for ubuntu linux

2007-04-05 Thread Thomas Hartman

This approach is fleshed out at

http://groups.google.de/group/fa.haskell/browse_thread/thread/ceabae2c3fdc8abc/814a86d89c3f7d28?lnk=stq=tphyahoo+haskell+ubunturnum=1hl=en#814a86d89c3f7d28

2007/3/16, Chad Scherrer [EMAIL PROTECTED]:

Brian,

I had this exact problem, and I found this approach to work wonderfully:

http://pupeno.com/2006/12/17/unstable-packages-on-ubuntu/


Chad
___
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] Re: Trouble trying to find packages for ubuntu linux

2007-04-05 Thread Thomas Hartman

and in more detail in
my other post linked above.


I meant, linked below.

2007/4/5, Thomas Hartman [EMAIL PROTECTED]:

In the spirit of...

  I hate package chasing, cabal doesn't do this automatically (yet),
and hard disk space is cheap...

  Here is a script to just hit the deb/ubuntu repos and install as
much haskell-loooking stuff as possible.

  If you're going to do this, I would recommend pulling at least from
the feisty repo, as described in pupeno's blog, and in more detail in
my other post linked above.

  Basically, this installs all ghc6* packages, with ad-hoc blocking of
packages that cause aptitude to complain.

  The basic approach seems sound though. If it gets stuck at some
point, I'll just add the offending package to the filter list.  (I
suspect there's a more intelligent way to do this if you know debian
package management better than I do.)

 The script below has been cranking away for a pretty long time now --
so not only may your mileage vary, mine isnt' even yet.

  I also wouldn't recommend doing this on a production server.
(When/if I hose my system, I can reload a virgin ubuntu in under five
minutes using my linode control panel.)

*

apt-cache search libghc6 | ghc -e 'interact $ unlines . map (\l -
head $ words l ) . lines' \
  | grep -ivE \(ghc6-hopengl\|libghc6-c2hs-dev\) \
  | xargs apt-get -y install


2007/3/16, Chad Scherrer [EMAIL PROTECTED]:
 Brian,

 I had this exact problem, and I found this approach to work wonderfully:

 http://pupeno.com/2006/12/17/unstable-packages-on-ubuntu/


 Chad
 ___
 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[2]: [Haskell-cafe] Tracking characters and a timestamp ?

2007-04-05 Thread Bulat Ziganshin
Hello Marc,

Thursday, April 5, 2007, 8:40:04 AM, you wrote:

 Bulat:
 When also using unsafeInterleavedMapM for the second mapM the program will 
 stop
 after processing the first list item. 
 question 2
 I can't see why this is the case.

because there is no need to calculate entire answer before return.
unsafeInterleavedMapM is written in the manner that only first list
item will be obligatory calculated, all other only on demand :)))

you definitely should read http://haskell.org/haskellwiki/IO_inside

 Continuation does work as well:

this code is 100% equivalent of (mapM_ (c- ...)) proposed earlier


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Re[2]: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont

Following tells me that Data.Derive.Peephole was built.

ar t dist/build/libHSderive-0.1.a says Derive.o is there.

ghc-pkg -l
/opt/local/lib/ghc-6.6/package.conf:
Cabal-1.1.6, FilePath-0.11, GLUT-2.0, HUnit-1.1, OpenGL-2.1,
QuickCheck-1.0, base-2.0, cgi-2006.9.6, derive-0.1, fgl-5.2,
(ghc-6.6), haskell-src-1.0, haskell98-1.0, html-1.0, mtl-1.0,
network-2.0, parsec-2.0, readline-1.0, regex-base-0.71,
regex-compat-0.71, regex-posix-0.71, rts-1.0, stm-2.0,
template-haskell-2.0, time-1.0, unix-1.0, xhtml-2006.9.13

derive-1.0 is in the list of packages.

ghc --make FunParser.hs

FunParser.hs:4:7:
Could not find module `Data.Derive.Peephole':
  Use -v to see a list of the files searched for.

I'm baffled again.

---
runhaskell Setup.hs build
Preprocessing library derive-0.1...
Preprocessing executables for derive-0.1...
Building derive-0.1...
[1 of 9] Compiling Data.Derive.FixedPpr ( Data/Derive/FixedPpr.hs,  
dist/build/Data/Derive/FixedPpr.o )
[2 of 9] Compiling Data.Derive  ( Data/Derive.hs, dist/build/Data/ 
Derive.o )
[3 of 9] Compiling Data.Derive.SYB  ( Data/Derive/SYB.hs, dist/build/ 
Data/Derive/SYB.o )
[4 of 9] Compiling Data.Derive.TH   ( Data/Derive/TH.hs, dist/build/ 
Data/Derive/TH.o )
[5 of 9] Compiling Data.Derive.BinaryDefer ( Data/Derive/ 
BinaryDefer.hs, dist/build/Data/Derive/BinaryDefer.o )
[6 of 9] Compiling Data.Derive.Eq   ( Data/Derive/Eq.hs, dist/build/ 
Data/Derive/Eq.o )
[7 of 9] Compiling Data.Derive.Peephole ( Data/Derive/Peephole.hs,  
dist/build/Data/Derive/Peephole.o )
[8 of 9] Compiling Data.Derive.Binary ( Data/Derive/Binary.hs, dist/ 
build/Data/Derive/Binary.o )
[9 of 9] Compiling Data.Derive.Play ( Data/Derive/Play.hs, dist/build/ 
Data/Derive/Play.o )

ar: creating archive dist/build/libHSderive-0.1.a
[1 of 1] Compiling Main ( Derive.hs, dist/build/derive/ 
derive-tmp/Main.o )

Linking dist/build/derive/derive ...

sudo runhaskell Setup.hs install
Installing: /usr/local/lib/derive-0.1/ghc-6.6  /usr/local/bin  
derive-0.1...

Registering derive-0.1...
Reading package info from .installed-pkg-config ... done.
Saving old package config file... done.
Writing new package config file... done.


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont

Stefan,

What version of ghc are you using? Mine is 6.6.

Data/Derive/Play.hs:9:7:
Could not find module `Control.Monad.State':
  it is a member of package mtl-1.0, which is hidden

I commented out that import line.

Preprocessing library derive-0.1...
Preprocessing executables for derive-0.1...
Building derive-0.1...
[1 of 9] Compiling Data.Derive.FixedPpr ( Data/Derive/FixedPpr.hs,  
dist/build/Data/Derive/FixedPpr.o )
[2 of 9] Compiling Data.Derive  ( Data/Derive.hs, dist/build/Data/ 
Derive.o )
[3 of 9] Compiling Data.Derive.SYB  ( Data/Derive/SYB.hs, dist/build/ 
Data/Derive/SYB.o )
[4 of 9] Compiling Data.Derive.TH   ( Data/Derive/TH.hs, dist/build/ 
Data/Derive/TH.o )


Data/Derive/TH.hs:25:26:
No instance for (Functor Q)
  arising from use of `fmap' at Data/Derive/TH.hs:25:26-31
Possible fix: add an instance declaration for (Functor Q)
In the first argument of `(.)', namely `fmap f'
In the expression: (fmap f) . deriveOne
In the definition of `derive':
derive (Derivation f _) = (fmap f) . deriveOne

This I don't know how to deal with.

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont


On Apr 5, 2007, at 11:04 AM, Joel Reymont wrote:

This is in Language.Haskell.TH.Syntax which is imported at the top  
of Data/Derive/TH.hs so I don't understand the cause of the error


Apparently instance Functor Q was added to 6.6 very recently and it's  
not in MacPorts yet.


I decided to throw down the gauntlet and run 6.7 instead.

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Re: Trouble trying to find packages for ubuntu linux

2007-04-05 Thread Dougal Stanton

On 05/04/07, Thomas Hartman [EMAIL PROTECTED] wrote:

In the spirit of...

  I hate package chasing, cabal doesn't do this automatically (yet),
and hard disk space is cheap...



Agreed. As much as I like the rest of Ubuntu I'm beginning to dislike
binary packages after only a week away from Gentoo ;-) Still, at least
they install quicker!

Are there recommended ways of setting up current development systems?
I'm the only person on this machine, so having system-wide packages
isn't much of an issue. Would I be better just building all my own
from tarball rather than hoping Feisty stays up to date?

Cheers,

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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont

That did it, thanks!

On Apr 5, 2007, at 12:07 PM, Twan van Laarhoven wrote:


 instance Functor Q where
 fmap = liftM


--
http://wagerlabs.com/





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


Re: Re[2]: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont

Installed derive, trying to load it with ghci -package derive

Loading package base ... linking ... done.
Loading package template-haskell ... linking ... done.
Loading package FilePath-0.11 ... linking ... done.
ghc-6.6:
unknown symbol `_derivezm0zi1_DataziDeriveziPeephole_zdf7_closure'
Loading package derive-0.1 ... linking ... ghc-6.6: unable to load  
package `derive-0.1'


What am I doing wrong?

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Twan van Laarhoven

Joel Reymont wrote:
 This is in Language.Haskell.TH.Syntax which is imported at the top of
 Data/Derive/TH.hs so I don't understand the cause of the error

 instance Functor Q where
   fmap f (Q x) = Q (fmap f x)

 ...

 Any suggestions?

Since Q is a Monad, you can make the instance

 instance Functor Q where
 fmap = liftM



 But Q is exported by Languave.Haskell.TH.Syntax !!!


Only the type constructor is exported, not the data constructor.

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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont
This is in Language.Haskell.TH.Syntax which is imported at the top of  
Data/Derive/TH.hs so I don't understand the cause of the error


instance Functor Q where
  fmap f (Q x) = Q (fmap f x)

Copying the above into TH.hs gives me

Preprocessing library derive-0.1...
Preprocessing executables for derive-0.1...
Building derive-0.1...
[4 of 9] Compiling Data.Derive.TH   ( Data/Derive/TH.hs, dist/build/ 
Data/Derive/TH.o )


Data/Derive/TH.hs:23:10: Not in scope: data constructor `Q'

Data/Derive/TH.hs:23:17: Not in scope: data constructor `Q'

But Q is exported by Languave.Haskell.TH.Syntax !!!

Any suggestions?

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Jules Bean

Joel Reymont wrote:

Folks,

I have very uniform Parsec code like this and I'm wondering if I can 
derive it using TemplateHaskell or DrIFT or some other tool. Any ideas?


Others have given good answers on how to use code-generation. I am more 
interested in whether code generation is actually necessary for this 
example. Haskell has good data-manipulation tools, and parsers are a 
kind of data...


First of all, the nullary commands. Here is an abbreviated version with 
only them:


strCall =
   choice [ do { reserved NewLine
   ; return NewLine
   }
  , do { reserved GetSymbolName
   ; return GetSymbolName
   }
  , do { reserved Description
   ; return Description
   }
  , do { reserved GetExchangeName
   ; return GetExchangeName
   }
  , do { reserved SymbolRoot
   ; return SymbolRoot
   }
  ]

The 'do' syntax is unpleasantly verbose for such simple examples. As a 
guideline, I personally only use 'do' syntax if there is at least one 
result to 'capture' (bind) and use elsewhere. Already the code is easier 
to read if we do something like this:


strCall =
   choice [ reserved NewLine  return NewLine
  , reserved GetSymbolNamereturn GetSymbolName
  , reserved Description  return Description
  , reserved GetExchangeName  return GetExchangeName
  , reserved SymbolRoot   return SymbolRoot
  ]


Now this we can make simpler with the very basic 'metaprogramming' built 
into the 'deriving Show' that haskell has:


nullary x = reserved (show x)  return x

strCall = choice ( map nullary
   
[NewLine,GetSymbolName,Description,GetExchangeName,SymbolRoot] )



To do the same for unaries, we need to know which kind of parameter to 
expect.



data paramType = JNum | JBool | JStr

paramParser JNum  = numExpr
paramParser JBool = boolExpr
paramParser JStr  = strExpr

unary x pt = reserved (quasiShow (x undefined))  parens (paramParser 
pt) = return . x


strCall = choice ( map unary 
[ELDateToString,TextGetString,LowerStr,UpperStr,Spaces] )



But what is 'quasiShow'? This is the function which maps these 
constructors to their string representation, without inspecting the 
argument (so I can safely pass undefined). This perhaps you do need 
meta-programming for. Although, I think you can write the following:


quasiShow = takeWhile (/=' ') . show

Feels a bit ugly though :)

And now binaries are only slightly more complex (but now I will use 'do' 
notation):




binary x pta ptb = reserved (quasiShow x undefined undefined) 
  parens $ do a - paramParser pta
  comma
  b - paramParser ptb
  return x a b



I'm sure you can work out ternaries.

Of course if you want to automatically choose binary, ternary or unary 
from the definition of the ADT then you're thoroughly back into the 
world of metaprogramming.


The purpose of this message was not to discourage you from 
metaprogamming, which is a powerful tool, but just to show that haskell 
is capable of many things which in other languages would be 
metaprogramming, either entirely without a meta part, or just using the 
limited built in meta-facilities (i.e. derived instances).


Jules


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


Re: Re[2]: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont
This is the exposed modules portion of derive.cabal. I had to remove  
the empty lines since Cabal was complaining about them. I suspect one  
of these lines had Data.Derive.Peephole in it.


Exposed-Modules:
Data.Derive
Data.Derive.FixedPpr

Data.Derive.SYB
Data.Derive.TH

Data.Derive.Binary
Data.Derive.BinaryDefer
Data.Derive.Eq
Data.Derive.Play

On Apr 5, 2007, at 12:46 PM, Joel Reymont wrote:


FunParser.hs:4:7:
Could not find module `Data.Derive.Peephole':
  Use -v to see a list of the files searched for.



--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Jules Bean

Jules Bean wrote:

data paramType = JNum | JBool | JStr

paramParser JNum  = numExpr
paramParser JBool = boolExpr
paramParser JStr  = strExpr

unary x pt = reserved (quasiShow (x undefined))  parens (paramParser 
pt) = return . x


strCall = choice ( map unary 
[ELDateToString,TextGetString,LowerStr,UpperStr,Spaces] )





Oops.

unary (x,pt) = reserved (quasiShow (x undefined))  parens (paramParser 
pt) = return . x


strCall = choice ( map unary   
[(ELDateToString,JNum),(TextGetString,JNum),

 (LowerStr,JStr),(UpperStr,JStr),(Spaces,JStr)] )

(have to specify the param types)

Jules

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


[Haskell-cafe] Type classes to 'reflect' constructor structure

2007-04-05 Thread Jules Bean
In the thread 'automatic derivation', Joel Reymont is looking for 
metaprogramming functionality with which he wants to automatically 
derive a parser and a pretty printer for his ADT (which is an AST for a 
minilanguage).


I replied showing that a significant amount of the boilerplate could be 
removed anyway just using haskell's built in ability to process parsers 
as 'data'. I could completely automate the nullary constructions, but I 
needed type information for n-ary ones.


A bit of poking around with typeclasses showed a proof-of-concept for 
getting the type-checker to extract that information for us:


{-# OPTIONS -fglasgow-exts #-}
import Data.Typeable


-- Stage 1 is just counting the arguments

class CountArgs s where numArgs :: s - Integer

data TestType = Nullary | Unary Int | Binary Int String
 | OtherBinary String Int

instance CountArgs TestType where numArgs x = 0
instance CountArgs (a-TestType) where numArgs x = 1
instance CountArgs (a-b-TestType) where numArgs x = 2

-- *Main numArgs Nullary
-- 0
-- *Main numArgs Unary
-- 1
-- *Main numArgs Binary
-- 2

-- Stage 2 actually lists the types of the arguments
-- I'll use a seperate ADT to make the types concrete

data ArgTypes = JInt | JStr deriving (Show)

class ConcreteType t where makeAT :: t - ArgTypes

instance ConcreteType Int where makeAT _ = JInt
instance ConcreteType String where makeAT _ = JStr

class DescribeArgs s where descArgs :: s - [ArgTypes]

instance DescribeArgs TestType  where descArgs _ = []
instance ConcreteType a = DescribeArgs (a-TestType)
where descArgs _ = [makeAT (undefined::a)]
instance (ConcreteType a, ConcreteType b) =
   DescribeArgs (a-b-TestType)
where descArgs _ = [makeAT (undefined::a), makeAT (undefined::b)]

-- *Main descArgs Nullary
-- []
-- *Main descArgs Unary
-- [JInt]
-- *Main descArgs Binary
-- [JInt,JStr]
-- *Main descArgs OtherBinary
-- [JStr,JInt]

-- Stage 3 is just the Data.Typeable version of the stage 2

class DescribeArgs2 s where descArgs2 :: s - [TypeRep]

instance DescribeArgs2 TestType  where descArgs2 _ = []
instance Typeable a = DescribeArgs2 (a-TestType)
where descArgs2 _ = [typeOf (undefined::a)]
instance (Typeable a, Typeable b) =
   DescribeArgs2 (a-b-TestType)
where descArgs2 _ = [typeOf (undefined::a), typeOf (undefined::b)]

-- *Main descArgs2 Nullary
-- []
-- *Main descArgs2 Unary
-- [Int]
-- *Main descArgs2 Binary
-- [Int,[Char]]
-- *Main descArgs2 OtherBinary
-- [[Char],Int]


There are still some things this approach fails on: it can't give you a 
complete list of all constructors of TestType, for example. (Such a list 
would necessarily an existential type, like [exists x . DescribeArgs x 
- x]).


I'm sure my thoughts aren't original. Have other people taken this 
further into interesting directions? Where is the line beyond which you 
need 'true' metaprogramming?


Jules

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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont
With derive compiled and installed I thought I would change the code  
a bit and try it...


ghci -fth -v0 -e '$( _derive_print_instance makeFunParser  
Foo )' baz.hs


baz.hs:30:3: Not in scope: `a1'

Any help is appreciated!

Thanks, Joel

---

FunParser.hs:

module FunParser where

import Data.Derive
import Data.Derive.Peephole
import Data.List

import Text.ParserCombinators.Parsec ( CharParser )

makeFunParser = Derivation drv FunParser

drv dat@(DataDef name arity ctors) =
simple_instance FunParser dat [funN parse [ sclause [] body ] ]
where
  body = l1 choice $ lst [ clause con | con - ctors ]
  clause con = l1 reserved (lit (trim (ctorName con)))
   : args con (ctorArity con)
  trim = reverse . takeWhile (/= '.') . reverse
  args ct 0 = return' (ctp ct 'a')
  args ct k = l1 char (lit '(') : args' ct k 0
  args'  ct remn seen = l0 parse
=: (('a' : show seen)
  -: args'' ct (remn-1) (seen+1))
  args'' ct 0 seen = l1 char (lit ')') : return' (ctp ct 'a')
  args'' ct k seen = l1 char (lit ',') : args' ct k seen

class FunParser a
where parse :: CharParser s a


baz.hs:

import Text.ParserCombinators.Parsec hiding ( parse )
import qualified Text.ParserCombinators.Parsec.Token as T
import Text.ParserCombinators.Parsec.Language( emptyDef )
import Data.Derive.TH
import FunParser

data NumExpr
= Int Integer
| Num Double

instance FunParser NumExpr where
parse = numExpr

data Foo
= Foo NumExpr

lexer = T.makeTokenParser emptyDef

identifier = T.identifier lexer
reserved = T.reserved lexer
integer = T.integer lexer
float = T.float lexer

numExpr :: GenParser Char a NumExpr
numExpr =
choice [ integer = return . Int
   , float = return . Num
   ]

$( derive makeFunParser ''Foo )


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont

Here's the output from -ddump-splices (thanks Saizan for the tip).

It's returning a1 instead of a0.

ghci -fth -e '$( _derive_print_instance makeFunParser Foo )'  
baz.hs -ddump-splices

baz.hs:1:0:
baz.hs:1:0: Splicing declarations
derive makeFunParser 'Foo
  ==
baz.hs:30:3-28
instance {FunParser Main.Foo} where
[]
{ parse = choice
[()
   (reserved ['F', 'o', 'o'])
   (()
  (char '(') ((=) parse (\ a0 - ()  
(char ')') (return (Main.Foo a1)] }


baz.hs:30:3: Not in scope: `a1'

--
http://wagerlabs.com/





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


Re: Re[2]: [Haskell-cafe] `Expect'-like lazy reading/Parsec matching on TCP sockets

2007-04-05 Thread Scott Bell

Bulat,


yes, with both variants. actually, second one should be easier to
implement and understand. you should look into unsafeInterleaveIO
section of http://haskell.org/haskellwiki/IO_inside


This seems to do what I want, and unless I'm overlooking something
it feels very straight-forward:

hGetContentsTimeout :: Handle - Int - IO String
hGetContentsTimeout h t = do
 hSetBuffering stdin NoBuffering
 ready - hWaitForInput h t
 if (not ready) then return []
   else do
 c - hGetChar h
 s - unsafeInterleaveIO (hGetContentsTimeout h t)
 return (c:s)

This is not extensivly tested, but applying my parser to the string
returned by hGetContentsTimeout behaves precisely as I wanted:

It returns a match as soon as it is available, and fails if it is not
seen within t ms.

Thanks for your help!

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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Stefan O'Rear
On Thu, Apr 05, 2007 at 02:47:21PM +0100, Joel Reymont wrote:
 Here's the output from -ddump-splices (thanks Saizan for the tip).
 
 It's returning a1 instead of a0.
 
 ghci -fth -e '$( _derive_print_instance makeFunParser Foo )'  
 baz.hs -ddump-splices
 baz.hs:1:0:
 baz.hs:1:0: Splicing declarations
 derive makeFunParser 'Foo
   ==
 baz.hs:30:3-28
 instance {FunParser Main.Foo} where
 []
 { parse = choice
 [()
(reserved ['F', 'o', 'o'])
(()
   (char '(') ((=) parse (\ a0 - ()  
 (char ')') (return (Main.Foo a1)] }
 
 baz.hs:30:3: Not in scope: `a1'

Sorry for the late multiple reply, I just spent seven hours sleeping...

I am not the maintainer of Data.Derive, nor did I write the majority
of the nice code; Neil Mitchell did it, you can ask him why replace
DrIFT.  However, using abstract syntax trees WAS my idea. 

First, _derive_print_instance will never give you a TH splice error,
since it always evaluates to an empty list of declarations.  It uses
the TH 'runIO' facility such that type-checking a file using
_derive_print_instance will emit the instances to standard output as a
side effect.  So the error is coming from the $(derive) in baz.hs, if
you have more errors try commenting it out. (you'll get bogus code on
stdout, but at least it will be completly haskell!)

_derive_print_instance was not intended to be a debugging aid,
although it certainly works well in that capacity.  The intent is that
it will be used when the standalone driver is rewritten to use TH,
which I intend to do not long after I can (Neil is out of
communication for a week with intent to continue hacking Derive; I'm
taking this as a repository lock).

Yes, we do use type classes to implement recursion across types.  This
seems to be a very standard idiom in Haskell, used by Show, Read, Eq,
Ord, NFData, Arbitrary, and doubtless many more. 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What I learned from my first serious attempt low-level Haskell programming

2007-04-05 Thread Stefan O'Rear
On Thu, Apr 05, 2007 at 02:50:49PM +0400, Bulat Ziganshin wrote:
 Hello Stefan,
 
 Thursday, April 5, 2007, 3:11:31 AM, you wrote:
 
  2. Parameters are very expensive.
 
 you should look at the asm code GHC generates. afair parameters are
 kept in stack and copied on each call (to the same place!). such sort
 of things are also very dependent on backend used - was it a ASM or C
 one?

Yes, I will update the wiki.

ghc -O2, where

[EMAIL PROTECTED]:~$ ghc -V
The Glorious Glasgow Haskell Compilation System, version 6.7.20070402
[EMAIL PROTECTED]:~$ uname -a
Linux stefans 2.6.18-3-686 #1 SMP Sun Dec 10 19:37:06 UTC 2006 i686 GNU/Linux
[EMAIL PROTECTED]:~$ cpuid
 eax ineax  ebx  ecx  edx
 0002 756e6547 6c65746e 49656e69
0001 0f24 00010809  3febfbff
0002 665b5001   007b7040
8000 8004   
8001    
8002 20202020 20202020 20202020 6e492020
8003 286c6574 50202952 69746e65 52286d75
8004 20342029 20555043 30302e32 007a4847

Vendor ID: GenuineIntel; CPUID level 2

Intel-specific functions:
Version 0f24:
Type 0 - Original OEM
Family 15 - Pentium 4
Extended family 0
Model 2 - 
Stepping 4
Reserved 0

Brand index: 9 [not in table]
Extended brand string:   Intel(R) Pentium(R) 4 CPU 2.00GHz
CLFLUSH instruction cache line size: 8
Hyper threading siblings: 1

Feature flags 3febfbff:
FPUFloating Point Unit
VMEVirtual 8086 Mode Enhancements
DE Debugging Extensions
PSEPage Size Extensions
TSCTime Stamp Counter
MSRModel Specific Registers
PAEPhysical Address Extension
MCEMachine Check Exception
CX8COMPXCHG8B Instruction
APIC   On-chip Advanced Programmable Interrupt Controller present and enabled
SEPFast System Call
MTRR   Memory Type Range Registers
PGEPTE Global Flag
MCAMachine Check Architecture
CMOV   Conditional Move and Compare Instructions
FGPAT  Page Attribute Table
PSE-36 36-bit Page Size Extension
CLFSH  CFLUSH instruction
DS Debug store
ACPI   Thermal Monitor and Clock Ctrl
MMXMMX instruction set
FXSR   Fast FP/MMX Streaming SIMD Extensions save/restore
SSEStreaming SIMD Extensions instruction set
SSE2   SSE2 extensions
SS Self Snoop
HT Hyper Threading
TM Thermal monitor

TLB and cache info:
50: Instruction TLB: 4KB and 2MB or 4MB pages, 64 entries
5b: Data TLB: 4KB and 4MB pages, 64 entries
66: 1st-level data cache: 8KB, 4-way set assoc, 64 byte line size
40: No 2nd-level cache, or if 2nd-level cache exists, no 3rd-level cache
70: Trace cache: 12K-micro-op, 4-way set assoc
7b: 2nd-level cache: 512KB, 8-way set assoc, sectored, 64 byte line size


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


[Haskell-cafe] Parsing unordered parameter list with Parsec

2007-04-05 Thread Will Newton

Hi all,

I'm new to Haskell and trying to do some parsing with Parsec. It's
been extremely good so far. I have run into a problem I can't seem to
see the solution to though. I hope someone on the list can help me
out!

I have a command with a parameter list like this:

CMD PARAM1 foo PARAM2 100 PARAM3 200

Which is easy enough to parse, but it turns out the grammar is not
particularly well defined, and it's considered acceptable to swap
parameter order round pretty much arbitrarily. Is there a simple way
to handle this? I would like to only allow one of each parameter, some
parameters may also be optional.

It feels like I might have to write my own combinator to do this but
I'm not sure I'm quite ready of that yet!

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


Re: Re[2]: [Haskell-cafe] Tracking characters and a timestamp ?

2007-04-05 Thread Rich Neswold

On 4/5/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

you definitely should read http://haskell.org/haskellwiki/IO_inside


Thanks for mentioning this link -- I wasn't aware of it. I wish it
existed when I first started learning Haskell...

--
Rich

AIM : rnezzy
ICQ : 174908475
Jabber: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Stefan O'Rear
On Thu, Apr 05, 2007 at 03:19:15PM +0100, Joel Reymont wrote:
 numExpr :: GenParser Char a NumExpr
 numExpr =
 choice [ integer = return . Int
, float = return . Num
]

Parsec's choice operator works by parsing the first, and only parsing
the second if the first fails immediately.  So, given the input
123.456:

- Parsec parses 'integer = return . Int'
- this is successful - numExpr returns (Int 123, .456)
- we try to match . against ) and fail.

The fix is to left-factor the grammar, or just use the existing
factored choice operator:

 numExpr :: GenParser Char a NumExpr
 numExpr = do sg - lexeme sign
  nf - natOrFloat
  return $ either (Int . sg) (Nat . sg) nf

It seems silly that there is no signed version of natOrFloat
predefined, any Parsec experts? 

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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread Joel Reymont

Shouldn't this work just as well?

numExpr =
choice [ try $ float = return . Num
   , integer = return . Int
   ]

It works on Foo(10.345) but not on Bar(10, 103.34).

On Apr 5, 2007, at 4:09 PM, Stefan O'Rear wrote:


numExpr :: GenParser Char a NumExpr
numExpr = do sg - lexeme sign
 nf - natOrFloat
 return $ either (Int . sg) (Nat . sg) nf


It seems silly that there is no signed version of natOrFloat
predefined, any Parsec experts?

Stefan


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Automatic derivation (TemplateHaskell?)

2007-04-05 Thread John Meacham
On Wed, Apr 04, 2007 at 04:48:56PM -0700, Stefan O'Rear wrote:
 Data.Derive can do this.  In an attempt to avoid munging the relevent
 files they are attached. 

You might want to note that DrIFT used to be called derive before it
(amicably) changed its name due to a conflict with a product
of the same name.

John
-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Short-circuiting a fold

2007-04-05 Thread David House

On 05/04/07, Kurt Hutchinson [EMAIL PROTECTED] wrote:

Straightforward:
 ssfold p f z = head . dropWhile ( not . p ) . scanl f z


I'd prefer find instead of head . dropWhile (not . p), making the
result type a Maybe, as this is essentially equivalent to searching
through the result of a scan for a specific value, so it should follow
find's example and use Maybe for its partiality.


I want to see some real creativity here, so pull out all the stops.


You may also be interested in the Compose experiment [1]: a bit of fun
seeing how many different ways compose :: [a - a] -(a - a) could be
defined. Most are quite silly, but the solution involving the State
monad, for example, is really quite elegant.

[1]: http://haskell.org/haskellwiki/Compose

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


Re: [Haskell-cafe] Short-circuiting a fold

2007-04-05 Thread Stefan O'Rear
On Thu, Apr 05, 2007 at 02:09:12PM -0400, Kurt Hutchinson wrote:
 Here's a bit of Thursday afternoon fun.
 
 Mission:
 Define ssfold, a short-circuiting fold. It evaluates to the folded
 value that first satisfies the given predicate.
 ssfold :: ( a - Bool ) - ( a - b - a ) - a - [b] - a
 
 Here are two of mine.
 
 Straightforward:
 ssfold p f z = head . dropWhile ( not . p ) . scanl f z
 
 Monadic:
 data Done a b = Done { undone :: a } | NotDone b
 instance Monad ( Done a ) where
 ( NotDone i ) = f = f i
 ( Doner ) = _ = Done r
 return = NotDone
 
 ssfold p f z = undone . foldM (\ v e - if p v then Done v else NotDone ( 
 f v e ) ) z


ssfold p f z = fromJust . find p . scanl f z

-- might need a few (safe) unsafeCoerce#s
ssfold p f z = go . (z:) where
 go (x:xs) | p x = x
   | otherwise = case xs of (xx:xxs) - go (f x xx:xxs)

ssfold p f z = go z where
 go a xs | xs `seq` p a = a
 | otherwise = case xs of (xx:xxs) - go (f x xx) xxs

ssfold p f z = foldr go (\k - if p k then k else undefined) where
 go ths cont acc | p acc = acc
 | otherwise = cont (f acc ths)

data Exit = Exit Any deriving Typeable
ssfold p f z l = unsafePerformIO $ catchDyn (evaluate (go l z)) (\ (Exit a) - 
return $ unsafeCoerce# a)
 where go l ac | p ac = throwDyn (Exit (unsafeCoerce# ac))
   go (x:xs) ac = go xs (f ac x)


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


[Haskell-cafe] Re: [web-devel] A light-weight web framework

2007-04-05 Thread Ricardo Herrmann

The maintenance nightmare happens when someone uses the embedded language to
specify business logic, and that's entirely the web-{developer,designer}'s
fault. Thus, the problem is not that these languages shouldn't be powerful
enough.

IMHO, a safe approach would be simply not allowing I/O inside templates
(hey, sounds familiar ;-)

On 4/5/07, Maurice Codik [EMAIL PROTECTED] wrote:


A few things, some of which I sort of mentioned in my previous email:

- If I'm already going to commit some time to learn a templating language,
why dont I just spend that same amount of time learning the little bit of
haskell I need to make the template work? If thats too much to ask, I can
just spit out HTML, and have the programmer put in the dynamic parts for me.
Both of these scenarios seem to be a more efficient use of time.

- Who is the target audience? If its a big organization where there are
multiple designers and multiple devs, then your approach may work just fine.
If its the single developer, then something like what David suggested would
work even better. If its a small team (which may or may not include a
full-time designer), then something like what I suggested would work best.
For a web framework for haskell, I would guess that the latter two are much
more likely.

- Embedding a real programming language in a template already gives you
power to do what ever you need to do. What if you need to implement some
logic that the template language doesnt support? In those cases, you're
usually out of luck and have to move that logic into a controller, where it
doesnt really belong (assuming its actual display logic, not business
logic).

- It's really just a matter of taste. Any web framework thats worth using
should be flexible in its support of view technologies, but come with one
thats a sensible default.

Maurice

On 4/5/07, Joel Reymont [EMAIL PROTECTED] wrote:

 Do you see anything wrong with the approach I suggested, though?

 On Apr 5, 2007, at 6:16 PM, Maurice Codik wrote:

  That's not necesarily true. Templates where there is mostly markup,
  but let you embed code into them using special tags (ex, % code %
  ) are extremely popular and work fairly well. They also keep the
  template language simple because there is already a full-powered
  programming language thats embedded into it. Good examples of this
  method are ERB templates in Rails, JSPs, Perl Mason templates, etc.

 --
 http://wagerlabs.com/








--
http://blog.mauricecodik.com
___
web-devel mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/web-devel





--
Ricardo Guimarães Herrmann
Any sufficiently complicated C or Fortran program contains an ad hoc,
informally specified, bug-ridden, slow implementation of half of Common
Lisp
Any sufficiently complicated Lisp or Ruby program contains an ad hoc,
informally-specified, bug-ridden, slow implementation of half of Haskell
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: What I learned from my first serious attempt low-level Haskell programming

2007-04-05 Thread Lennart Augustsson
It's not that hard to figure out an order to permute the arguments on  
the stack before a tail call that minimizes that number of moves and  
temporary locations.  Lmlc did this 20 years ago. :)


-- Lennart

On Apr 5, 2007, at 19:17 , Claus Reinke wrote:


Stefan O'Rear wrote:
 2. Parameters are very expensive.  Our type of functions that build
(ignoring CPS for the time being) was MBA# - Int# -  
[ByteString],
where the Int# is the current write pointer.  Adding an extra  
Int#

to cache the size of the array (rather than calling sMBA# each
time) slowed the code down ~2x.  Conversely, moving the write
pointer into the byte array (storing it in bytes 0#, 1#, 2#, and
3#) sped the code by 4x.
If you were measuring on x86 then parameters are passed on the  
stack, which may be expensive.  On x86_64 the first 3 arguments  
are passed in registers, which is usually a win, but if the  
function immediately does an eval they need to be saved on the  
stack anyway.  Still, 4x sounds like a lot, perhaps you managed to  
avoid a stack check in the inner loop or something.


just out of curiosity: what does GHC do with stack parameters in  
loops/tail calls?


there tends to be a conflict as the old set of parameters is needed  
to build the new
one for the recursive call/next loop iteration, while one wants to  
get rid of the old set before doing the call. unless one keeps the  
parameter frames away from the stack,
or can figure out a safe order in which to overwrite the parameters  
in the frame,
that seems to imply some copying, even though that may be cheap for  
few/small

parameters per frame.

many years ago, i saw an abstract machine and RISC processor design  
aiming for good fp support that used two parameter stacks instead  
of one for just this reason.


instead of moving stack frames around on a single stack, parameters  
were read
from one stack, and built up on the other, followed by a cheap  
stack switch before

the call. perhaps something like this might be of use here, too?

claus


___
Libraries mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/libraries


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


Re: [Haskell-cafe] ANN: Atom - Yet another Haskell HDL

2007-04-05 Thread Lennart Augustsson

It's great to see the Bluespec ideas cast in Haskell syntax again.
Bluspec Inc has strayed from that path, I'm afraid.

-- Lennart

On Apr 4, 2007, at 05:18 , Tom Hawkins wrote:


Hi,

Haskell has a rich history of embedded hardware description languages.
Here's one more for the list.

Inspired by the work of Arvind, Hoe, and all the sharp folks at
Bluespec, Atom is a small HDL that compiles conditional term rewriting
systems down to Verilog RTL.  In Atom, a circuit description is
composed of a set of state elements (registers) and a set of rules.
Each rule has two components: an enabling condition and a collection
of actions, or state updates.  When a rule is enabled, it's actions
may be selected to execute atomically.  In contrast to Verilog
always blocks, multiple rules can write to the same state element.

Here's an enabled counter in Atom:

counter :: Int - Signal - System Signal
counter width enable = do
 count - reg count width 0
 rule updateCount $ do
   when enable
   count == value count +. one width
 return $ value count

Enjoy!

 http://funhdl.org/

-Tom


A few details:  The Atom compiler attempts to maximize the number of
rules that can execute in a given clock cycle without breaking the
semantics of one-rule-at-a-time.  For simplicity, rules are assigned
a global, linear priority.  Data dependencies between rules form a
graph.  A acyclic graph is ideal, because all rules become
sequentially composable.  The compiler attempts to order the rules
to minimize the number of edges feeding back from lower to higher
priority rules.  This is equivalent to the feedback arc set problem.
(Atom's FAS optimization is pretty poor at the moment.)

In a rule-data dependency graph, many of the edges are irrelevent
because pairs of rules are often mutually exclusive, ie. can not be
enabled at the same time.  MiniSat is used to hunt and prune edges
from mutually exclusive rules.  By only looking back to primary inputs
and registers, the SAT procedure is not guaranteed to find all
mutually exclusive rules, but it does a pretty good job.
___
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