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.
Ins
Hi
Sorry for the late multiple reply, I just spent seven hours sleeping...
And ditto for my delayed reply - I've just spent 9 hours in a car on a
motorway :)
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 rep
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. Parame
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
> import Control.Monad
> import Control.Monad.Instances
foldr is The One True Fold:
> ssfold :: (a -> Bool) -> (a -> b -> a) -> a -> [b] -> a
> ssfold p f a0 xs = foldr (\x xs a -> if p a then a else xs (f a x)) id xs a0
pointfree obfuscated:
> if' True x _ = x
> if' __ y = y
> ssfold'
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 -> [
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 f
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#
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 . dro
John Meacham wrote:
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.
DrIFT might consider changing back, since TI has now officially stopped
support for said product [1].
Jacques
[1]
http://
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 th
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
On Thu, Apr 05, 2007 at 03:50:26PM +0100, Will Newton wrote:
> 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 h
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
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 PRO
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 PA
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 sam
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:
Here's a complete working example. There seems to be an error in the
parser but everything is derived fine.
*Main> run fooParser "Foo(10)"
Foo (Int 10)
*Main> run fooParser "Foo(10.5)"
parse error at (line 1, column 7):
unexpected "."
expecting digit or ")"
FunParser.hs:
Replace "show seen" w
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:
hGe
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
==>
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
Hi all,
does anyone know about any Haskell implementation for .NET platform
with published performance results?
Thanks in advance,
--
__
Monique Monteiro, MSc
MCP .NET Framework 2.0 / SCJP / IBM OOAD
http://www.cin.ufpe.br/~mlbm
http://th
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
r
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,Lo
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.Der
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 ne
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
> i
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 p
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/ha
Hello Joel,
Thursday, April 5, 2007, 12:25:39 PM, you wrote:
> Data.Derive is a most awesome piece of code!
> Is there soemething in DrIFT that you did not like that made you
> write it?
my TH experience says that it is very hard to write code using it, and
using DrIFT doesn't look easy too.
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 Gen
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
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 th
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,
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-
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 d
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
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
This approach is fleshed out at
http://groups.google.de/group/fa.haskell/browse_thread/thread/ceabae2c3fdc8abc/814a86d89c3f7d28?lnk=st&q=tphyahoo+haskell+ubuntu&rnum=1&hl=en#814a86d89c3f7d28
2007/3/16, Chad Scherrer <[EMAIL PROTECTED]>:
Brian,
I had this exact problem, and I found this approac
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
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,
Bulat
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 atta
| 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.
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#
45 matches
Mail list logo