[Haskell-cafe] Type families in export lists

2009-05-30 Thread Maurí­cio
Hi, How do I include type families (used as associated types) in a module export list? E.g.: class MyClass a where type T a :: * coolFunction :: Ta - a (...) If I just include MyClass and its functions in the list, instances in other modules complain they don't know T, but I wasn't

Re: [Haskell-cafe] Re: Error message reform

2009-05-30 Thread Tillmann Rendel
wren ng thornton wrote: (Though it doesn't necessarily generalize to cover similar messages like: Prelude :t (\x - x) :: a - b interactive:1:7: Couldn't match expected type `b' against inferred type `a' `b' is a rigid type variable bound by the polymorphic

Re: [Haskell-cafe] Re: Error message reform

2009-05-30 Thread Claus Reinke
I find this slightly more complicated case quite confusing with the current wording: Prelude :t (\x - x) :: (a - b) - (a - a) interactive:1:7: Couldn't match expected type `a' against inferred type `b' `a' is a rigid type variable bound by an expression type

Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Bartosz Wójcik
On Saturday 30 May 2009 03:10:11 Bryan O'Sullivan wrote: On Fri, May 29, 2009 at 5:04 PM, Bartosz Wójcik bar...@sudety.it wrote: I don't undersdand what is being missed. Brevity. liftM f m1 = do { x1 - m1; return (f x1) } so liftM fromIntegral integer will result the

Re: [Haskell-cafe] can someone point me to more help about Database.HDBC.ODBC?

2009-05-30 Thread Wei Hu
Try http://sites.google.com/site/haskell/notes/connecting-to-mysql-with-haskell that I wrote up. An important thing that I don't think was documented anywhere is that the trailing ';' is required. On Fri, May 29, 2009 at 11:01 PM, Michael P Mossey m...@alumni.caltech.edu wrote: I'm trying to use

Re: [Haskell-cafe] Type families in export lists

2009-05-30 Thread Lee Duhem
On Sat, May 30, 2009 at 7:35 PM, Maurí­cio briqueabra...@yahoo.com wrote: Hi, How do I include type families (used as associated types) in a module export list? E.g.: class MyClass a where    type T a :: *    coolFunction :: Ta - a    (...) If I just include MyClass and its functions in

Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Jason Dusek
2009/05/30 Bartosz Wójcik bar...@sudety.it: ...reading RWH I could not memorize what those liftM funtions meant. The basic one, `liftM`, means `fmap`, though specialized for functors that are monads. Prelude Control.Monad :t liftM liftM :: forall a b (m :: * - *). (Monad m) = (a -

Re: [Haskell-cafe] Parsec float

2009-05-30 Thread Derek Elkins
On Sat, May 30, 2009 at 1:12 PM, Jason Dusek jason.du...@gmail.com wrote: 2009/05/30 Bartosz Wójcik bar...@sudety.it: ...reading RWH I could not memorize what those liftM funtions meant.  The basic one, `liftM`, means `fmap`, though specialized for  functors that are monads.    Prelude

[Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Cetin Sert
Hi how could one implement a function in concurrent haskell that either returns 'a' successfully or due timeout 'b'? timed :: Int → IO a → b → IO (Either a b) timed max act def = do Best Regards, Cetin Sert ___ Haskell-Cafe mailing list

[Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
The following code is from Section 8.4.2, pgs. 111-112 (PDF paging) of YAHT. It compiles fine, but upon trying it I get the following error message. It seems to be trying to 'Show' the Computation class but I'm not sure where to put the 'Deriving'. Michael Loading package

Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Sebastian Sylvan
2009/5/30 Cetin Sert cetin.s...@gmail.com Hi how could one implement a function in concurrent haskell that either returns 'a' successfully or due timeout 'b'? timed :: Int → IO a → b → IO (Either a b) timed max act def = do Something like (warning, untested code - no compiler atm). timed

Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Cetin Sert
Thank you for your reply, I'd come up with the following: timed :: Int → IO a → b → IO (Either b a) timed max act def = do r ← new t ← forkIO $ do a ← act r ≔ Right a s ← forkIO $ do wait max e ← em r case e of True → do kill t r ≔ Left def

Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Sebastian Sylvan
On Sat, May 30, 2009 at 10:32 PM, Cetin Sert cetin.s...@gmail.com wrote: Thank you for your reply, I'd come up with the following: timed :: Int → IO a → b → IO (Either b a) timed max act def = do r ← new t ← forkIO $ do a ← act r ≔ Right a s ← forkIO $ do wait max

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Miguel Mitrofanov
It's trying to 'Show' the 'c [Int]' type, but doesn't know which 'c' to use; so it's trying to find a generic instance, which doesn't exist. You can't fix this with 'deriving' or anything like this; instead, provide the type annotation like this: *Main searchAll g 1 3 :: Maybe [Int] On 31

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Ketil Malde
michael rice nowg...@yahoo.com writes: The following code is from Section 8.4.2, pgs. 111-112 (PDF paging) of YAHT. It compiles fine, but upon trying it I get the following error message. It seems to be trying to 'Show' the Computation class but I'm not sure where to put the 'Deriving'. My

Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Sterling Clover
The proper way is just to wrap System.Timeout, which does some rather clever things with regards to exception semantics. The code for it is a joy to read, by the way. --S. On May 30, 2009, at 5:36 PM, Sebastian Sylvan wrote: On Sat, May 30, 2009 at 10:32 PM, Cetin Sert

[Haskell-cafe] get Scale of window in HOpenGL?

2009-05-30 Thread yu yang
Hi,   I want to move one object to the border of window, then go back to the start point. Does anyone one have an idea to implement it ? Thank you! ___ 好玩贺卡等你发,邮箱贺卡全新上线!

[Haskell-cafe] Re: Lazy Parsing

2009-05-30 Thread GüŸnther Schmidt
Dear Doaitse, It is my pleasure to announce that after 5 days of experimenting with uu-parsinglib I have absolutely no clue, whatsoever, on how to use it. Period. I do not even manage to write a parser for even a mere digit or a simple character. I have read the tutorial from a to a to z

Re: [Haskell-cafe] Concurrent Haskell Actions with Timeout

2009-05-30 Thread Cetin Sert
-__- hehe why did I not let Hayoo or Hoogle help me there *sigh* Thanks!! 2009/5/31 Sterling Clover s.clo...@gmail.com The proper way is just to wrap System.Timeout, which does some rather clever things with regards to exception semantics. The code for it is a joy to read, by the way. --S.

Re: [Haskell-cafe] [] == []

2009-05-30 Thread Derek Elkins
On Fri, May 29, 2009 at 5:36 AM, Max Rabkin max.rab...@gmail.com wrote: On Fri, May 29, 2009 at 12:29 PM, Paul Keir pk...@dcs.gla.ac.uk wrote: f''' = ([]::[()]) == ([]::[()]) (Very pretty.) So why doesn't ghc have 'default' instances? It does. I believe Num defaults to Integer and then to

[Haskell-cafe] HPC and derived instances

2009-05-30 Thread Felipe Lessa
Hello! Why isn't there an option to control whether HPC, the Haskell Program Coverage, will consider derived instances coverable. I'm using it and my top level coverage is 52% while my expression coverage is at 92%. Looking carefully we see that most non-tested top level definitions are derived

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
Hi Miguel, That works. but it gives just a single solution [1,2,3] when there are supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in error. Also, how the heck does Haskell decide which success, failure, augment, and combine to use in function searchAll, since there are

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread David Menendez
On Sat, May 30, 2009 at 9:00 PM, michael rice nowg...@yahoo.com wrote: That works. but it gives just a single solution [1,2,3] when there are supposed to be two [[1,2,3],[1,4,3]]. Of course the code in YAHT may be in error. Works for me. *Main searchAll g 1 3 :: [[Int]] [[1,2,3],[1,4,3]]

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Ryan Ingram
On Sat, May 30, 2009 at 6:33 PM, David Menendez d...@zednenem.com wrote: *Main :t searchAll searchAll :: (Computation c) = Graph t t1 - Int - Int - c [Int] The way searchAll is written, the choice of which functions to use depends on the type variable c. That's determined by the calling

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
I figured out the [[Int]] case for myself, but hadn't considered the Failure case. Thanks. In function searchAll, given a calling context Failable [Int],  for the line    where search' [] = failure no path failure would be Fail, a constructor that takes a String. Right? But using either of

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread michael rice
Belay that last question. I just realized that its the const function being used rather than a constant declaration in const Nothing and const []. MIchael --- On Sat, 5/30/09, David Menendez d...@zednenem.com wrote: From: David Menendez d...@zednenem.com Subject: Re: [Haskell-cafe] Missing a

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread nowgate
Hi Ryan, Is there something missing or mislabeled in your post, because I don't see any definition of toDynamic. Michael --- On Sun, 5/31/09, Ryan Ingram ryani.s...@gmail.com wrote: From: Ryan Ingram ryani.s...@gmail.com Subject: Re: [Haskell-cafe] Missing a Deriving? To: David Menendez

Re: [Haskell-cafe] Missing a Deriving?

2009-05-30 Thread Ryan Ingram
Oops, it's called toDyn; from Data.Dynamic [1] toDyn :: Typeable a = a - Dynamic -- ryan [1] http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Dynamic.html On Sat, May 30, 2009 at 10:18 PM, nowg...@yahoo.com wrote: Hi Ryan, Is there something missing or mislabeled in your