Re: Proposal: ArgumentDo

2016-07-10 Thread Ryan Trinkle
Akio,

Yes, definitely!  I think I was a bit unclear, but what I was trying to say
was that, in the (rare) circumstances in which I'm editing Haskell without
the benefit of syntax highlighting, the difference between keywords and
identifiers is not quite as obvious.  In those cases, requiring an operator
may make things easier to read.

This is a very small point, but I appreciate you taking the time to respond!


Ryan

On Sun, Jul 10, 2016 at 9:53 PM, Akio Takano <tkn.a...@gmail.com> wrote:

> Hi Ryan,
>
> On 7 July 2016 at 19:40, Ryan Trinkle <ryan.trin...@gmail.com> wrote:
> > I'm very on the fence on this topic, but one point i haven't seen
> mentioned
> > is the influence of syntax highlighting on this.  My guess is that I
> would
> > like this extension when I have syntax highlighting available and would
> > dislike it when I do not.
>
> vim and hscolour can highlight code with the new syntax just fine. I
> imagine that most existing syntax highlighter will be able to deal
> with the new syntax without needing to be updated, because they
> usually don't attempt to fully parse expressions: they mostly just
> pattern-match on tokens.
>
> - Akio
>
> >
> > Also, I agree with Carter about the record update syntax - I find it
> harder
> > to parse visually than most other parts of the language, and I expect I'd
> > find curly brace syntax for inline 'do' harder to parse in a similar way.
> > On the other hand, maybe I should get used to both...
> >
> > On Thu, Jul 7, 2016 at 2:50 PM, Joachim Breitner <
> m...@joachim-breitner.de>
> > wrote:
> >>
> >> Hi,
> >>
> >> Am Donnerstag, den 07.07.2016, 13:15 -0400 schrieb Carter Schonwald:
> >> > agreed -1,
> >> > ambiguity is bad for humans, not just parsers.
> >> >
> >> > perhaps most damningly,
> >> > > f do{ x } do { y }
> >> >
> >> > is just reallly really weird/confusing to me,
> >>
> >> It is weird to me, but in no way confusing under the simple new rules,
> >> and I am actually looking forward to using that, and also to reading
> >> code with that.
> >>
> >> In fact, everything I wanted to pass two arguments in do-notation to a
> >> function I felt at a loss. The prospect of itemizing multiple large
> >> arguments to a function by writing
> >>
> >> someFunctionWithManyArguments
> >>   do firstArgument
> >>   do second Argument which may span
> >>several lines
> >>   do third Argument
> >>
> >> is actually making me happy! It feels like going from XML to YAML...
> >>
> >> Greetings,
> >> Joachim
> >>
> >> --
> >>
> >> Joachim “nomeata” Breitner
> >>   m...@joachim-breitner.de • https://www.joachim-breitner.de/
> >>   XMPP: nome...@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F
> >>   Debian Developer: nome...@debian.org
> >> ___
> >> Glasgow-haskell-users mailing list
> >> Glasgow-haskell-users@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
> >>
> >
> >
> > ___
> > Glasgow-haskell-users mailing list
> > Glasgow-haskell-users@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
> >
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: Proposal: ArgumentDo

2016-07-07 Thread Ryan Trinkle
I'm very on the fence on this topic, but one point i haven't seen mentioned
is the influence of syntax highlighting on this.  My guess is that I would
like this extension when I have syntax highlighting available and would
dislike it when I do not.

Also, I agree with Carter about the record update syntax - I find it harder
to parse visually than most other parts of the language, and I expect I'd
find curly brace syntax for inline 'do' harder to parse in a similar way.
On the other hand, maybe I should get used to both...

On Thu, Jul 7, 2016 at 2:50 PM, Joachim Breitner 
wrote:

