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, wrote:
> Hi Ryan,
>
> Is there something missing or mislabeled in your post, because I
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 wrote:
From: Ryan Ingram
Subject: Re: [Haskell-cafe] Missing a "Deriving"?
To: "David Menendez"
Cc: "michael rice" , haskell-cafe@haskell
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 wrote:
From: David Menendez
Subject: Re: [Haskell-cafe] Missing a "Deriving"?
To: "michael rice"
Cc:
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 eithe
On Sat, May 30, 2009 at 6:33 PM, David Menendez 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
> context of
On Sat, May 30, 2009 at 9:00 PM, michael rice 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]]
*Main> searchAll g
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 t
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
On Fri, May 29, 2009 at 5:36 AM, Max Rabkin wrote:
> On Fri, May 29, 2009 at 12:29 PM, Paul Keir wrote:
>> f''' = ([]::[()]) == ([]::[()])
>>
>> (Very pretty.)
>>
>> So why doesn't ghc have 'default' instances?
>
> It does. I believe Num defaults to Integer and then to Double.
>
> Generally, thou
-__-" hehe why did I not let Hayoo or Hoogle help me there *sigh*
Thanks!!
2009/5/31 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
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 and
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!
___
好玩贺卡等你发,邮箱贺卡全新上线!
http://card.mail.cn.yahoo.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.
On May 30, 2009, at 5:36 PM, Sebastian Sylvan wrote:
On Sat, May 30, 2009 at 10:32 PM, Cetin Sert
wrote:
Thank y
michael rice 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 guess is that
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
On Sat, May 30, 2009 at 10:32 PM, Cetin Sert 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
> e ←
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
2009/5/30 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
>
Something like (warning, untested code - no compiler atm).
timed timeout act fa
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 ghc-pr
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@has
On Sat, May 30, 2009 at 1:12 PM, Jason Dusek wrote:
> 2009/05/30 Bartosz Wójcik :
>> ...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
> li
2009/05/30 Bartosz Wójcik :
> ...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 -> b) -> m a -
On Sat, May 30, 2009 at 7:35 PM, Maurício 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 the
> list,
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
wrote:
> I'm trying to use Database.HDBC.ODBC to
On Saturday 30 May 2009 03:10:11 Bryan O'Sullivan wrote:
> On Fri, May 29, 2009 at 5:04 PM, Bartosz Wójcik 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 same.
I find this slightly more complicated case quite confusing with the
current wording:
Prelude> :t (\x -> x) :: (a -> b) -> (a -> a)
:1:7:
Couldn't match expected type `a' against inferred type `b'
`a' is a rigid type variable bound by
an expression type signature at
wren ng thornton wrote:
(Though it doesn't necessarily generalize to cover similar messages like:
Prelude> :t (\x -> x) :: a -> b
:1:7:
Couldn't match expected type `b' against inferred type `a'
`b' is a rigid type variable bound by
the polymorphic type `foral
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
28 matches
Mail list logo