Re: [Haskell-cafe] typeclass to select a list element

2013-10-12 Thread Paolino
extract = undefined update :: L Zero - (X n - X n) - L Zero update = undefined Thanks for hints and help paolino 2013/10/7 Paolino paolo.verone...@gmail.com Hello, I'm trying to use a type class to select an element from a list. I would like to have a String CC as a value for l10

[Haskell-cafe] typeclass to select a list element

2013-10-07 Thread Paolino
. paolino ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Over general types are too easy to make.

2012-08-31 Thread Paolino
Hello Timothy GADTs let you catch more errors at compile time. With them you can give different types to constructors of the same datatype. regards paolino 2012/8/31 timothyho...@seznam.cz Sure, but that's relying on the promise that you're passing it a valid BadFrog... Consider

Re: [Haskell-cafe] Dealing poker hands, redux

2012-08-25 Thread Paolino
and a MonadRandom instance regards paolino 2012/8/25 Matthew wonderzom...@gmail.com So I've finally got some code which shuffles a deck of cards and deals out an arbitrary number of hands. https://gist.github.com/19916435df2b116e0edc type DealerState = State [Card] [[Card]] deck :: [Card] deck = [ (s

Re: [Haskell-cafe] Combining State and List Monads

2012-08-24 Thread Paolino
countCalls :: ListT (State Int) (Int,Int) countCalls = do a - ListT . return $ [1..2] b - ListT . return $ [1..2] modify (+1) return (a,b) regards paolino 2012/8/25 Henry Laxen nadine.and.he...@pobox.com Dear Cafe, It seems to me there should be some simple way of doing this, but thus

Re: [Haskell-cafe] Adding to / subtracting from a LocalTime?

2012-08-18 Thread Paolino
the Integral arguments is in seconds, by docs regards paolino 2012/8/18 Adde Nilsson trialc...@gmail.com Hi. How do you add to or subtract from a LocalTime? I'm trying to subtract a second from a LocalTime value but the only API's I can find act only on the TimeOfDay part. subSec

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-08-01 Thread Paolino
Value a :: * and adding Typeable (Key a) to the contexts and Key 'a' in place of 'a' leads to a lot of type errors. Maybe it's possible with more help. Hope I got it right. Regards paolino 2012/7/31 Alexander Foremny alexanderfore...@gmail.com Hello list, I am currently thinking that a problem

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-08-01 Thread Paolino
ciao *Main Regards paolino 2012/8/1 Paolino paolo.verone...@gmail.com Hello, I made some trial and error with ghci to make it happy. I'm not really sure this has the type safety you asked. {-# LANGUAGE TypeFamilies, ExistentialQuantification, FlexibleContexts #-} import Prelude hiding

Re: [Haskell-cafe] combining predicates, noob question

2012-07-09 Thread Paolino
You can still use the monadic combinators, with the price of wrapping and unwrapping in case of newtype. newtype P a = P {unP :: a - Bool} liftM2'P :: (Bool - Bool - Bool) - P a - P a - P a liftM2'P op = (P .) . on (liftM2 op) unP paolino 2012/7/8 Sebastián Krynski skryn...@gmail.com Ok

Re: [Haskell-cafe] existential types and cast