> Hi,
>
> Am Donnerstag, den 07.07.2016, 13:15 -0400 schrieb Carter Schonwald:
> > agreed -1,
> > ambiguity is bad for humans, not just parsers.
> >
> > perhaps most damningly,
> > > f do{ x } do { y }
> >
> > is just reallly really weird/confusing to me,
>
> It is weird to me, but in no way confusing under the simple new rules,
> and I am actually looking forward to using that, and also to reading
> code with that.
>
> In fact, everything I wanted to pass two arguments in do-notation to a
> function I felt at a loss. The prospect of itemizing multiple large
> arguments to a function by writing
>
> someFunctionWithManyArguments
>   do firstArgument
>   do second Argument which may span
>several lines
>   do third Argument
>
> is actually making me happy! It feels like going from XML to YAML...
>
> Greetings,
> Joachim
>
> --
>
> Joachim “nomeata” Breitner
>   m...@joachim-breitner.de • https://www.joachim-breitner.de/
>   XMPP: nome...@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F
>   Debian Developer: nome...@debian.org
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: type error formatting

2015-10-24 Thread Ryan Trinkle
This looks like an improvement to me.  I love the idea of a visual
demarcation between sections, too; the bullets seem like a good choice
there (the horizontal lines seem like they'd take up more space).


Ryan

On Sat, Oct 24, 2015 at 6:07 AM, Roman Cheplyaka  wrote:

> I have the same issue with the current error messages. I think these are
> all good ideas.
>
> On 10/24/2015 05:48 AM, Evan Laforge wrote:
> > Here's a typical simple type error from GHC:
> >
> > Derive/Call/India/Pakhawaj.hs:142:62:
> > Couldn't match type ‘Text’ with ‘(a1, Syllable)’
> > Expected type: [([(a1, Syllable)], [Sequence Bol])]
> >   Actual type: [([Syllable], [Sequence Bol])]
> > Relevant bindings include
> >   syllables :: [(a1, Syllable)]
> > (bound at Derive/Call/India/Pakhawaj.hs:141:16)
> >   best_match :: [(a1, Syllable)]
> > -> Maybe (Int, ([(a1, Syllable)], [(a1, Sequence
> Bol)]))
> > (bound at Derive/Call/India/Pakhawaj.hs:141:5)
> > In the second argument of ‘mapMaybe’, namely ‘all_bols’
> > In the second argument of ‘($)’, namely
> >   ‘mapMaybe (match_bols syllables) all_bols’
> >
> > I've been having more trouble than usual reading GHC's errors, and I
> > finally spent some time to think about it.  The problem is that this new
> > "relevant bindings include" section gets in between the expected and
> > actual types (I still don't like that wording but I've gotten used to
> > it), which is the most critical part, and the location context, which is
> > second most critical.  Notice the same effect in the previous sentence
> > :)  After I see a type error the next thing I want to see is the where
> > it happened, so I have to skip over the bindings, which can be long and
> > complicated.  Then I usually know what to do, and only look into the
> > bindings if something more complicated is going on, like wonky
> > inference.  So how about reordering the message:
> >
> > Derive/Call/India/Pakhawaj.hs:142:62:
> > Couldn't match type ‘Text’ with ‘(a1, Syllable)’
> > Expected type: [([(a1, Syllable)], [Sequence Bol])]
> >   Actual type: [([Syllable], [Sequence Bol])]
> > In the second argument of ‘mapMaybe’, namely ‘all_bols’
> > In the second argument of ‘($)’, namely
> >   ‘mapMaybe (match_bols syllables) all_bols’
> > Relevant bindings include
> >   syllables :: [(a1, Syllable)]
> > (bound at Derive/Call/India/Pakhawaj.hs:141:16)
> >   best_match :: [(a1, Syllable)]
> > -> Maybe (Int, ([(a1, Syllable)], [(a1, Sequence
> Bol)]))
> > (bound at Derive/Call/India/Pakhawaj.hs:141:5)
> >
> > After this, why not go one step further and set off the various sections
> > visibly to make it easier to scan.  The context section can also be
> > really long if it gets an entire do block or record:
> >
> > Derive/Call/India/Pakhawaj.hs:142:62:
> >   * Couldn't match type ‘Text’ with ‘(a1, Syllable)’
> > Expected type: [([(a1, Syllable)], [Sequence Bol])]
> >   Actual type: [([Syllable], [Sequence Bol])]
> >   * In the second argument of ‘mapMaybe’, namely ‘all_bols’
> > In the second argument of ‘($)’, namely
> >   ‘mapMaybe (match_bols syllables) all_bols’
> >   * Relevant bindings include
> >   syllables :: [(a1, Syllable)]
> > (bound at Derive/Call/India/Pakhawaj.hs:141:16)
> >   best_match :: [(a1, Syllable)]
> > -> Maybe (Int, ([(a1, Syllable)], [(a1, Sequence
> Bol)]))
> > (bound at Derive/Call/India/Pakhawaj.hs:141:5)
> >
> > Or alternately, taking up a bit more vertical space:
> >
> > Derive/Call/India/Pakhawaj.hs:142:62:
> > Couldn't match type ‘Text’ with ‘(a1, Syllable)’
> > Expected type: [([(a1, Syllable)], [Sequence Bol])]
> >   Actual type: [([Syllable], [Sequence Bol])]
> > -
> > In the second argument of ‘mapMaybe’, namely ‘all_bols’
> > In the second argument of ‘($)’, namely
> >   ‘mapMaybe (match_bols syllables) all_bols’
> > -
> > Relevant bindings include
> >   syllables :: [(a1, Syllable)]
> > (bound at Derive/Call/India/Pakhawaj.hs:141:16)
> >   best_match :: [(a1, Syllable)]
> > -> Maybe (Int, ([(a1, Syllable)], [(a1, Sequence
> Bol)]))
> > (bound at Derive/Call/India/Pakhawaj.hs:141:5)
> >
> > Thoughts?  It seems simple enough that I could do myself, but of course
> > not without buy-in.
>
>
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: Proposal: ValidateMonoLiterals - Initial bikeshed discussion

