Thanks for your proposal.
> It is not clear if the class constraint is really needed.
Well 'IM' means 'ImplementationMonad', so it wouldn't make much sense if an
IM of an implementation wasn't also a monad. And since IM is the central
monad of the library, a lot of functions will use IM.
The meth
Yves Pare`s wrote:
> I'm working on a library which aims to be a generic interface for 2D
> rendering. To do that, one of my goals is to enable each implementation of
> this interface to run in its own monad (most of the time an overlay to IO),
> thus giving me the following class
>
> class (Mona
The trick is to write the rank-2 type in the function that runs
the monad, and leave the typeclasses skolemized.
Here's an example:
-- | Typeclass for monads that write or read to a network. Useful
-- if you define operations that need to work for all such monads.
-- You're expected to put extra
2011/3/2 Yves Parès :
> Is what I'm trying to do a common technique to type-ensure contexts or are
> there simpler methods?
I don't understand your problem well enough to be able to venture a
solid opinion on this. Sorry! What you have detailed so far doesn't
sound too complex, though.
Max
_
Thank you !
Is what I'm trying to do a common technique to type-ensure contexts or are
there simpler methods?
2011/3/2 Max Bolingbroke
> On 2 March 2011 09:11, Yves Parès wrote:
> > class (forall x. Monad (IM i x)) => Impl i where
> > data IM i :: * -> * -> *
> >
> > But GHC forbids me to
On 2 March 2011 09:11, Yves Parès wrote:
> class (forall x. Monad (IM i x)) => Impl i where
> data IM i :: * -> * -> *
>
> But GHC forbids me to do so.
The way I usually work around this is by doing something like the
following pattern:
{{{
class Monad1 m where
return1 :: a -> m x a
Hello,
I'm working on a library which aims to be a generic interface for 2D
rendering. To do that, one of my goals is to enable each implementation of
this interface to run in its own monad (most of the time an overlay to IO),
thus giving me the following class
class (Monad (IM i x)) => Impl i x
On Mon, Apr 26, 2010 at 2:55 PM, Thomas van Noort wrote:
> On 26-4-2010 20:12, Daniel Fischer wrote:
>>
>> Am Montag 26 April 2010 19:52:23 schrieb Thomas van Noort:
>>>
>>> ...
>>
>> Yes, y's type is more general than the type required by f, hence y is an
>> acceptable argument for f - even z ::
On 26-4-2010 20:12, Daniel Fischer wrote:
Am Montag 26 April 2010 19:52:23 schrieb Thomas van Noort:
...
Yes, y's type is more general than the type required by f, hence y is an
acceptable argument for f - even z :: forall a b. a -> b -> Bool is.
That's what I thought. I've just never seen
On 26-4-2010 20:13, Jochem Berndsen wrote:
Thomas van Noort wrote:
...
f requires a function that is able to compute, for two values of type a
(which instantiates Eq), a Boolean.
y certainly fulfills that requirement: it does not even require that the
values are of a type instantiating Eq.
T
Am Montag 26 April 2010 19:52:23 schrieb Thomas van Noort:
> Hello all,
>
> I'm having difficulties understanding rank-2 polymorphism in combination
> with overloading. Consider the following contrived definition:
>
> f :: (forall a . Eq a => a -> a -> Bool) -> Bool
> f eq = eq True True
>
> Then,
Thomas van Noort wrote:
> Hello all,
>
> I'm having difficulties understanding rank-2 polymorphism in combination
> with overloading. Consider the following contrived definition:
>
> f :: (forall a . Eq a => a -> a -> Bool) -> Bool
> f eq = eq True True
>
> Then, we pass f both an overloaded fun
Hello all,
I'm having difficulties understanding rank-2 polymorphism in combination
with overloading. Consider the following contrived definition:
f :: (forall a . Eq a => a -> a -> Bool) -> Bool
f eq = eq True True
Then, we pass f both an overloaded function and a regular polymorphic
functi
On Fri, Mar 23, 2007 at 02:18:50PM +0100, Martin Huschenbett wrote:
>
> -- The type I want to get.
> readValue' :: Field -> (forall s. SqlBind s => Maybe s) -> Value
>
> -- First trial:
> readValue' fld s =
> if isJust s then readValue fld (fromJust s) else emptyValue fld
Is there a reason you
Hi,
I'm writing some database code using HSQL and had to stop on a problem
with rank-2-polymorphism that I can't solve. The essence of my code is:
module Value where
import Data.Maybe
class SqlBind a where
fromSqlValue :: String -> a
data Field
data Value
emptyValue :: Field -> Value
em
Hello,
See this message:
http://article.gmane.org/gmane.comp.lang.haskell.general/13145/
Your (initial) program should work in GHC 6.2. I actually find this feature useful,
but Simon apparently changed this when moving to GHC 6.4 and nobody complained...
Apparently not many people us
This counterintuitive typechecking result came up when I wrote a wrapper
around runST. Is there some limitation of HM with respect to type checking
pattern matching?
data X a b = X (a -> a)
run :: forall a. (forall b. X a b) -> a -> a
-- This definition doesn't pass the typechecker
run (X f) =
On Tue, Jan 10, 2006 at 08:47:32PM +0300, Bulat Ziganshin wrote:
> those rank-2 types wil make me mad :)
>
> encodeHelper :: (MRef m r, Binary m a, BitStream m (StringBuffer m r))
> => a -> m String
> encodeHelper x = do h <- newStringBuffer "" stringBufferDefaultCloseFunc
>
Hello ,
those rank-2 types wil make me mad :)
encodeHelper :: (MRef m r, Binary m a, BitStream m (StringBuffer m r))
=> a -> m String
encodeHelper x = do h <- newStringBuffer "" stringBufferDefaultCloseFunc
put_ h x
getStringBuffer h
encode x =
Hi,
can someone give me an example of an arbitrary rank
polymorphism function?
Thanks
Jan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi,
foo _ = undefined
works fine.
Otherwise the poor little "a" has no chance to get disambiguated.
... Ambiguous type variable `a' in the top-level constraint ...
Ralf
Stefan Holdermans wrote:
Hi,
Just out of curiosity (I cannot come up with a practical example):
Why doesn't the following piece
Hi,
Just out of curiosity (I cannot come up with a practical example): Why
doesn't the following piece of code type check in GHC (with
extensions)?
> foo :: (forall a . (Eq a) => a) -> Integer
> foo = undefined
It seems like the type-class constraint is playing a decisive rôle
here, since the
22 matches
Mail list logo