2012-07-05 Thread Paolino
Hi Corentin, This is how I would model your request (without concrete constructors for Player and Rule) I'm sure there are better descriptions also as I'm not an expert. paolino {-# LANGUAGE DataKinds, GADTs, KindSignatures #-} data Player data Rule data Data = Player | Rule data EventKind

Re: [Haskell-cafe] existential types and cast

2012-07-05 Thread Paolino
Sorry, drop the data Data line, I was experimenting with a deeper description. paolino 2012/7/4 Paolino paolo.verone...@gmail.com Hi Corentin, This is how I would model your request (without concrete constructors for Player and Rule) I'm sure there are better descriptions also as I'm

Re: [Haskell-cafe] existential types and cast

2012-07-05 Thread Paolino
Typeable defeats moving checks at runtime. So lifting values to types and eliminating this information with existentials and casting seems wrong. paolino 2012/7/4 Corentin Dupont corentin.dup...@gmail.com Hi Paolino, the user can add as many handlers he wants for each event. When a event

Re: [Haskell-cafe] existential types and cast

2012-07-04 Thread Paolino
issue. By the way , it's not clear to me why you don't have a simple Event datatype describing all the possible events in advance. Regards paolino 2012/7/3 Corentin Dupont corentin.dup...@gmail.com Hi all, I read somewhere (here: http://stackoverflow.com/questions/2300275/how-to-unpack

Re: [Haskell-cafe] Arithmetic expressions with GADTs: parsing

2012-06-05 Thread Paolino
Very useful to get a gadt back to monotype without an existential, which would mean to use classes for future uses of it with its load of object oriented thinking. Thanks for sharing. paolino 2012/6/4 Ryan Ingram ryani.s...@gmail.com Another option is to reify the type so that you can get

Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-19 Thread Paolino
to perfect C. paolino P.S. The performance problems are actually learning haskell programming abstractions and the intuition development on when to use each. 2012/5/6 Janek S. fremenz...@poczta.onet.pl: Hi, a couple of times I've encountered a statement that Haskell programs can have

Re: [Haskell-cafe] Subcategories on Hackage

2011-06-05 Thread Paolino
don't think even software categories are. But this is really debatable. my 2 cents paolino 2011/6/5 Evan Laforge qdun...@gmail.com On Sat, Jun 4, 2011 at 7:46 PM, Felipe Almeida Lessa felipe.le...@gmail.com wrote: tl;dr: I don't think ontologies are suitable for Hackage. I think I agree

Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-02 Thread Paolino
It's first time I use TH. It would be nice to point out the motivations for using it. If everything TH does is doable without it, the point of using it is write less code, eliminating some necessary and automatically computable code. But I guess there is some more . paolino 2010/11/2 Antoine

[Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Paolino
, or some hints on how to arrive there. Thanks paolino ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Paolino
Thanks. I annotated the function http://hpaste.org/paste/41035/test_simpleclasssynonym It seems to produce the right code. How should I use the Parents synonym in my functions? This is a noob question I suppose. paolino 2010/11/1 Gábor Lehel illiss...@gmail.com On Mon, Nov 1, 2010 at 6:09

Re: [Haskell-cafe] template haskell for typeclass synonyms

2010-11-01 Thread Paolino
is printing some strange type variables but it compiles paolino 2010/11/1 Gábor Lehel illiss...@gmail.com On Mon, Nov 1, 2010 at 6:09 PM, Christopher Done chrisd...@googlemail.com wrote: On 1 November 2010 17:53, Paolino paolo.verone...@gmail.com wrote: I'd like to have a template haskell

Re: [Haskell-cafe] Long running Haskell program

2009-11-12 Thread Paolino
get complicate, but resolving the persistence issue for those parts should resolve also the space leak, I think. paolino 2009/11/11 Paolino paolo.verone...@gmail.com Hello leimy, the only simple solution I have found to avoid a leaking state of a server is doing a periodical rnf

Re: [Haskell-cafe] Problem with JHC

2009-11-11 Thread Paolino
instead. paolino 2009/11/11 Ross Mellgren rmm-hask...@z.odi.ac According to the paste you gave for the JHC test run: Here is what happens when I try to run it: phi...@desktop:~/jhctut$ ./jtree Give me a tree: T AND (L 1, L 2) jtree_code.c:2670: case fell off Aborted You gave it parens

Re: [Haskell-cafe] Long running Haskell program

2009-11-11 Thread Paolino
Hello leimy, the only simple solution I have found to avoid a leaking state of a server is doing a periodical rnf of it, this implying the NFData constraint on its datatype. The reader should leak only if you nest forever the local function. paolino 2009/11/11 David Leimbach leim

[Haskell-cafe] STM semantics

2009-10-24 Thread Paolino
the readTChan. Should I trust this is the correct STM behaviour , and will not change in different implementations ? thanks paolino ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] STM semantics

2009-10-24 Thread Paolino
Thanks, atomicity is what I was missing in the STM semantics. Now it is clear. The retry primitive is not saying block here and this can imply no more pass here, which is somewhat difficult to express with locks paolino 2009/10/24 Matthew Brecknell matt...@brecknell.net: Hi Paolino, You wrote

[Haskell-cafe] testing par with simple program

2009-08-21 Thread Paolino
with ghc --make prova -O2 -threaded timings paol...@paolino-casa:~$ time ./prova +RTS -N1 32762 real0m7.031s user0m6.304s sys0m0.004s paol...@paolino-casa:~$ time ./prova +RTS -N2 32762 real0m6.997s user0m6.728s sys0m0.020s paol...@paolino-casa:~$ without optimizations it gets

Re: [Haskell-cafe] testing par with simple program

2009-08-21 Thread Paolino
paol...@paolino-casa:~$ ghc --make prova -threaded [1 of 1] Compiling Main ( prova.hs, prova.o ) Linking prova ... paol...@paolino-casa:~$ time ./prova +RTS -N1 63262367 real1m17.485s user1m16.473s sys0m0.392s paol...@paolino-casa:~$ time ./prova +RTS -N2 63262367 real

[Haskell-cafe] iteratee enumHandle

2009-07-09 Thread Paolino
language to capture it. thanks paolino ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] parallelism or concurrency ? if they are different

2009-02-20 Thread Paolino
then it's an implementation choice. It would be nice to have a suffix for this kind of functions, something remembering the unrepeatability of them when not cached. Sorry for my lacks of structure, I did my best. paolino 2009/2/17, Henk-Jan van Tuyl hjgt...@chello.nl: On Fri, 13 Feb 2009 11:09:35

[Haskell-cafe] parallelism or concurrency ? if they are different

2009-02-13 Thread Paolino
IO values ? Finally, why and where the optimizer will substitute a value with its definition, so that it possibly get computed twice ? Thanks paolino ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Paolino
= print test main is a working program. Thanks for explanations. paolino ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Paolino
I must ask why runWriterT k :: State s (a,[Int]) is working. Looks like I could runIO the same way I evalState there. In that case I wouldn't wait for the State s action to finish. Thanks 2008/12/31 Derek Elkins derek.a.elk...@gmail.com On Wed, 2008-12-31 at 21:48 +0100, Paolino wrote

Re: [Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Paolino
How do I read IO is not lazy ? Is IO (=) forcing the evaluation of its arguments, causing the unwanted neverending loop? And, this happens even in (MonadTrans t = t IO) (=) ? Thanks paolino 2008/12/31 Ryan Ingram ryani.s...@gmail.com IO is not lazy; you never make it to print. Consider

Re: [Haskell-cafe] Parsing words with parsec

2007-03-30 Thread Paolino
On 3/30/07, Stefan O'Rear [EMAIL PROTECTED] wrote: On Fri, Mar 30, 2007 at 05:43:34AM +0200, paolino wrote: Hi, I had a bad time trying to parse the words of a text. I suspect I miss some parsec knowledge. I'd start by not sextuple-posting, it just sextuples the ugliness ;-) Mhh

[Haskell-cafe] A simple parsing task for parsec.

2007-03-29 Thread paolino
word | nextWord) parseLine end = do f - option [] $ return `fmap` try word r - many $ try nextWord manyTill anyChar end return (f ++ r) --- Any comment to simplify this code is welcome. Paolino

[Haskell-cafe] Parsing words with parsec

2007-03-29 Thread paolino
word | nextWord) parseLine end = do f - option [] $ return `fmap` try word r - many $ try nextWord manyTill anyChar end return (f ++ r) --- Any comment to simplify this code is welcome. Paolino

[Haskell-cafe] Parsing words with parsec

2007-03-29 Thread paolino
word | nextWord) parseLine end = do f - option [] $ return `fmap` try word r - many $ try nextWord manyTill anyChar end return (f ++ r) --- Any comment to simplify this code is welcome. Paolino