2015-02-06 Thread Ryan Trinkle
I think the idea of compile-time validation for overloaded literals is
fantastic, and doing it with nicer syntax than quasiquoting would really
improve things.  However, I'm a bit confused about specifically how the
requirement that it be monomorphic will play into this.  For example, if I
have:

x = 1

Presumably this will compile, and give a run-time error if I ever
instantiate its type to Even.  However, if I have:

x :: Even
x = 1

it will fail to compile?  Furthermore, if I have the former, and type
inference determines that its type is Even, it sounds like that will also
fail to compile, but if type inference determines that its type is forall
a. Nat a = a, then it will successfully compile and then fail at runtime.

Am I understanding this correctly?


Ryan

On Fri, Feb 6, 2015 at 8:55 AM, Erik Hesselink hessel...@gmail.com wrote:

 On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese
 dominique.devri...@cs.kuleuven.be wrote:
  Agreed.  For the idea to scale, good support for type-level
  programming with Integers/Strings/... is essential.  Something else
  that would be useful is an unsatisfiable primitive constraint
  constructor `UnsatisfiableConstraint :: String - Constraint` that can
  be used to generate custom error messages. Then one could write
  something like
 
type family MustBeTrue (t :: Bool) (error :: String) :: Constraint
type family MustBeTrue True _ = ()
type family MustBeTrue False error = UnsatisfiableConstraint error
 
type family MustBeEven (n :: Nat) :: Constraint
type family MustBeEven n = MustBeTrue (IsEven n) (Error in Even
  literal :' ++ show n ++ ' is not even!)
 
instance (KnownNat n, MustBeEven n) = HasIntegerLiteral Even n where
 ...

 Note that there is a trick to fake this with current GHC: you can
 write an equality constraint that is false, involving the type level
 string:

type family MustBeTrue False error = (() ~ error)

 Erik
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: ValidateMonoLiterals - Initial bikeshed discussion

2015-02-06 Thread Ryan Trinkle
My greatest concern here would be that, as an application is maintained, a
literal might go from monomorphic to polymorphic, or vice versa, without
anybody noticing.  It sounds like this could result in a value silently
becoming partial, which would be a big problem for application stability;
in the opposite case - a partial value becoming a compile-time error - I am
somewhat less concerned, but it could still be confusing and disruptive.

