Re: Type families in kind signatures with TypeInType

2016-09-23 Thread David Menendez
On Fri, Sep 23, 2016 at 3:00 PM, Simon Peyton Jones wrote: > Interesting. Is this case also an example, or is it a non-feature? > > > > class C t where > > type K t :: Type > > type T t :: K t -> Type > > > > m :: t -> T t a > > > > > > Ah, that’s quite different! We should do strong

Re: Type families in kind signatures with TypeInType

2016-09-23 Thread David Menendez
On Fri, Sep 23, 2016 at 3:19 AM, Simon Peyton Jones wrote: > This is an example of https://ghc.haskell.org/trac/ghc/ticket/12088. > Interesting. Is this case also an example, or is it a non-feature? class C t where type K t :: Type type T t :: K t -> Type m :: t -> T t a min.hs:21

Type families in kind signatures with TypeInType

2016-09-22 Thread David Menendez
Should the code below work in GHC 8.0.1? {-# LANGUAGE TypeInType, TypeFamilies #-} import Data.Kind (Type) type family K t :: Type type family T t :: K t -> Type data List type instance K List = Type type instance T List = [] Right now, I get an error like this on

Re: default roles

2013-10-11 Thread David Menendez
On Thu, Oct 10, 2013 at 10:09 PM, Edward Kmett wrote: > Wait, that sounds like it induces bad semantics. > > Can't we use that as yet another way to attack the sanctity of Set? > > class Ord a => Foo a where > badInsert :: a -> Set a -> Set a > > instance Foo Int where > badInsert = insert >

Re: default roles

2013-10-10 Thread David Menendez
On Thu, Oct 10, 2013 at 12:11 PM, Simon Peyton-Jones wrote: > Does GND make sense in cases where the superclasses aren't also derived? > If I had a type T whose Ord instance made use of the Eq instance for some > reason, and then I made a newtype T' with a new Eq instance and a GND Ord > instance

Re: default roles

2013-10-10 Thread David Menendez
On Wed, Oct 9, 2013 at 3:21 PM, Richard Eisenberg wrote: > Now I think we're on the same page, and I *am* a little worried about the > sky falling because of this. (That's not a euphemism -- I'm only a little > worried.) > > Well, maybe I should be more worried. > > The whole idea of roles is to

Re: Known problems with promoted tuples and lists in GHC 7.4.1?

2012-06-07 Thread David Menendez
it. > | -Original Message- > | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- > | users-boun...@haskell.org] On Behalf Of David Menendez > | Sent: 06 June 2012 23:50 > | To: José Pedro Magalhães > | Cc: glasgow-haskell-users@haskell.org Mailing List > | S

Re: Known problems with promoted tuples and lists in GHC 7.4.1?

2012-06-06 Thread David Menendez
= Phantom Something seems to have gone wrong internally. On Wed, Jun 6, 2012 at 5:43 PM, José Pedro Magalhães wrote: > Hi David, > > Are you using HEAD? If so, and you run into problems, please report them > (either here or as bugs in trac). > > > Thanks, > Pedro > > On We

Known problems with promoted tuples and lists in GHC 7.4.1?

2012-06-06 Thread David Menendez
Are there any known issues involving type-level pairs and lists? I've hit a few baffling type errors that went away when I refactored my code to use locally-defined pairs and lists instead of those provided by the prelude. More worryingly, I had one function that would stop passing the type checke

Re: Unit unboxed tuples

2011-12-24 Thread David Menendez
On Sat, Dec 24, 2011 at 7:15 AM, Duncan Coutts wrote: > On 23 December 2011 20:09, Stefan Holdermans wrote: >>> Here are the kinds of the type constructors: >>> >>>                 (,,) :: * -> * -> * -> * >>>                 (,) :: * -> * -> * >>>                 () :: * >>> >>>                

Re: Implicit 'forall' in data declarations

2010-10-25 Thread David Menendez
On Mon, Oct 25, 2010 at 3:16 AM, Simon Peyton-Jones wrote: > | On a related note, these are also apparently allowed (in 6.10.4): > |     f :: forall a. (Eq a => a -> a) -> a -> a > |    -- the Eq context prevents the function from ever being called. > > That's not true.  E.g. >        f ((==) True

