On Mon, Mar 08, 2010 at 11:32:16PM +0100, Wolfgang Jeltsch wrote:
> Generalized newtype deriving doesn’t just allow otherwise undefinable
> functions
> to be defined. It probably also allows for faster function implementations.
> For
> example, with the above conv method, you could probably conve
I am pleased to announce that the first release of the storable library has
been uploaded to Hackage. Let me describe it in a few sentences (copied from
its haddock comments):
This class fills the gap between Foreign.Storable and Data.Binary. It adds
support for marshalling (finite) values of va
What about AString or AnyString?
> -Original Message-
> From: haskell-boun...@haskell.org [mailto:haskell-boun...@haskell.org]
> On Behalf Of Chris Kuklewicz
> Sent: Friday, March 06, 2009 8:17 PM
> To: Matthew Pocock
> Cc: haskell@haskell.org
> Subject: Re: [Haske
Matthew Pocock wrote:
It seems every time I look at hackage there is yet another stringy
datatype. For lots of apps, the particular stringy datatype you use
matters for performance but not algorithmic reasons. Perhaps this is a
good time for someone to propose a stringy class?
Not likely.
I
Sean Leather schrieb:
Like this?
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ListLike
Indeed, a class StringLike is included there as well.
Why not take or improve that one?
Till
___
Haskell mailing list
Haskell@haskell.org
http://w
On 2009 Mar 6, at 12:24, David Menendez wrote:
How about CharSequence?
I'd be tempted on first sight to assume that's related to Data.Seq.
--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
elect
On 2009 Mar 6, at 11:13, Wolfgang Jeltsch wrote:
Am Freitag, 6. März 2009 13:33 schrieb Matthew Pocock:
It seems every time I look at hackage there is yet another stringy
datatype. For lots of apps, the particular stringy datatype you use
matters
for performance but not algorithmic reasons. Pe
> I'd be more interested in a kitchen-sink "List" class. ByteString,
> ByteString.Lazy, Text, [a], and the pending Text.Lazy all support the basic
> operations of lists of a particular type. It'd be a fairly huge dictionary
> by the current API design of those however. Its just a reiteration of the
2009/3/6 David Menendez :
> On Fri, Mar 6, 2009 at 12:05 PM, Wolfgang Jeltsch
> wrote:
>> Am Freitag, 6. März 2009 17:31 schrieben Sie:
>>> What name would you suggest?
>>
>> If we wouldn’t have to care about compatibility, I would name the class
>> String
>> and drop the type alias String.
>>
>>
On Fri, Mar 6, 2009 at 12:05 PM, Wolfgang Jeltsch
wrote:
> Am Freitag, 6. März 2009 17:31 schrieben Sie:
>> What name would you suggest?
>
> If we wouldn’t have to care about compatibility, I would name the class String
> and drop the type alias String.
>
> It’s hard to come up with a good name si
Am Freitag, 6. März 2009 17:31 schrieben Sie:
> What name would you suggest?
If we wouldn’t have to care about compatibility, I would name the class String
and drop the type alias String.
It’s hard to come up with a good name since String is already taken. However,
things like StringLike, Strin
I'd be more interested in a kitchen-sink "List" class. ByteString,
ByteString.Lazy, Text, [a], and the pending Text.Lazy all support the basic
operations of lists of a particular type. It'd be a fairly huge dictionary
by the current API design of those however. Its just a reiteration of the
classic
2009/3/6 Wolfgang Jeltsch :
> Am Freitag, 6. März 2009 13:33 schrieb Matthew Pocock:
>> Hi,
>>
>> It seems every time I look at hackage there is yet another stringy
>> datatype. For lots of apps, the particular stringy datatype you use matters
>> for performance but not algorithmic reasons. Perhaps
Am Freitag, 6. März 2009 13:33 schrieb Matthew Pocock:
> Hi,
>
> It seems every time I look at hackage there is yet another stringy
> datatype. For lots of apps, the particular stringy datatype you use matters
> for performance but not algorithmic reasons. Perhaps this is a good time
> for someone
Hi,
It seems every time I look at hackage there is yet another stringy datatype.
For lots of apps, the particular stringy datatype you use matters for
performance but not algorithmic reasons. Perhaps this is a good time for
someone to propose a stringy class?
Matthew
__
On 8/1/07, apfelmus <[EMAIL PROTECTED]> wrote:
> There are some fundamental problems/design choices for type classes
> in conjunction with separate compilation/modularity that need to be
> researched before trying anything like that. In particular, any
> ad-hoc Prolog, CHR or -fallow-undecidable-i
lways restrict to pattern unification
> (L-lamda unification) which is decidable and has MGUs. 2) is true,
> but these implicit lambdas don't play very well with instance
> selection and require that all reductions are spelled out via an
> Apply type class.
> I think it might be us
Am Mittwoch, 1. August 2007 14:41 schrieb apfelmus:
> […]
> The problem with the Functor/Cofunctor instances is that they are
> ambiguous as soon as a type constructor X is made an instance of both
> Functor and Cofunctor . Of course, such an X cannot exist in a
> mathematically useful way
Conal Elliott wrote:
> I keep running into situations in which I want more powerful search in
> selecting type class instances. One example I raised in June, in which all
> of the following instances are useful.
>
>> instance (Functor g, Functor f) => Functor (O g f) where
&
; any unifications done as a result of discarded searches, much like the "trail" in a
Prolog implementation.
there was some discussion of this on the haskell-prime list some time ago,
indicating that there is some room for exploration between the current
no-context and a full backtrack-ov
Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:
> It certainly makes sense to do backward chaining, but I don't know any
> Haskell implementation
> that's tried it. It'd be more complicated in the presence of functional
> dependencies, since we
> must "undo" any unifications done as a result of d
If only for those watching from home, here are some references.
jeff p <[EMAIL PROTECTED]> wrote in article <[EMAIL PROTECTED]> in
gmane.comp.lang.haskell.general:
> >Better yet,
> > how about LambdaProlog (
> > http://www.lix.polytechnique.fr/Labo/Dale.Miller/lProlog),
> > which generalizes from
complete (finds all solutions).
Simon
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Conal Elliott
Sent: 31 July 2007 20:09
To: haskell@haskell.org
Subject: [Haskell] type class instance selection & search
I keep running into situations in which I want more powerful search i
a bit of a cop-out since you could
always restrict to pattern unification (L-lamda unification) which is
decidable and has MGUs. 2) is true, but these implicit lambdas don't
play very well with instance selection and require that all reductions
are spelled out via an Apply type class.
I think it might
wrote:
>
> Conal Elliott <[EMAIL PROTECTED]> wrote in article <
> [EMAIL PROTECTED]> in
> gmane.comp.lang.haskell.general:
> > I keep running into situations in which I want more powerful search in
> > selecting type class instances.
>
> I agree that
t;
> I keep running into situations in which I want more powerful search in
> selecting type class instances. One example I raised in June, in which all
> of the following instances are useful.
>
> > instance (Functor g, Functor f) => Functor (O g f) where
> > fmap h (O gf)
Conal Elliott <[EMAIL PROTECTED]> wrote in article <[EMAIL PROTECTED]> in
gmane.comp.lang.haskell.general:
> I keep running into situations in which I want more powerful search in
> selecting type class instances.
I agree that it's quite useful for instance search to back
I keep running into situations in which I want more powerful search in
selecting type class instances. One example I raised in June, in which all
of the following instances are useful.
> instance (Functor g, Functor f) => Functor (O g f) where
> fmap h (O gf) = O (fmap (fmap h) gf)
&
Sorry, forgor the precise URLs
http://pobox.com/~oleg/ftp/Haskell/poly2.hs
http://pobox.com/~oleg/ftp/Haskell/poly2.txt
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell
We demonstrate functions polymorphic over classes of types. Each
instance of such (2-polymorphic) function uses ordinary 1-polymorphic
methods, to generically process values of many types, members of that
2-instance type class. The typeclass constraints are thus manipulated
as first-class
On 9/10/06, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:
data Expr t = If (Expr Bool) (Expr t) (Expr t)
Expr Int = Lit Int
Expr Bool | Eq t = Eq (Expr t) (Expr t)
I find this somewhat unreadable due to the implicit "t" parameter not
showing up on the left-hand side...
-> m [a] | Monad m
I am not entirely sure, but I think this syntax for type class
context is used in the Concurrent Clean language.
Best regards
Tomasz
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell
"Neil Mitchell" <[EMAIL PROTECTED]> writes:
> Hi,
>
> > class Monad m | Functor m, Monoid m where ...
>
> Nice - I was having exactly this problem in Hoogle, if you list all
> the class dependancies first, you can't really see the actual class.
> It also makes grep'ing easier.
>
> > data Encode
Hi,
class Monad m | Functor m, Monoid m where ...
Nice - I was having exactly this problem in Hoogle, if you list all
the class dependancies first, you can't really see the actual class.
It also makes grep'ing easier.
data EncodedStream m h | Monad m, Stream m h = ...
Ditto
sequence :: [
ds" to the right side we will get more readable
definitions where most important information (type/class name and
shape of parameters) are written first and less important after
Even more unification can be applied to GADT-style definitions and
definitions of type/data families. The followin
Hi John,
NB
the essence what I am trying to do is to define a proxy class Foo for
class Ba1 I would have thought that something as simple as the
following would have worked ??
class Ba1 a where
dosomething :: a -> IO ()
ba1 :: Ba1 a => a -> IO ()
ba1 x = dosomething x
instance Ba1 Int w
NB
the essence what I am trying to do is to define a proxy class Foo for class
Ba1 I would have thought that something as simple as the following would
have worked ??
class Ba1 a where
dosomething :: a -> IO ()
ba1 :: Ba1 a => a -> IO ()
ba1 x = dosomething x
instance Ba1 Int where
doso
** this is literate haskell
hoping someone can help me. What I am trying to do is
class Ba1 a
ba1 :: Ba1 a => a -> IO ()
ba1 x = print "helllo"
what I wish to do is declare another function
class Foo a
proxy :: Foo a => a -> IO ()
so that I can do something like
proxy x = ba1 x
Paul Govereau wrote:
> BTW, The above program is a translation of an idiomatic use of
> functors in ML (pardon my syntax):
>
> module A : sig type t = ... end
> module B : funsig(X:SHOW where t = A.t) sig bar : A.t -> string end
> module C : SHOW where t = A.t
> open A
> open B(C)
ML mo
GHC insists that every type class constraint mentions a type variable
that is quantified just outside the constraint. E.g.
forall a b c. (C a c, D b) => ...
The constraints (C a c), (D b) must each mention at least one of a,b,c.
Why? Because it makes it much easier to know whe
phic to begin with, you should never need
> them.
>
> - Cale
>
> On 21/11/05, Paul Govereau <[EMAIL PROTECTED]> wrote:
> > Hello,
> >
> > I was hoping that someone could answer a question I have about the
> > type class system. In Haskell, I ca
.
The only purpose of class constraints is to restrict polymorphism. If
a function isn't polymorphic to begin with, you should never need
them.
- Cale
On 21/11/05, Paul Govereau <[EMAIL PROTECTED]> wrote:
> Hello,
>
> I was hoping that someone could answer a question I have abo
Hello,
I was hoping that someone could answer a question I have about the
type class system. In Haskell, I cannot write a term with an exact
constraint:
> data X = X
> bar :: Show X => X -> String
> bar x = show x
According to the Haskell 98 report, a qualifier can only be
Thanks alot for the clarifications. If I understand correctly, I ran
into the monomorphism restriction because of the constraint on the
type variable. The Haskell report says this in Section 4.5.5:
In addition, the constrained type variables of a restricted
declaration group may not be gener
On 07/08/2005, at 12:47 AM, Srinivas Nedunuri wrote:
Finally a plain English explanation of the silly thing. Thank you!
I tried
reading the Haskell report's version of it, and yes I'm sure it has
all the
gory technical details, but at the end I was still left thinking So
exactly
what is the
Finally a plain English explanation of the silly thing. Thank you! I tried
reading the Haskell report's version of it, and yes I'm sure it has all the
gory technical details, but at the end I was still left thinking So exactly
what is the monomorphism restriction? Why on earth couldn't they have ad
Hello,
On 8/5/05, Paul Govereau <[EMAIL PROTECTED]> wrote:
>
> Hello,
>
> I have encountered a type error that I find quite puzzling. I would
> appreciate it if someone could help me understand what is going wrong.
> Here is the program:
>
> > data Expr = Var String | Const Int
> > data Constra
Paul Govereau wrote:
[snip]
>>instance AbSyn Constraint where
>>subst e n constr =
>>let sub = subst e n -- :: AbSyn a => a -> a
>>in case constr
>> of Zero expr -> Zero (sub expr)
>> AndL cs -> AndL (sub cs)
>
>It looks sort of like sub is being monom
Hello,
I have encountered a type error that I find quite puzzling. I would
appreciate it if someone could help me understand what is going wrong.
Here is the program:
> data Expr = Var String | Const Int
> data Constraint = Zero Expr | AndL Constraint
> class AbSyn a where
> subst :: Expr
Just spotted this typo:
How can we prevent the user from adding instances to Fail, whilst
still exporting
Fail so that it can be used in the constraints of other classes, like:
class MustBeInt a
instance MustBeInt a
instance MustBeInt Int
instance Fail a => MustBeInt a
Keean
___
Marcin 'Qrczak' Kowalczyk wrote:
[EMAIL PROTECTED] writes:
Thus we have reduced the problem of excluding certain types from a
typeclass to the problem of excluding all types from one particular
typeclass: Fail. How can we prevent the user from adding instances to
Fail?
By not exporting its
[EMAIL PROTECTED] writes:
> Thus we have reduced the problem of excluding certain types from a
> typeclass to the problem of excluding all types from one particular
> typeclass: Fail. How can we prevent the user from adding instances to
> Fail?
By not exporting its name?
--
__("< Mar
It is well known that type classes in Haskell are open. A user may at
any time extend a visible type class by providing a new
instance. There are situations where such an extensibility is
undesirable. We may want to prevent the user from adding an instance
to our class for some specific type
constraint I gave in the instance
declaration.
What am I doing wrong here?
There's no information in the instance type for the compiler to figure out
what u' (in the constraint expressions) might be. (See other responses.)
...
I would question whether or not you really should be using a
Ben Yu wrote:
> class Rule r u u' m where
> apply :: r -> u -> m u'
>
> data And = And
>
> data Bin a b o = Bin a b o
>
> instance (Monad m, Rule r1 u u' m, Rule r2 u' u'' m) =>
> Rule (Bin r1 r2 And) u u'' m where
> apply (Bin r1 r2 _) u = apply r1 u >>= apply r2
>
> Ghc complains
Another solution would be to use lexically scoped type variables:
instance (Monad m, Rule r1 u u' m, Rule r2 u' u'' m) => Rule (Bin r1 r2 And) u u'' m
where
apply (Bin r1 r2 _) u = ((apply r1 u)::m u') >>= apply r2
Martin
> Hi,
> please bear with me if my question turns out to be a stupid
Try class Rule r u u' m | r u -> u'
Martin
> Hi,
> please bear with me if my question turns out to be a stupid mistake. It has
> taken me hours to figure this out.
>
> class Rule r u u' m where
> apply :: r -> u -> m u'
>
> data And = And
>
> data Bin a b o = Bin a b o
>
> ins
Hi,
please bear with me if my question turns out to be a stupid mistake. It has
taken me hours to figure this out.
class Rule r u u' m where
apply :: r -> u -> m u'
data And = And
data Bin a b o = Bin a b o
instance (Monad m, Rule r1 u u' m, Rule r2 u' u'' m) => Rule (Bin r1 r2
And) u u'' m w
b)
cause of the overlap.
> - Would it be possible to _exclude_ a type from a class, to aviod
> overlapping instances? Perhaps what I want is negation in a type class
> declaration:
>
> < forall a . a /= [] => class ListT a
>
> Alternatively, I'd like to
I keep running
into the same problems related to managing type class contexts.
Ultimately, I think what I might want is a way of _excluding_ types from
classes, or declaring classes closed. Much of this is a rehash of what
others have presented; sorry if I don't give appropriate cr
Hi everyone
I've built GHC from CVS and I'm getting some odd errors about overlapping
instances. This is different from 6.0.1, but it's not obvious it is wrong,
so I'm probably missing something here.
The example is
class A x
class (A x) => B x
instance A x
instance B x
The new GHC complains th
Hi there,
I'm having a problem with type classes.
I have a class called PrettyPrintable,
For data type:
data Generic a = ..
I need to provide instance of Generic a for type class PrettyPrintable.
The parameter type a could be either PrettyPrintable or Show.
If I write the followin
There's another possible fix which makes use of scoped variables.
instance (RT r1 t1, RT r2 t2, TPair t t1 t2) => RT (RPair r1 r2) t where
rtId (RPair r1 r2) t = "RT (RPair " ++ rtId r1 t1 ++ " " ++ rtId r2 t2 ++")"
where (t1::t1,t2::t2) = prj t
^^
scoped vari
Dean Herington wrote:
> Can someone explain why the following doesn't work?
> {-# OPTIONS -fglasgow-exts #-}
> class R r where
> rId :: r -> String
> class (R r) => RT r t where
> rtId :: r -> t -> String
> data RPair r1 r2 = RPair r1 r2
> instance (R r1, R r2) => R (RPair r1 r2) where
>
Can someone explain why the following doesn't work? Is there some other
way to achieve the same effect (declaring a set of instances for pair-like
types in one go)?
Thanks.
Dean
swan(108)% cat Test1.hs
{-# OPTIONS -fglasgow-exts #-}
class R r where
rId :: r -> String
class (R r) => RT r t
Hello everyone
I think I'm close to useful results on the instance restrictions.
First there's an obvious extension to the Haskell98 rule. The H98 rule
says the instance head must be a type constructor applied to type
variables, and the context must mention only those type variables. This
gives a
maybe it
| > should be ignored. Adding the current goal as an axiom would not be
| > difficult, but I don't have time to do it today! Is anyone else
| > interested in such a feature?
|
| I would like to try making this change, but I couldn't puzzle out
enough
| of the type class
| I'm wondering if the general method of avoiding non-termination can be
| made to work in these more complex cases.
|
| Incidentally, the constraint solver stack overflow problem can be
| turned to our advantage. The typechecker's exhausting the stack should
| be considered a failure to match the
David McAllester's papers from about 1990-1994 may be
> relevant here. He has several papers on deciding when sets of inference
> rules are terminating, or terminating in polynomial time. (He applies
> this in the context of automated theorem proving, but it should apply
> perfect
ink some of David McAllester's papers from about 1990-1994 may be
relevant here. He has several papers on deciding when sets of inference
rules are terminating, or terminating in polynomial time. (He applies
this in the context of automated theorem proving, but it should apply
perfect
ld be ignored. Adding the current goal as an axiom would not be
> difficult, but I don't have time to do it today! Is anyone else
> interested in such a feature?
I would like to try making this change, but I couldn't puzzle out enough
of the type class system the last time I looked.
Simon Peyton-Jones wrote:
> > instance (Show (f (Mu f))) => Show (Mu f) where
> >show (In x) = show x
> >
> > instance Show (N (Mu N)) where
> >show Z = "Z"
> >show (S k) = "S "++show k
> But again, it's fragile isn't it? You are dicing with non-termination
> if you have instance dec
Brandon writes
| An application of Mu should be showable if the functor maps showable
types
| to showable types, so the most natural way to define the instance
seemed
| to be
|
| instance (Show a => Show (f a)) => Show (Mu f) where
| show (In x) = show x
|
| Of course that constraint didn't w
On Sun, 17 Aug 2003 [EMAIL PROTECTED] wrote:
>
> > I defined type recursion and naturals as
>
> > >newtype Mu f = In {unIn :: f (Mu f)}
> > >data N f = S f | Z
> > >type Nat = Mu N
>
> > An application of Mu should be showable if the functor maps showable types
> > to showable types, so the most
> I defined type recursion and naturals as
> >newtype Mu f = In {unIn :: f (Mu f)}
> >data N f = S f | Z
> >type Nat = Mu N
> An application of Mu should be showable if the functor maps showable types
> to showable types, so the most natural way to define the instance seemed
> to be
> instance
To try some of the examples from paper "Recursion Schemes from Comonads",
I wanted to define instances of Show and Observable for types defined as
the fixed point of a functor.
I defined type recursion and naturals as
>newtype Mu f = In {unIn :: f (Mu f)}
>data N f = S f | Z
>type Nat = Mu N
An
You can also export the type without exporting the constructors. That
way "import"ers can use the type in type signatures and instance
declarations while still not being able to use anything but the
exported interface.
E.g. instead of
Module Set
( emptySet
, makeSet
At 13:15 2002-01-22 -0500, Hongwei Xi wrote:
><...>
>In Haskell, I guess that the one implemented later is always chosen.
>Why can't I have two different implementations for an interface?
Actually, I can't think of situations where I would desire this.
Could you please give an example?
>Another
On Sat, 19 Jan 2002, [EUC-KR] ¾È±â¿µ wrote:
>>I prefer Haskell style type classes because
>>using them one can overload functions.
>>e.g.
>>
>>\begin{code}
>>class Container a where
>> celem :: Eq b => b -> a b -> Bool
>> cmap :: (Eq b, Eq c) => (b->c) -> a b -> a c
>>
>>data MyList a = MyList
I prefer Haskell style type classes because
using them one can overload functions.
e.g.
\begin{code}
class Container a where
celem :: Eq b => b -> a b -> Bool
cmap :: (Eq b, Eq c) => (b->c) -> a b -> a c
data MyList a = MyList [a] deriving Show
instance Container MyList where
celem x (MyL
is ad hoc overloading depends on whether you find
> ad hoc this particular theory of how sentence fragments in natural
> language combine with each other...
That particular theory is certainly unknown to the type class mechanism
and, I guess, hard to encode in it.
> I don't particularly
On 2001-02-16T09:52:41+0100, Lars Lundgren wrote:
> This is ad hoc overloading, and IMHO bad style, at least in haskell. As I
> understand it, haskell type classes were never intended to support this.
Well, whether this is ad hoc overloading depends on whether you find
ad hoc this particular theo
On 2001-02-16T07:56:42+, Marcin 'Qrczak' Kowalczyk wrote:
> > > test2 = apply [int 3] (apply [(+)::Int->Int->Int] [int 5])
> The monomorphism restriction bites again. A variable binding without
> a type signature is monomorphic...
But, but, but... The type *is* monomorphic, in the sense t
Thu, 15 Feb 2001 21:08:13 -0500, Dylan Thurston <[EMAIL PROTECTED]> pisze:
> On Thu, Feb 15, 2001 at 02:37:09PM -0500, Ken Shan wrote:
> > test2 = apply [int 3] (apply [(+)::Int->Int->Int] [int 5])
>
> What's strange is that when I tried this just now, the identical line at
> the interpreter
On Thu, 15 Feb 2001, Ken Shan wrote:
> Hello all,
>
> I'm trying to implement some simple natural language semantics with
> Haskell (Hugs), and I'm running into trouble with type classes.
> Here's what I want to do: Suppose that
>
> x :: a -> b
> y :: a
>
> then I want to write
>
>
On 2001-02-15T21:38:54-0500, Dylan Thurston wrote:
> > On Thu, Feb 15, 2001 at 02:37:09PM -0500, Ken Shan wrote:
> > > test2 = apply [int 3] (apply [(+)::Int->Int->Int] [int 5])
> > What's strange is that when I tried this just now, the identical line at
> > the interpreter prompt returned the
On Thu, Feb 15, 2001 at 09:08:13PM -0500, Dylan Thurston wrote:
> On Thu, Feb 15, 2001 at 02:37:09PM -0500, Ken Shan wrote:
> > test2 = apply [int 3] (apply [(+)::Int->Int->Int] [int 5])
>
> What's strange is that when I tried this just now, the identical line at
> the interpreter prompt retu
On Thu, Feb 15, 2001 at 02:37:09PM -0500, Ken Shan wrote:
> test2 = apply [int 3] (apply [(+)::Int->Int->Int] [int 5])
What's strange is that when I tried this just now, the identical line at
the interpreter prompt returned the correct answer [8]. This is with
Hugs from February 2000; I'm ab
Hello all,
I'm trying to implement some simple natural language semantics with
Haskell (Hugs), and I'm running into trouble with type classes.
Here's what I want to do: Suppose that
x :: a -> b
y :: a
then I want to write
apply x y = x y :: b
Moreover, if
x :: a
y :: a -
Hi Mark,
Thanks for the references you provided!
Mark P Jones wrote:
> My instinct (which perhaps somebody will prove incorrect) is that this will
> not help. Suppose, for example, that you needed to unify ([a],[b]) with f c
> as part of the type inference process. How would you solve this pr
Hi Zhanyong,
| In Haskell, instances of a type class can only be well-formed type
| constructors ...
| Note there is no type constructor abstraction.
|
| In practice, I found this rule too restrictive.
There are good reasons for the restrictions that were alluded to in
my constructor classes
> Simon Peyton-Jones <[EMAIL PROTECTED]> writes:
>> | How about extending TC with a branch for abstraction: | | TC ::= ...
>> | | /\a. TC -- abstraction | | This is too powerful and will get out
>> of control -- we surely
>> | don't want to give TC the full power of lambda-calculus. So let's
>>im
Simon Peyton-Jones <[EMAIL PROTECTED]> writes:
> | How about extending TC with a branch for abstraction:
> |
> | TC ::= ...
> | | /\a. TC -- abstraction
> |
> | This is too powerful and will get out of control -- we surely
> | don't want to give TC the full power of lambda-calculus. So
| How about extending TC with a branch for abstraction:
|
| TC ::= ...
| | /\a. TC -- abstraction
|
| This is too powerful and will get out of control -- we surely
| don't want to give TC the full power of lambda-calculus. So let's impose
a
| restriction: in /\a.TC, a must occur free in
Hi,
In Haskell, instances of a type class can only be well-formed type
constructors, which in turn is defined by:
TC ::= T -- a type constant
| a -- a variable
| TC TC -- a type constructor application
Note there is no type constructor abstraction.
In practice, I
but it relies on the `Typeable' type class and on existential types,
which in Hugs/ghc but which are not part of Haskell 98.
===
Proposal: add a function called say `class_cast' to the standard
l
Dear Sverker Nilsson,
Thanks for your message - interesting ideas and interesting questions.
[I'm copying the reply to the Haskell mailing list in case anyone
wishes to support your suggestions.]
First, one of Haskell's annoying features is that the scope of a type
variable in a type signature
t I had to use
-- (maxVal `asTypeOf` c) instead of (maxVal::a). I believe the reason
-- for this might be clear when I learn more. Somebody have a clue?
* Running into a problem: type class synonyms are not synonymous?
Then, I got the report on the developments of Haskell 1.3 and began to
98 matches
Mail list logo