I would prefer that there be some syntactic indication that I want my
literal to be checked at compile time.  This syntax could also add whatever
monomorphism requirement is needed, and then it would become a compile-time
error for the value to become polymorphic.  I don't know nearly enough
about the type system to know whether this is possible.

Also, it seems to me that it might not be so clean as monomorphic versus
polymorphic.  For example, suppose I have this:

newtype PostgresTableName s = PostgresTableName String

where 's' is a phantom type representing the DB schema that the name lives
in.  The validation function is independent of the schema - it simply fails
if there are illegal characters in the name, or if the name is too long.
So, ideally, (foo\0bar :: forall s. PostgresTableName s) would fail at
compile time, despite being polymorphic.


Ryan

On Fri, Feb 6, 2015 at 11:16 AM, Merijn Verstraaten mer...@inconsistent.nl
wrote:

 Ryan,

 Unfortunately, yes, you are understanding that correctly.

 The reason I qualified it with monomorphic only is that, I want to avoid
 breakage that would render the extension practically unusable in real code.

 Let's say I right now have:

 foo :: Num a = [a] - [a]
 foo = map (+1)

 I have two options 1) we compile this as currently using fromIntegral and
 it WILL break for Even or 2) we reject any polymorphic use of literals like
 this. Given the amount of numerical code relying on the polymorphism of
 Num, I think the option of not being able to compile Num polymorphic code
 is completely out of the question. Almost no application  would work.

 I would advocate in favour of not requiring an IsList/IsString instance
 for the validation class, this would allow you to write a conversion that
 ONLY converts literals in a validated way and will never successfully
 convert literals without the extension, since with the extension disabled
 GHC would try to use the fromList/fromString from the IsString/IsList
 classes which do not exist.

 Unfortunately, given how deeply fromIntegral is tied to the Num class I
 don't see any way to achieve the same for Num. The only option would be to
 not make Even an instance of Num, that way the same trick as above could
 work. Removing fromIntegral from Num is obviously not going to happen and
 without doing that I don't see how we could prevent someone using
 fromIntegral manually to convert to Even in a way that won't break Num
 polymorphic functions. If you have any ideas on how to tackle this, I'm all
 open to hearing them!

 I agree with you that this is ugly, but I console myself with the thought
 that being able to check all monomorphic literals is already a drastic
 improvement over the current state. And in the case of lists and strings we
 could actually ensure that things work well, since almost no one writes
 IsString polymorphic code.

 Cheers,
 Merijn

  On 6 Feb 2015, at 16:59, Ryan Trinkle ryan.trin...@gmail.com wrote:
 
  I think the idea of compile-time validation for overloaded literals is
 fantastic, and doing it with nicer syntax than quasiquoting would really
 improve things.  However, I'm a bit confused about specifically how the
 requirement that it be monomorphic will play into this.  For example, if I
 have:
 
  x = 1
 
  Presumably this will compile, and give a run-time error if I ever
 instantiate its type to Even.  However, if I have:
 
  x :: Even
  x = 1
 
  it will fail to compile?  Furthermore, if I have the former, and type
 inference determines that its type is Even, it sounds like that will also
 fail to compile, but if type inference determines that its type is forall
 a. Nat a = a, then it will successfully compile and then fail at runtime.
 
  Am I understanding this correctly?
 
 
  Ryan
 
  On Fri, Feb 6, 2015 at 8:55 AM, Erik Hesselink hessel...@gmail.com
 wrote:
  On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese
  dominique.devri...@cs.kuleuven.be wrote:
   Agreed.  For the idea to scale, good support for type-level
   programming with Integers/Strings/... is essential.  Something else
   that would be useful is an unsatisfiable primitive constraint
   constructor `UnsatisfiableConstraint :: String - Constraint` that can
   be used to generate custom error messages. Then one could write
   something like
  
 type family MustBeTrue (t :: Bool) (error :: String) :: Constraint
 type family MustBeTrue True _ = ()
 type family MustBeTrue False error = UnsatisfiableConstraint error
  
 type family MustBeEven (n :: Nat) :: Constraint

