Thanks for the responses. I realized after sending the message that
it wasn't clear exactly what I was advocating, which is probably more
modest that what people are thinking.
Mostly I was hoping the AssociatedTypes wiki page could be updated to
reflect that AssociatedTypes can't replace Function
At Sun, 29 May 2011 19:35:15 -0400,
Dan Doel wrote:
>
> On Sun, May 29, 2011 at 6:45 PM, Ben Millwood
> wrote:
> 1) Disallow the overlapping instance C Int Char, because it is
> incompatible with the C Int Int from the other module. This is what
> GHC 7 seems to do.
This seems like the only rea
At Tue, 14 Jun 2011 09:36:41 +,
Simon Peyton-Jones wrote:
>
> 5. David wants a wiki page fixed. But which one? And how is it "locked
> down"?
This page:
http://hackage.haskell.org/trac/haskell-prime/wiki/FunctionalDependencies
Currently under cons for FunctionalDependencies, it
At Tue, 14 Jun 2011 10:40:48 -0400,
Dan Doel wrote:
>
> > 1. As things stand in GHC you can do some things with functional
> > dependencies that you can't do with type families. The archetypical example
> > is type equality. We cannot write
> > type family Eq a b :: *
> > type ins
At Tue, 14 Jun 2011 12:31:47 -0400,
Dan Doel wrote:
>
> Sorry about the double send, David. I forgot to switch to reply-all in
> the gmail interface.
>
> Okay. I don't really write a lot of code like this, so maybe I missed
> the quirks.
>
> In that case, HList has been relying on broken behavio
At Tue, 14 Jun 2011 15:09:02 -0400,
Dan Doel wrote:
>
> On Tue, Jun 14, 2011 at 1:19 PM,
> wrote:
> > No, these are not equivalent. The first one "TypeEq a b c" is just
> > declaring an instance that works "forall c". The second is declaring
> > multiple instances, which, if there were class me
At Tue, 14 Jun 2011 19:21:38 -0400,
Dan Doel wrote:
>
> If this is really about rules for selecting instances unambiguously
> without any regard to whether some parameters are actually functions
> of other parameters, then the name "functional dependencies" is pretty
> poor.
Maybe "functional dep
At Wed, 15 Jun 2011 10:36:46 +,
Simon Peyton-Jones wrote:
>
> The issue doesn't even arise with type families:
>
> class MonadState m where
> type State m :: *
>
> instance MonadState m => MonadState (MaybeT m) where
> type State (MaybeT m) = State m
>
> So examp
At Tue, 14 Jun 2011 19:52:00 -0700 (PDT),
o...@okmij.org wrote:
>
>
> Dan Doel wrote:
> >class C a b | a -> b where
> > foo :: a -> b
> > foo = error "Yo dawg."
> >
> >instance C a b where
>
> The instance 'C a b' blatantly violates functional dependency and
> should not have b
At Wed, 15 Jun 2011 10:10:14 -0700,
Iavor Diatchki wrote:
>
> Hello,
>
> On Wed, Jun 15, 2011 at 12:25 AM, Simon Peyton-Jones
> wrote:
>
> | > class C a b | a -> b where
> | > foo :: a -> b
> | > foo = error "Yo dawg."
> | >
> | > instance C a b where
>
>
At Wed, 15 Jun 2011 16:54:24 -0700,
Iavor Diatchki wrote:
>
> > | > class C a b | a -> b where
> > | > foo :: a -> b
> > | > foo = error "Yo dawg."
> > | >
> > | > instance C a b where
> >
> > Wait. What about
> >
At Wed, 15 Jun 2011 20:48:07 -0400,
Dan Doel wrote:
>
> I know that the actual, current implementation won't violate type
> safety. But there are reasonable expectations for how *functional
> dependencies* might work that would cause problems. Here's an example.
>
> class C a b | a -> b
>
>
Okay, we seem to be having a debate where, to caricature only a
little, I'm arguing that Fundeps/UndecidableInstances are ugly but
useful, and other people are arguing that they are truly absolutely
horrible in their current GHC implementation. I think the debate
boils down to where you see the sc
At Fri, 17 Jun 2011 13:21:41 +,
Simon Peyton-Jones wrote:
>
> Concerning "1. mutual dependencies" I believe that equality
> superclasses provide the desired expressiveness. The code may not
> look quite as nice, but equality superclasses (unlike fundeps) will
> play nicely with GADTs, type fa
At Mon, 20 Jun 2011 09:57:38 +0200,
José Pedro Magalhães wrote:
>
> class JSON1 a r | a -> r
> toJSON1 :: a -> r
>
> instance (JSON a) => JSON1 (S1 NoSelector (K1 c a)) [Value] where
> toJSON1 (M1 (K1 a)) = [toJSON a]
>
> instance (Selector x, JSON a) => JSON
At Tue, 21 Jun 2011 10:01:24 +0200,
José Pedro Magalhães wrote:
>
> | One thing you could do to help in this specific case would be to use a
> | different M1 tag--e.g., M1 S ... for selectors and M1 NS ... for
> | fields without selectors (or K1 NS). I presume you've already
> | c
At Tue, 21 Jun 2011 00:35:46 -0700 (PDT),
o...@okmij.org wrote:
>
>
> I have implemented type-level TYPEREP (along with a small library for
> higher-order functional programming at the type level). Overlapping
> instances may indeed be avoided. The library does not use functional
> dependencies
At Thu, 23 Jun 2011 00:40:38 -0700 (PDT),
o...@okmij.org wrote:
>
>
> > How would you make this safe for dynamic loading? Would you have to
> > keep track of all the package/module names that have been linked into
> > the program and/or loaded, and not allow duplicates? Is dynamic
> > unloading
At Sun, 26 Jun 2011 23:25:31 +1200,
Anthony Clayden wrote:
>
> Totally brilliant, and almost impenetrable.
>
> If I understand what's going on (big IF), I'm wondering a
> few things:
> - You've used type-level NAT to encode the type.
> What if two different types get encoded as the same NAT?
>
The Haskell 2010 report contains ambiguous and sometimes contradictory
definitions of the terms "simple pattern binding" and "declaration
group". The confusion is compounded by the phrasing of the
monomorphism restriction, which is carried over from the Haskell98
report in which a different defini
At Mon, 27 Jun 2011 00:06:09 +0100,
Paterson, Ross wrote:
>
> I don't believe the definition of "depends" in Section 4.5.1 needs
> to change. The Report consistently uses "expression type signature"
> for the expression and "type signature" for the declaration, so it is
> clear that the latter is
At Mon, 27 Jun 2011 15:02:33 +0100,
Paterson, Ross wrote:
>
> > There is no a priori reason why b should depend on a in a pair of
> > bindings such as these:
> >
> >a = const (\x -> x) b
> >b = const (a :: Int -> Int) (a :: Bool -> Bool)
>
> There is: section 3.16 says that in an
22 matches
Mail list logo