Re: Implicit 'forall' in data declarations

2010-10-22 Thread David Menendez
On Fri, Oct 22, 2010 at 4:20 AM, Simon Peyton-Jones wrote: > Does anyone listening to this thread have an opinion?  Just to summarise, > Sebastian's > proposal is that Haskell's implicit quantification (adding foralls) would > occur *only* right > at the top of a  type signature. Before this di

Re: Inliner behaviour - tiny changes lead to huge performance differences

2009-11-13 Thread David Menendez
On Fri, Nov 13, 2009 at 2:04 AM, Bryan O'Sullivan wrote: > > And the lengthI function is defined more generally, in the hope that I could > use it for both Int and Int64 lengths: > > lengthI :: Integral a => Stream Char -> a > lengthI (Stream next s0 _len) = loop_length 0 s0 >     where >       lo

Re: inferred type doesn't type-check (using type families)

2009-11-03 Thread David Menendez
On Tue, Nov 3, 2009 at 3:20 PM, Max Bolingbroke wrote: > 2009/11/3 Daniel Fischer : >> Am Dienstag 03 November 2009 19:28:55 schrieb Roland Zumkeller: >>> Hi, >>> >>> Compiling >>> >>> > class WithT a where >>> >   type T a >>> > >>> > f :: T a -> a -> T a >>> > f = undefined >>> > >>> > g x = f x

Re: Type checker's expected and inferred types (reformatted)

2009-10-25 Thread David Menendez
On Sun, Oct 25, 2009 at 1:37 PM, Isaac Dupree wrote: > David Menendez wrote: >> >> The expected type is what the context wants (it's *ex*ternal). The >> inferred type is what the expression itself has (it's *in*ternal). >> >> So inferring the type Maybe

Re: Type checker's expected and inferred types (reformatted)

2009-10-23 Thread David Menendez
On Fri, Oct 23, 2009 at 9:46 PM, Isaac Dupree wrote: > C Rodrigues wrote: >> >> fun1 produces the error message: >> Couldn't match expected type `Maybe a' against inferred type `IO ()' >> In the first argument of `(>>=)', namely `bar' >> >> >> fun2 produces the error message: >> Couldn't match exp

GHC on Snow Leopard: best practices?

2009-10-06 Thread David Menendez
Is there any consensus about what needs to be done to get a working ghc installation on a Snow Leopard (Mac OS X 10.6) system? The Mac OS X wiki page[1] currently links to a blog post[2] that recommends manually patching /usr/bin/ghc, but I have also seen recommendations that people patch ghci, run

Re: "Could not deduce (MArray (STUArray s) Int (ST s)) from context ()" when applying runST

2009-07-21 Thread David Menendez
On Tue, Jul 21, 2009 at 5:30 PM, Christian Klauser wrote: > Hi, I'm in the process of learning haskell and came across this problem: > > Using `Glasgow Haskell Compiler, Version 6.10.4, for Haskell 98, stage 2 > booted by GHC version 6.10.1` > > Common beginning of the file > ==

Re: [Haskell-cafe] Re: FlexibleContexts and FlexibleInstances

2009-06-11 Thread David Menendez
On Thu, Jun 11, 2009 at 4:16 AM, Claus Reinke wrote: > |What you describe is exactly how I would *want* things to work. It's > |nice to hear my wishes echoed from a user perspective. :-) > > actually, I was describing how things seem to work right now. > > |> Only MultiParamTypeClasses does (and ne

Re: [Fwd: OSX installer -- first draft]

2009-06-03 Thread David Menendez
On Tue, Jun 2, 2009 at 5:38 AM, Duncan Coutts wrote: > OSX users, > > please could you try out Gregory's Haskell Platform package below and > send commentary to the platform list, or file tickets in the platform > trac, that'd be great. > http://trac.haskell.org/haskell-platform/newticket?componen

Re: Deep fmap with GADTs and type families.

2009-03-05 Thread David Menendez
On Thu, Mar 5, 2009 at 10:07 PM, Dan Doel wrote: > > But we've so far not been able to find a way of merely annotating the original > into working. So, I was wondering if any of the more knowledgeable folks here > could illuminate what's going wrong here, and whether I should expect my > original