Re: GHC 7.4.2 on Ubuntu Trusty

2014-10-22 Thread Ryan Trinkle
Here's an off-the-wall solution idea: you could try the Nix package
manager.  It essentially sandboxes everything all the time, so you
shouldn't have any trouble with dependencies like this, and ghc 7.4.2 is
explicitly supported.  Of course, if your requirements include tight apt
integration, this won't help; but if you just need to get things running
reliably somehow, I think Nix can handle it.

Feel free to message me off-list for more details.


Ryan

On Wed, Oct 22, 2014 at 6:48 AM, Yitzchak Gale g...@sefer.org wrote:

 In order support some older software that we released, we need
 to get a working GHC 7.4.2 on Ubuntu Trusty. We currently have
 GHC 7.8.3.

 The binary tarball for GHC 7.4.2 does not install on Trusty due to
 multiple incompatibilities. For example, GHC requires GMP 3, but
 Trusty only provides GMP = 4. Etc.

 I tried building GHC 7.4.2. from source on Trusty. But the process
 won't boot from our currently installed GHC 7.8.3. The oldest
 GHC binary I can get is GHC 7.6.3, which happens to be
 still available from the Ubuntu distribution itself (neither the binary
 tarball nor compiling from source work for GHC 7.6.3 on Trusty
 either). But booting from GHC 7.6.3 won't work either.

 How do I get a working GHC 7.4.2 on Trusty?

 Thanks,
 Yitz
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: The future of the haskell2010/haskell98 packages - AKA Trac #9590

2014-09-30 Thread Ryan Trinkle
Would something like John Meacham's class alias proposal (
http://repetae.net/recent/out/classalias.html) help alleviate this problem?

On Tue, Sep 30, 2014 at 5:02 PM, Brandon Allbery allber...@gmail.com
wrote:

 On Tue, Sep 30, 2014 at 5:00 PM, Malcolm Wallace malcolm.wall...@me.com
 wrote:

 How about doing the honest thing, and withdrawing both packages in
 ghc-7.10?  Haskell'98 is now 15 years old, and the 2010 standard was never
 really popular anyway.


 There are apparently educators using both, although they're not used much
 if at all in production.

 --
 brandon s allbery kf8nh   sine nomine
 associates
 allber...@gmail.com
 ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: EPHEMERAL pragma

2012-10-25 Thread Ryan Trinkle
On a related note, it would be nice to have a little more tooling for
ensuring that SPECIALIZE pragmas take full effect.  In particular, it's
nice to write generic code over numeric types (Double, Float), but if it
doesn't get specialized away, performance really tanks.  Going through a
codebase and manually annotating all uses of the class can be really
laborious, and it's a brittle solution.  It would be nice to indicate to
the compiler that a particular instance or even a particular class should
always be specialized away, and to get some warnings when this isn't
possible.

Of course, I have no idea what the ramifications of this would be; I just
thought I'd file the idea under this thread.


Ryan

