Thanks, at least the title looks like exactly what I've been looking
for, however I cannot quickly appreciate the notation-heavy contents:
I definitely will as soon as possible.
2009/5/20 Masahiro Sakai :
> From: Eugene Kirpichov
> Date: Sun, 17 May 2009 23:10:12 +0400
>
>> Is there any research
Thanks for the thorough response.
I've found Barras&Bernardo's work (at least, slides) about ICC*, I'll
have a look at it.
Could you provide with names of works by Altenkirch/Morris/Oury/you?
The unordered pair example was especially interesting, since I am
somewhat concerned with which operations
Hi,
I've been writing some code to calculate the stretch factor of a tree
of points. What it means is that for every node in a tree (lets call
it 'pivot'), I have to traverse the same tree (lets call each node
'current') and sum d_t(pivot, current) / d(pivot, current) for each
node, where
I've opened a ticket for this
(http://hackage.haskell.org/trac/ghc/ticket/3245), but someone else
will have to do the investigation into the problem.
Michael D. Adams
On Thu, May 14, 2009 at 10:59 AM, Simon Peyton-Jones
wrote:
> Interesting. Would anyone care to make a Trac ticket for this (wit
2009/5/20 Bernie Pope :
> Oh right. I didn't see your proposal (did it get sent to the list?).
Yes, I just push the Replay button, not the
> Sorry for the confusion.
It's my fault, sorry.
lee
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http
On Wed, May 20, 2009 at 3:40 AM, z_a...@163.com wrote:
> Hi, friends
>
> rollDice :: Word8 -> IO Word8
> rollDice n = do
> bracket (openFile "/dev/random" ReadMode) (hClose)
> (\hd -> do v <- fmap B.unpack (B.hGet hd 1)
> let v1 = Data.List.head v
> retu
On May 19, 2009, at 10:20 , Chaddaï Fouché wrote:
On Tue, May 19, 2009 at 8:46 AM, Brandon S. Allbery KF8NH
wrote:
On May 19, 2009, at 01:42 , Jason Dagit wrote:
I've often seen this bit of scary code in VB:
Dim i as Integer = 5
If i = "5" Then
' Do something, because 5 = "5"
End If
Sure, t
2009/5/20 z_a...@163.com :
> Hi, friends
>
> rollDice :: Word8 -> IO Word8
> rollDice n = do
> bracket (openFile "/dev/random" ReadMode) (hClose)
> (\hd -> do v <- fmap B.unpack (B.hGet hd 1)
> let v1 = Data.List.head v
> return $ (v1 `mod` n) + 1)
>
Not exactly São Carlos: São Paulo - SP.
On Tue, May 19, 2009 at 09:28:55PM -0300, Maurício wrote:
> Anybody else around here?
>
> Best,
> Maurício
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/h
On Wed, May 20, 2009 at 08:40:15AM +0800, z_a...@163.com wrote:
> I know "length [1..33]" is Int not Word8, but Word8 is enough here.
Just saying '33' is enough here. :)
--
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskel
Hi, friends
rollDice :: Word8 -> IO Word8
rollDice n = do
bracket (openFile "/dev/random" ReadMode) (hClose)
(\hd -> do v <- fmap B.unpack (B.hGet hd 1)
let v1 = Data.List.head v
return $ (v1 `mod` n) + 1)
.
blueIdx <- rollDice $ length [1..33]
Anybody else around here?
Best,
Maurício
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi Ryan,
I'm afraid you've lost me. Maybe if you showed how this would be used in ML I
would get the picture.
Michael
--- On Tue, 5/19/09, Ryan Ingram wrote:
From: Ryan Ingram
Subject: Re: [Haskell-cafe] showing a user defined type
To: "michael rice"
Cc: "Brandon S. Allbery KF8NH" , haskell
From: Eugene Kirpichov
Date: Sun, 17 May 2009 23:10:12 +0400
> Is there any research on applying free theorems / parametricity to
> type systems more complex than System F; namely, Fomega, or calculus
> of constructions and alike?
You may be interested in this:
"The Theory of Parametricity in La
Hi Kenneth,
I wrote a benchmark similar to yours using the haskell blas library I
wrote (latest version is on github at http://github.com/patperry/blas/tree/master
, an older version is on hackage).
The pure Haskell implementation is not very good, and the problem
seems to be repeated boxi
This new version of atom adds an array datatype (A a), which has
helped us shrink and speed up the embedded code in our application.
Enjoy!
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/atom
-Tom
___
Haskell-Cafe mailing list
Haskell-Cafe@h
Hi,
I have ghc 6.10.1 and gtk2hs 0.10.0 installed on my windows vista
computer. Both were installed using the installer on the webpages.
I am able to use gtk, glade etc but not sourceview or cairo. If I
compile the examples in the gtk2hs example folder, I get "not in
scope" error messages for fun
David Leimbach wrote:
> main = interact (unlines . lines)
> This *appears* to somewhat reliably get me functionality that looks like
> take a line of input, and print it out.
>
> Is this behavior something I can rely on working?
>
> I like the idea that lines can pull lines lazily from "getConten
On Tue, May 19, 2009 at 7:07 AM, michael rice wrote:
> A little further along in "The Little MLer" the ints function is replaced by
> other functions like primes and fibs, which also return Links:
>
> fun primes(n)
> = if is_prime(n+1)
> then Link(n+1,primes)
> else primes(n+1)
>
> fun fibs(n)
2009/05/19 David Leimbach :
> ...I'm concerned that relying on a pure function like
> "unlines . lines" to sequence IO is a bit too implicit in nature.
You aren't relying on `unlines . lines` to do the sequencing;
you're relying on them to process a string. That the
characters of the string
main = interact (unlines . lines)
This *appears* to somewhat reliably get me functionality that looks like
take a line of input, and print it out.
Is this behavior something I can rely on working?
I like the idea that lines can pull lines lazily from "getContents" which
lazily consume the input.
michael rice wrote on 19.05.2009 18:16:
Cool!
Is there *anything* Haskell *can't* do?
Well, I haven't found a way to emulate polymorphics kinds yet, and I feel like
I need them. Other than than - probably no.
Michael
--- On *Mon, 5/18/09, David Menendez //* wrote:
From: David Men
Hi Justin,
I updated my changes to apply against that repo, thanks for
the pointer. Cool to see new changes to haskelldb, especially
all the new unit tests!
You can find my updated repo at:
http://patch-tag.com/r/haskelldb-hlist
Re-reading your email now, I see you asked for a patch, but
On Tue, May 19, 2009 at 8:46 AM, Brandon S. Allbery KF8NH
wrote:
> On May 19, 2009, at 01:42 , Jason Dagit wrote:
>>
>> I've often seen this bit of scary code in VB:
>> Dim i as Integer = 5
>> If i = "5" Then
>> ' Do something, because 5 = "5"
>> End If
>
> Sure, that works in Perl too.
That's b
Cool!
Is there *anything* Haskell *can't* do?
Michael
--- On Mon, 5/18/09, David Menendez wrote:
From: David Menendez
Subject: Re: [Haskell-cafe] showing a user defined type
To: "Ryan Ingram"
Cc: haskell-cafe@haskell.org
Date: Monday, May 18, 2009, 10:26 PM
On Mon, May 18, 2009 at 10:02 PM,
Thanks.
I had put together something similar to your first suggestion but tried to use
PutStrLn(Show...). I'd also thought of your second suggestion about a dummy
show for functions.
A little further along in "The Little MLer" the ints function is replaced by
other functions like primes and fi
On May 19, 2009, at 13:24 , Daniel Schüssler wrote:
Hello!
On Monday 18 May 2009 14:37:51 Kenneth Hoste wrote:
I'm mostly interested in the range 10D to 100D
is the dimension known at compile-time? Then you could consider
Template
Haskell.
In general, no. :-)
It will be known for some
Hello,
2009/5/19 leledumbo :
>> expression ::= term | term "+" expression
>> term ::= factor | factor "*" term
>> factor ::= constant | variable | "(" expression ")"
>
> Oh, left recursion. Well, it should be easy to transform:
>
> expression ::= term | moreTerm
> term ::= factor | moreFactor
> mo
Hi,
meh, I just realised that there is no sensible way to actually
introduce/eliminate the generated types. I'm attaching a revised version with
fromList/toList functions. Maybe the vector type should be polymorphic and be
an instance of Functor, Monad and Foldable? But then we really depend on
I understand from your later post that is was in fact specialized, but
how do I make sure it _is_ specialized?
-ddump-tc seems to give the generalized type, so it seems you'd need
to look at the -ddump-simpl output if you want to know whether a
local function is specialized.
http://www.haskell
Hello!
On Monday 18 May 2009 14:37:51 Kenneth Hoste wrote:
> I'm mostly interested in the range 10D to 100D
is the dimension known at compile-time? Then you could consider Template
Haskell. I wrote up some code for generating the vector types and vector
subtraction/inner product below, HTH. One
I hope you're right. 7 pages... 1-2 nights should be enough. Thanks for all.
--
View this message in context:
http://www.nabble.com/Expression-parsing-problem-tp23610457p23614011.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
__
> Surely you didn't read my original post, do you? I have a very limited
> knowledge of Monad and I try to find a solution using my current skills
> because the due date is within two weeks. Therefore, I don't think I can
> create a Monadic parser for this.
I think you're giving up way too easily.
These QuickCheck properties don't really test your sort function.
The `a' type variable will be instantiated to ().
So you will test with lists of units, like so:
ghci> quickCheck (\xs -> isSorted (reverse xs))
OK, passed 100 tests.
This can be simply solved by added a more specific type signatu
Am Samstag, 16. Mai 2009 16:18 schrieb Günther Schmidt:
> Hi all,
>
> In my app, there is one part which has a rather complicated GUI logic,
> it involves n drop downs with n choices each.
>
> Whenever the current selection in one of the drop downs changes by user
> interaction, the other (n-1) dr
On Tue, May 19, 2009 at 12:54 AM, Miguel Mitrofanov
wrote:
> I've posted it once or twice.
>
> newtype C m r a = C ((a -> m r) -> m r)
>
> It's a monad, regardless of whether m is one or not. If you have something
> like "return" and "bind", but not exactly the same, you can make "casting"
> funct
> Why is Symbol = (String, Token)? A more sensible token type would
> include values in the Value constructor and string identifiers in the
> Identifier constructor; the strings in everything else seem redundant.
Surely you didn't read my original post, do you? I have a very limited
knowledge of
Nicolas Pouillard wrote:
> Excerpts from Ryan Ingram's message of Tue May 19 10:23:01 +0200 2009:
>> To be fair, you can do this with some extensions; I first saw this in
>> a paper on Oleg's site [1]. Here's some sample code:
>
> This seems like the same trick as the rmonad package:
> http://hac
Why is Symbol = (String, Token)? A more sensible token type would
include values in the Value constructor and string identifiers in the
Identifier constructor; the strings in everything else seem redundant.
A more pure/monadic parser would have a type like this:
data Result a = Error String | OK
Minor addition, optimize >>
(I couldn't help myself!)
-- ryan
> instance Ord b => ConstrainedBind (S.Set a) (S.Set b) where
>type BindElem (S.Set a) = a
>m >>= f = S.unions $ map f $ S.toList m
>m >> n = if S.null m then S.empty else n
__
Excerpts from Ryan Ingram's message of Tue May 19 10:23:01 +0200 2009:
> To be fair, you can do this with some extensions; I first saw this in
> a paper on Oleg's site [1]. Here's some sample code:
This seems like the same trick as the rmonad package:
http://hackage.haskell.org/cgi-bin/hackage-sc
I've posted it once or twice.
newtype C m r a = C ((a -> m r) -> m r)
It's a monad, regardless of whether m is one or not. If you have something like "return" and "bind", but not exactly the same, you can make
"casting" functions
m a -> C m r a
and backwards.
Jason Dusek wrote on 19.05.2009
To be fair, you can do this with some extensions; I first saw this in
a paper on Oleg's site [1]. Here's some sample code:
{-# LANGUAGE NoImplicitPrelude, TypeFamilies, MultiParamTypeClasses #-}
module SetMonad where
import qualified Data.Set as S
import qualified Prelude as P (Monad, (>>=), (>>)
> Indeed, the grammar does not admit "1*2/3" as a sentence ...
Huh? Why not? "1 * 2 / 3" should match factor "*" factor "/" factor.
Remember that { } is repetition, so it should be able to handle such term.
> expression ::= term | term "+" expression
> term ::= factor | factor "*" term
> factor
Excerpts from Taral's message of Tue May 19 00:05:39 +0200 2009:
> On Mon, May 18, 2009 at 10:30 AM, Nicolas Pouillard
> wrote:
> > The type I would need for bind is this one:
> >
> > (>>=) :: NFData sa => LI sa -> (sa -> LI b) -> LI b
>
> Will this do?
>
> (>>=) :: (NFData sa, NFData b) => LI
> Could either of those approaches (FRP / Delimited Continuations) be a
> solution for implementing complex GUI code?
I think the answer is generally yes; I have tried writing a user
interface which has a form with several controls; a change in one
control may affect all other controls on the for
The grammar:
expression = "get" | [ "+" | "-" ] term { ( "+" | "-" ) term }
term = factor { ( "*" | "/" ) factor }
factor = IDENTIFIER | VALUE | "(" expression ")"
I can't make term parse, for instance "1 * 2 / 3"
Indeed, the grammar does not admit "1*2/3" as a sentence of that
lan
On Mon, 18 May 2009, Nicolas Pouillard wrote:
Excerpts from Jason Dusek's message of Sun May 17 15:45:25 +0200 2009:
From the documentation:
" LI could be a strict monad and a strict applicative functor.
However it is not a lazy monad nor a lazy applicative
functor as required Has
On May 18, 2009, at 20:54 , Claus Reinke wrote:
As I said, I don't get the fusion if I just add the function above
to the original Dist.hs, export it and compile the module with '-c
-O2 -ddump-simpl':
I can't reproduce this.
Interesting. I'm using ghc 6.11.20090320 (windows), uvector-0.1.
On May 18, 2009, at 15:28 , Claus Reinke wrote:
My current best try uses the uvector package, has two 'vectors' of
type
(UArr Double) as input, and relies on the sumU and zipWithU
functions
which use streaming to compute the result:
dist_fast :: UArr Double -> UArr Double -> Double
dist_fa
50 matches
Mail list logo