Re: Segmentation fault trying to build ghc 6.10.1 using macports, Mac OS X 10.5, PPC

2009-02-03 Thread David Menendez
On Mon, Feb 2, 2009 at 9:58 AM, Gregory Wright wrote: > On Feb 2, 2009, at 4:48 AM, Christian Maeder wrote: > >> David Menendez wrote: >>> >>> I'm trying to upgrade GHC to 6.10.1 using macports on a PowerBook G4 >>> running OS X 10.5.5. From what I ca

Segmentation fault trying to build ghc 6.10.1 using macports, Mac OS X 10.5, PPC

2009-01-31 Thread David Menendez
I'm trying to upgrade GHC to 6.10.1 using macports on a PowerBook G4 running OS X 10.5.5. From what I can tell, I'm getting a segmentation fault from cabal-bin. This is possibly related to and . cd extensibl

Re: Changes in scoped type variable behavior?

2009-01-23 Thread David Menendez
2009/1/23 Austin Seipp : > > The code is attached to this message; the problem is in the normalize > function: > >> normalize :: (Modular s a, Integral a) => a -> M s a >> normalize a = M (mod a (modulus (u :: s))) "s" isn't scoped over the definition of "normalize" in this definition. You need an

Re: Differences in pattern matching syntax?

2009-01-16 Thread David Menendez
On Fri, Jan 16, 2009 at 11:07 AM, Simon Peyton-Jones wrote: > > So, clearly not a bug in GHC; but it would be more felicitous if it gave you > a warning about the instance declaration for Eq RuleType. The difficulty is > that it's not clear when to warn; it's ok to use default methods, but you

Re: Lazy minimum

2008-11-19 Thread David Menendez
On Thu, Nov 20, 2008 at 12:18 AM, Dan Doel <[EMAIL PROTECTED]> wrote: > On Wednesday 19 November 2008 11:38:07 pm David Menendez wrote: >> One possibility would be to add minimum and maximum to Ord with the >> appropriate default definitions, similar to Monoid's mconcat

Re: Lazy minimum

2008-11-19 Thread David Menendez
On Wed, Nov 19, 2008 at 8:06 PM, Dave Bayer <[EMAIL PROTECTED]> wrote: > What I'm wondering, however, is if there is a way to code "minimum" > efficiently in general, > >> minimum :: Ord a => [a] -> a > > > where one knows absolutely nothing further about the type "a", but one > believes that lazy

Re: Unicode's greek lambda

2008-11-19 Thread David Menendez
On Wed, Nov 19, 2008 at 5:24 PM, Duncan Coutts <[EMAIL PROTECTED]> wrote: > On Wed, 2008-11-19 at 15:01 +, Tony Finch wrote: >> On Wed, 19 Nov 2008, Simon Marlow wrote: >> > >> > Tue Jan 16 16:11:00 GMT 2007 Simon Marlow <[EMAIL PROTECTED]> >> > * Remove special lambda unicode character, it

Re: Control.Exception