On Thu, Oct 25, 2012 at 9:56 AM, José Pedro Magalhães j...@cs.uu.nl wrote:

 Hi all,

 Following up on a chat with Simon Peyton Jones at ICFP, I would like to
 discuss the
 possible introduction of a EPHEMERAL pragma. For example:

 {-# EPHEMERAL Rep #-}
 data Rep = ...


 This pragma would indicate that the programmer intends the Rep datatype
 not to
 be present in the final generated core code. Its proposed semantics are
 the following:

 1. Make the compiler very keen to inline any functions that produce or
 consume Rep.

 2. If Rep is exported, make all functions that operate on Rep INLINABLE
 (that is, make
 their code available for inlining in other modules).

 3. Emit a warning if the generated core code still contains uses of Rep.

 My main use case for such a pragma is in the generic representation of
 datatypes in
 GHC.Generics. It's clear that we don't want sums and products lying around
 in user
 code, and in most cases we can get rid of them by inlining aggressively.
 Hopefully
 such a pragma can simplify or entirely replace the use of INLINE/INLINABLE
 pragmas
 in some cases.

 However, I'm not sure how well this can work in practice. Regarding (3),
 for instance,
 it's clear that functions that operate on Rep will be around in the final
 core code;
 perhaps only functions which do not directly produce or consume Rep, yet
 end up
 having values of Rep within them, should trigger a warning.

 (1) is hard to do well, in general. In particular when there are rewriting
 rules involving
 values of Rep, or functions that produce/consume Rep, the order in which
 they are
 inlined might affect the elimination of Rep values.

 In any case, I thought I'd share this with this list, in the hope to get
 feedback regarding
 how to improve the inliner (and the feedback programmers get regarding
 inlining).


 Cheers,
 Pedro


 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Superclass Cycle via Associated Type

2011-07-22 Thread Ryan Trinkle
My situation is fairly similar to Gabor's, and, like him, I was able to make
do with an equality superclass.  However, instead of combining two classes,
I found that I needed to add a third.

My concept here is to create two monads which share much of their
functionality, but not all of it.  Specifically, one of them is high and
one is low.  Values of type Low encapsulate computations in the low
monad, and values of type High encapsulate values in the high monad.  Both
low and high monads can *create* Low and High values and *execute* Low
values, but only the high monad can *execute* High values.

So, what I'd like to write is:

data High a

data Low a

class (Monad m, MonadLow (LowM m), MonadHigh (HighM m)) = MonadLow m where
  execLow :: Low a - m a
  type LowM m :: * - *
  mkLow :: LowM m a - m (Low a)
  type HighM m :: * - *
  mkHigh :: HighM m a - m (High a)

class MonadLow m = MonadHigh m where
  execHigh :: High a - m a

data L a

data H a

instance Monad L

instance MonadLow L where
type LowM L = L
type HighM L = H

instance Monad H

instance MonadLow H where
type LowM H = L
type HighM H = H

instance MonadHigh H

Of course, this has a superclass cycle.  Instead, I can write:

...
class Monad m = MonadLow m where
...
class (MonadHigh m, MonadLow (LowM m), HighM m ~ m, HighM (LowM m) ~ m, LowM
(LowM m) ~ LowM m) = MonadHigh' m where {}

Then I can use MonadHigh' wherever I might have instead used MonadHigh, and
achieve roughly the result I was looking for.  However, it doesn't seem like
a very clean definition to me.

That being said, I haven't found any problem with using the MonadHigh'
approach, although I've just recently started investigating it.


Ryan


2011/7/22 Dan Doel dan.d...@gmail.com

 2011/7/22 Gábor Lehel illiss...@gmail.com:
  Yeah, this is pretty much what I ended up doing. As I said, I don't
  think I lose anything in expressiveness by going the MPTC route, I
  just think the two separate but linked classes way reads better. So
  it's just a would be nice thing. Do recursive equality superclasses
  make sense / would they be within the realm of the possible to
  implement?

 Those equality superclasses are not recursive in the same way, as far
 as I can tell. The specifications for classes require that there is no
 chain:

C ... = D ... = E ... = ... = C ...

 However, your example just had (~) as a context for C, but C is not
 required by (~). And the families involved make no reference to C,
 either. A fully desugared version looks like:

type family Frozen a :: *
type family Thawed a :: *

class (..., Thawed (Frozen t) ~ t) = Mutable t where ...

 I think this will be handled if you use a version where equality
 superclasses are allowed.

 -- Dan

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Superclass Cycle via Associated Type

2011-07-20 Thread Ryan Trinkle
The following code doesn't compile, but it seems sensible enough to me.  Is
this a limitation of GHC or is there something I'm missing?

class C (A x) = C x where
  type A x :: *
instance C Int where
  type A Int = String
instance C String where
  type A String = Int


The error I get is:


SuperclassCycle.hs:1:1:
Cycle in class declarations (via superclasses):
  SuperclassCycle.hs:(1,1)-(2,15): class C (A x) = C x where {
   type family A x :: *; }



Ryan
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users