2008/7/10 Ron Alford <[EMAIL PROTECTED]>:
> Ok, I'm closer, but I'm running into a problem with typeOf and lists,
> of all things:
> *WouterTest> typeOf (eVar "v" :: TermExpr)
> Planning.Wouter.Expr (Planning.Wouter.:+: WouterTest.Const WouterTest.Var)
> *WouterTest> typeOf ([eVar "v"] :: [TermExpr
On Thu, 10 Jul 2008, Don Stewart wrote:
thomas.dubuisson:
I could try GHC's new debugger. But my experiences with it so far have
shown that for all but the most trivial programs possible, it becomes
intractably difficult to figure out what the debugger is actually
showing you.
At times I thi
thomas.dubuisson:
> > I could try GHC's new debugger. But my experiences with it so far have
> > shown that for all but the most trivial programs possible, it becomes
> > intractably difficult to figure out what the debugger is actually
> > showing you.
>
> At times I think of ghcid as the ant
Ok, I'm closer, but I'm running into a problem with typeOf and lists,
of all things:
*WouterTest> typeOf (eVar "v" :: TermExpr)
Planning.Wouter.Expr (Planning.Wouter.:+: WouterTest.Const WouterTest.Var)
*WouterTest> typeOf ([eVar "v"] :: [TermExpr])
*** Exception: Prelude.undefined
I'm pretty sure
> I could try GHC's new debugger. But my experiences with it so far have
> shown that for all but the most trivial programs possible, it becomes
> intractably difficult to figure out what the debugger is actually
> showing you.
GDB is to C as
(a) GHCi debugger :: Haskell
(b) Pigs :: Farmers
(
On Thu, 2008-07-10 at 16:52 -0700, Don Stewart wrote:
> Well, they're radically different graph representations, and fgl
> hasn't been designed for large graphs.
Do you know if King and Launchbury's implementation (Data.Graph) scales
better?
> What C library is Ruby's binding to? It might be quit
andre:
> On Thu, 2008-07-10 at 18:32 -0400, Ronald Guida wrote:
> > Your ratios are about 1 : 3 : 8.
> > That pretty close to quadratic growth, 1 : 4 : 9, so I think all is well.
>
> Maybe, but 96MB of resident memory for a 1000-node graph looks bad,
> especially considering p is low. Is the inter
On Thu, 2008-07-10 at 18:32 -0400, Ronald Guida wrote:
> Your ratios are about 1 : 3 : 8.
> That pretty close to quadratic growth, 1 : 4 : 9, so I think all is well.
Maybe, but 96MB of resident memory for a 1000-node graph looks bad,
especially considering p is low. Is the internal representation
On 2008 Jul 10, at 14:00, Eric wrote:
I have downloaded cabal and am trying to install it but have gotten
the
following error message:
C:\cabal\cabal-install-0.5.1>runghc Setup configure
Cabal itself is a special case; you need the same version of Cabal
already installed to install it vi
This is a bit similar to Either. Is there a way to see the generated
instance code for
deriving instance Data Either ?
On Thu, Jul 10, 2008 at 6:38 PM, Ron Alford <[EMAIL PROTECTED]> wrote:
> Close - it compiles now! I made a minor change, going to Typeable1
> instead of Typeable:
>
> instance (
Close - it compiles now! I made a minor change, going to Typeable1
instead of Typeable:
instance (Typeable1 f, Typeable1 g) => Typeable1 (f :+: g) where
typeOf1 l@(Inl x) = mkTyConApp (mkTyCon "Planning.Wouter.:+:")
[typeOf1 x, typeOf1 y]
where (Inr y) = undefined `asTypeOf` l
typ
On Thu, Jul 10, 2008 at 4:57 PM, Andre Nathan <[EMAIL PROTECTED]> wrote:
> Hello
>
> I'm trying to create a directed graph using the Data.Graph.Inductive.
> The graph is a random graph using the G(n, p) model, that is, each of
> the n nodes is linked to every other node with probability p.
So the
Hello
I'm trying to create a directed graph using the Data.Graph.Inductive.
The graph is a random graph using the G(n, p) model, that is, each of
the n nodes is linked to every other node with probability p.
I'm seeing a large increase of memory usage when n grows (this is using
p = 0.1):
n = 10
Hello,
I am not sure about the full answer to your qusetion, but I do know
that template haskell support in haskell-src-exts is currently broken,
but supposedly easy to fix. Not sure if that will give you the
features you need or not though.
From this thread:
http://groups.google.com/group/haske
On Thu, Jul 10, 2008 at 2:15 PM, Ron Alford <[EMAIL PROTECTED]> wrote:
> I'm making progress, but how would I make the following a Typeable instance:
> data (f :+: g) e = Inl (f e) | Inr (g e) deriving Eq
>
> Here is what I'm using for Expr:
> data Expr f = In (f (Expr f))
> instance Typeable1 f =>
Hi,
Can one represent the ''Type template Haskell syntax of
$( makeMergeable ''FileDescriptorProto )
in haskell-src.exts Language.Haskell.Exts.Syntax ?
And what are the HsReify data (e.g. HsReifyType and HsReifyDecl and
HsReifyFixity )?
I don't see any pretty print capability to produce th
Hi
> > Did you do the runhaskell Setup configure && runhaskell Setup build &&
> > runhaskell Setup install?
>
> I used 'sudo cabal install derive'. I did find the binary - in my
> user's .cabal/bin directory! Odd that it should default to that when
> run as root.
I think if you pass --globa
On 10 Jul 2008, at 21:25, Ron Alford wrote:
On Thu, Jul 10, 2008 at 3:18 PM, Neil Mitchell
<[EMAIL PROTECTED]> wrote:
Hi Ron,
I'm using GHC 6.8.3 with $ cabal --version
cabal-install version 0.5.1
using version 1.4.0.1 of the Cabal library
I installed Data.Derive from hackage, only to be u
On Thu, Jul 10, 2008 at 3:18 PM, Neil Mitchell <[EMAIL PROTECTED]> wrote:
> Hi Ron,
>
>> I'm using GHC 6.8.3 with $ cabal --version
>> cabal-install version 0.5.1
>> using version 1.4.0.1 of the Cabal library
>>
>> I installed Data.Derive from hackage, only to be unable to find the
>> 'derive'
I have a similar piece of code at http://code.haskell.org/gmap/serial/
which is fairly well tested. It currently only outputs lists of words
but its based on Data.Binary so it should be fairly easy to get
bytestrings out it (bytestrings worked up till 2-3 weeks ago, I just
havent bothered to keep t
Hi Ron,
> I'm using GHC 6.8.3 with $ cabal --version
> cabal-install version 0.5.1
> using version 1.4.0.1 of the Cabal library
>
> I installed Data.Derive from hackage, only to be unable to find the
> 'derive' binary!
Did you do the runhaskell Setup configure && runhaskell Setup build &&
run
I'm making progress, but how would I make the following a Typeable instance:
data (f :+: g) e = Inl (f e) | Inr (g e) deriving Eq
Here is what I'm using for Expr:
data Expr f = In (f (Expr f))
instance Typeable1 f => Typeable (Expr f) where
typeOf (In x) = mkTyConApp (mkTyCon "Data.Trie.Genera
I'm using GHC 6.8.3 with $ cabal --version
cabal-install version 0.5.1
using version 1.4.0.1 of the Cabal library
I installed Data.Derive from hackage, only to be unable to find the
'derive' binary!
Trying it directly from darcs, I get:
$ ghc --make Setup.hs
[1 of 1] Compiling Main (
Two questions. How often does the array change, and how big does it
get? It may well be that you just copy it and take the hit, as
that'll be cheaper (even in C, incidentally) than any other solution,
if it's a short array or if the updates happen rarely.
If not, try using Data.Array.Diff and re
andrewcoppin:
> I could try GHC's new debugger. But my experiences with it so far have
> shown that for all but the most trivial programs possible, it becomes
> intractably difficult to figure out what the debugger is actually
> showing you. I actually tried to debug a "normal" LZW implementatio
On Thu, 10 July 2008, Marco Túlio Gontijo e Silva wrote:
> how do I unbox a existential quantificated data type?
Dan Doel wrote:
>elim :: L a -> (forall l. l a -> r) -> r
>elim (L e) f = f e
Just one catch: You can't actually write a function 'f' of type
(forall l. l a -> r) without knowi
OK, so I just spent an entire day trying to write some code, and after
hours of struggling I have something that's semi-working but very ugly
and rather unreliable. My usual guideline for Haskell programming is "if
it seems hard, you're doing it wrong"...
After many hours of effort, I came up
On Thursday 10 July 2008, Marco Túlio Gontijo e Silva wrote:
> Hello,
>
> how do I unbox a existential quantificated data type?
>
> > {-# LANGUAGE ExistentialQuantification #-}
> > data L a = forall l. L (l a)
> > unboxL (L l) = l
>
> is giving me, in GHC:
>
> Inferred type is less polymorphic
Hello Eric.
Em Qui, 2008-07-10 às 19:00 +0100, Eric escreveu:
> C:\cabal\cabal-install-0.5.1>runghc Setup configure
> Configuring cabal-install-0.5.1...
> Setup: At least the following dependencies are missing
> Cabal >=1.4&&<1.5, HTTP >=3000&&<3002, zlib >=0.4
>
> I'm not sure from this mess
eeoam:
> Dear all,
>
> I have downloaded cabal and am trying to install it but have gotten the
> following error message:
>
> C:\cabal\cabal-install-0.5.1>runghc Setup configure
> Configuring cabal-install-0.5.1...
> Setup: At least the following dependencies are missing
>Cabal >=1.4&&<1.5, H
jonathanccast:
> On Thu, 2008-07-10 at 03:16 -0700, Grzegorz Chrupala wrote:
> > Hi all,
> >
> > Is there a less ugly way of avoiding laziness in the code pasted below then
> > the use of seq in the last line?
> > The program is supposed to split a large input file into chunks and check in
> > how
On Thu, 2008-07-10 at 14:53 -0300, Marco Túlio Gontijo e Silva wrote:
> Hello,
>
> how do I unbox a existential quantificated data type?
You can't. You have to use case analysis:
case foo of
L l ->
where none of the information your case analysis discovers about the
actual type of l can
Dear all,
I have downloaded cabal and am trying to install it but have gotten the
following error message:
C:\cabal\cabal-install-0.5.1>runghc Setup configure
Configuring cabal-install-0.5.1...
Setup: At least the following dependencies are missing
Cabal >=1.4&&<1.5, HTTP >=3000&&<3002, zlib
Hello,
how do I unbox a existential quantificated data type?
> {-# LANGUAGE ExistentialQuantification #-}
> data L a = forall l. L (l a)
> unboxL (L l) = l
is giving me, in GHC:
Inferred type is less polymorphic than expected
Quantified type variable `l' escapes
When checking an e
On Thu, 2008-07-10 at 03:16 -0700, Grzegorz Chrupala wrote:
> Hi all,
>
> Is there a less ugly way of avoiding laziness in the code pasted below then
> the use of seq in the last line?
> The program is supposed to split a large input file into chunks and check in
> how many of those chunks each of
2008/7/9 Mitar <[EMAIL PROTECTED]>:
>
> And it took 15 s. And also the profiling was like I would anticipate.
> Calculating points coordinates and checking spheres takes almost all
> time.
>
> So any suggestions how could I build a list of objects to check at
> runtime and still have this third pe
2008/7/10 Dmitri O.Kondratiev <[EMAIL PROTECTED]>:
> allows construct an array of a fixed size. How to add more elements to the
> array later?
I can't really answer your question, however I bet that it would
require allocating another, bigger array and copying the old elements
over, at least from
What is the best way to extend array?
I would use a list instead of array as it is easy to append, but need to
have random access to its elements later.
So in fact I need to start with an integer array of size 1. Next I may need
to add new elements to this array or modify values of the existing one
I figured it out, but it's not pretty. The problem is that the eof
parser had no awareness of the showTok function. To fix the problem, I
had to replace eof with its definition in terms of notFollowedBy, then
replace notFollowedBy with its definition in terms of try and
unexpected. Then, I chan
Or, if people have easy-enough extensible records that /will/ work
with funky types, I'd be happy to use those!
-Ron
On Thu, Jul 10, 2008 at 10:29 AM, Ron Alford <[EMAIL PROTECTED]> wrote:
> On Wed, Jul 9, 2008 at 11:01 PM, Antoine Latter <[EMAIL PROTECTED]> wrote:
>>
>> It isn't immediately obvi
On Wed, Jul 9, 2008 at 11:01 PM, Antoine Latter <[EMAIL PROTECTED]> wrote:
>
> It isn't immediately obvious to me that the "Typeable" family of
> classes deal at all with higher-kinded type constructors, but I didn't
> look that hard.
>
Yes, that's what I'm worried about. For people's fun and amu
On Wed, Jul 09, 2008 at 11:05:47PM -0400, Ronald Guida wrote:
> Question: If I can't change my function f (in this case, accumulator),
> then is it possible to get the effect I want without having to resort
> to "unsafeInterleaveIO"?
Here's a possibility; you may or may not like it.
module Main
Hi Marc,
> The Chalmers Lava homepage tells abouta Xilinx version which should
> be merged in soon. But on the xilinx homepage there was no reference
> to neither Lava nor haskell..
> I'm thinking about designing a similar tool to www.combimouse.com.
you also might consider using a PIC or some su
Hi all,
Op Thursday 10 July 2008 12:16:25 schreef Grzegorz Chrupala:
> Is there a less ugly way of avoiding laziness in the code pasted below then
> the use of seq in the last line?
You could replace the list dfs' with a strict list type, like:
data StrictList a = Cons !a !(StrictList a) | Nil
Hi all,
Is there a less ugly way of avoiding laziness in the code pasted below then
the use of seq in the last line?
The program is supposed to split a large input file into chunks and check in
how many of those chunks each of a list of words appear, as well as the
total number of chunks. Without
Hi Ryan,
Please see below.
Vasili
On Wed, Jul 9, 2008 at 4:03 AM, Ryan Ingram <[EMAIL PROTECTED]> wrote:
> Try {-# LANGUAGE RankNTypes #-}?
[EMAIL PROTECTED]:~/FTP/Haskell/hsql-1.7$ runhaskell Setup.lhs build
Preprocessing library hsql-1.7...
Building hsql-1.7...
[1 of 2] Compiling D
Hi folks,
I'm using Parsec to parse a stream of tokens. The token primitive takes,
among other arguments, a function to print tokens. However, this
function is not always applied. Try the code below:
-
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Pos(newPo
47 matches
Mail list logo