2008-11-03 Thread David Menendez
On Mon, Nov 3, 2008 at 7:27 PM, shelarcy <[EMAIL PROTECTED]> wrote: > On Tue, 04 Nov 2008 07:40:50 +0900, David Menendez <[EMAIL PROTECTED]> wrote: >>> ie: >>> >>> action >>> `catches` >>>[ \(e :: ExitCode) -> ... >>>

Re: No atomic read on MVar?

2008-11-03 Thread David Menendez
On Mon, Nov 3, 2008 at 6:29 AM, Philip K.F. Hölzenspies <[EMAIL PROTECTED]> wrote: > > I have now implemented my variable as a pair of MVars, one of which serves as > a lock on the other. Both for performance reasons and for deadlock analysis, > I would really like an atomic read on MVars, though.

Re: Control.Exception

2008-11-03 Thread David Menendez
On Mon, Nov 3, 2008 at 12:53 PM, Duncan Coutts <[EMAIL PROTECTED]> wrote: > On Mon, 2008-11-03 at 09:26 -0800, Sigbjorn Finne wrote: >> One way to do this now is to use Control.Exception.catches: >> >> catches :: IO a -> [Handler a] -> IO a >> data Handler a where >> Handler :: forall a e. (E

Re: base-3 vs base-4 (Was: Breakage with 6.10)

2008-10-11 Thread David Menendez
2008/10/11 José Pedro Magalhães <[EMAIL PROTECTED]>: > In base4, no Data.Generics.* modules were kept. Instead, a new module, > Data.Data, contains all that was in Data.Generics.Basics and most of > Data.Generics.Instances. Data.Data? Surely we can come up with something better than that. -- Dav

Re: Illegal type synonym family application in instance (Was: Breakage with 6.10)

2008-10-10 Thread David Menendez
On Fri, Oct 10, 2008 at 8:40 PM, Niklas Broberg <[EMAIL PROTECTED]> wrote: > src\HSX\XMLGenerator.hs:71:0 >Illegal type synonym family application in instance: XML m >In the instance declaration for `EmbedAsChild m (XML m)´ > --- > > Could someone help me point out the problem h

Re: GADTs and functional dependencies

2008-09-23 Thread David Menendez
On Tue, Sep 23, 2008 at 1:44 PM, Chris Kuklewicz <[EMAIL PROTECTED]> wrote: > You cannot create a normal function "fun". You can make a type class > function > > fun :: Class a b => GADT a -> b > >> data GADT a where >> GADT :: GADT () >> GADT2 :: GADT String >> >> -- fun1 :: GADT () -> ()

Re: Arrow without `>>>'

2008-01-23 Thread David Menendez
On Jan 23, 2008 12:20 PM, Valery V. Vorotyntsev <[EMAIL PROTECTED]> wrote: > I've built GHC from darcs, and... > Could anybody tell me, what's the purpose of Arrow[1] not having `>>>' > method? It's derived from the Category superclass. -- Dave Menendez <[EMAIL PROTECTED]>

Re: [Haskell-cafe] class default method proposal

2007-12-11 Thread David Menendez
On Dec 11, 2007 1:29 PM, apfelmus <[EMAIL PROTECTED]> wrote: > Without the automatic search, this is already possible > > class Functor f where > fmap :: (a -> b) -> f a -> f b > > class Functor m => Monad m where > return :: a -> m a > (>>=) :: m a -> (a -> m b) -

Re: [Haskell-cafe] class default method proposal

2007-12-11 Thread David Menendez
On Dec 11, 2007 9:20 AM, Duncan Coutts <[EMAIL PROTECTED]> wrote: > So my suggestion is that we let classes declare default implementations > of methods from super-classes. Does this proposal have any unintended consequences? I'm not sure. > Please discuss :-) It creates ambiguity if two class

Re: forall a (Ord a => a-> a) -> Int is an illegal type???

2006-02-09 Thread David Menendez
. Foo a c) => (forall b. Foo a b => a -> b) -> Int -- David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the laws <http://www.eyrie.org/~zednenem> |of thermodynamics!" ___ Glasgow-haskell-

Re: forall a (Ord a => a-> a) -> Int is an illegal type???

2006-02-09 Thread David Menendez
s (like JHC core, IIRC) which treat "forall" and "->" as special cases of the dependent product. That is, "T -> U" is short for "Pi _:T. U" and "forall a. T" is short for "Pi a:*. T". Using that syntax, the types above become: Pi a

Re: Simple GADTs Question

2005-10-06 Thread David Menendez
t) I think you want something like this: Deriv :: Int -> DFExpr t -> DFExpr t -> DFExpr t Ignorning the other clauses, it's equivalent to data DFExpr t = Deriv Int (DFExpr t) (DFExpr t) -- David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the laws

Re: Automatically derived instances

2005-08-28 Thread David Menendez
class A t where a :: t class B t where b :: t class C t where c :: t instance A t => C t where c = a instance B t => C t where c = b instance A Char where a = 'a' instance B Char where b = 'b' Wha

Error building GHC from darwin ports

2005-06-16 Thread David Menendez
/opt/local/var/db/dports/build/file. _opt_local_var_db_dports_sources_rsync.rsync.opendarwin. org_dpupdate_dports_lang_ghc/work/ghc-6.4/happy/src/happy-inplace] Error 2 Warning: the following items did not execute (for ghc): com.apple.destroot com.apple.build Error: Unable to upgrade port: 1 -- David Menendez <[EMAIL PROTECTED]>