From david.feuer at gmail.com Sun Feb 1 18:54:56 2015 From: david.feuer at gmail.com (David Feuer) Date: Sun, 1 Feb 2015 13:54:56 -0500 Subject: What is the story behind the type of undefined? Message-ID: If I define {-# LANGUAGE MagicHash #-} g :: Int# -> Int g 3# = 3 myUndefined = undefined then this gives a sensible type error about a kind mismatch: usual :: Int usual = g myUndefined but this, oddly enough, compiles: peculiar :: Int peculiar = g undefined GHCi and the definition in GHC.Error agree that undefined :: a So why am I allowed to use it as a type of kind #? From adam at well-typed.com Sun Feb 1 19:07:47 2015 From: adam at well-typed.com (Adam Gundry) Date: Sun, 01 Feb 2015 19:07:47 +0000 Subject: What is the story behind the type of undefined? In-Reply-To: References: Message-ID: <54CE7983.6000104@well-typed.com> Hi David, See Note [Error and friends have an "open-tyvar" forall] in MkCore. The short answer is that error and undefined are treated magically by GHC: the actual type of undefined is forall (a :: OpenKind) . a and both * and # are subkinds of OpenKind. (There is a plan to get rid of this subkinding in favour of normal polymorphism, but it hasn't been implemented yet. See https://ghc.haskell.org/trac/ghc/wiki/NoSubKinds for more details.) Hope this helps, Adam On 01/02/15 18:54, David Feuer wrote: > If I define > > {-# LANGUAGE MagicHash #-} > > g :: Int# -> Int > g 3# = 3 > > myUndefined = undefined > > then this gives a sensible type error about a kind mismatch: > > usual :: Int > usual = g myUndefined > > but this, oddly enough, compiles: > > peculiar :: Int > peculiar = g undefined > > GHCi and the definition in GHC.Error agree that > > undefined :: a > > So why am I allowed to use it as a type of kind #? -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From david.feuer at gmail.com Sun Feb 1 19:38:00 2015 From: david.feuer at gmail.com (David Feuer) Date: Sun, 1 Feb 2015 14:38:00 -0500 Subject: What is the story behind the type of undefined? In-Reply-To: <54CE7983.6000104@well-typed.com> References: <54CE7983.6000104@well-typed.com> Message-ID: Yes it does. Thanks. For the sake of consistency, I'd rather even have separate functions with funny-looking types than hidden magic. That is, we could hypothetically have undefined# :: forall (a :: #) . a error# :: forall (a :: #) . String -> a There's no mechanism in Haskell to create things with such types, but at least that would make the strange types explicit. Of course, if someone can do something better, well, better is better. On Sun, Feb 1, 2015 at 2:07 PM, Adam Gundry wrote: > Hi David, > > See Note [Error and friends have an "open-tyvar" forall] in MkCore. The > short answer is that error and undefined are treated magically by GHC: > the actual type of undefined is > > forall (a :: OpenKind) . a > > and both * and # are subkinds of OpenKind. > > (There is a plan to get rid of this subkinding in favour of normal > polymorphism, but it hasn't been implemented yet. See > https://ghc.haskell.org/trac/ghc/wiki/NoSubKinds for more details.) > > Hope this helps, > > Adam > > > On 01/02/15 18:54, David Feuer wrote: >> If I define >> >> {-# LANGUAGE MagicHash #-} >> >> g :: Int# -> Int >> g 3# = 3 >> >> myUndefined = undefined >> >> then this gives a sensible type error about a kind mismatch: >> >> usual :: Int >> usual = g myUndefined >> >> but this, oddly enough, compiles: >> >> peculiar :: Int >> peculiar = g undefined >> >> GHCi and the definition in GHC.Error agree that >> >> undefined :: a >> >> So why am I allowed to use it as a type of kind #? > > > > -- > Adam Gundry, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ From eir at cis.upenn.edu Sun Feb 1 20:28:55 2015 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sun, 1 Feb 2015 15:28:55 -0500 Subject: What is the story behind the type of undefined? In-Reply-To: <54CE7983.6000104@well-typed.com> References: <54CE7983.6000104@well-typed.com> Message-ID: On Feb 1, 2015, at 2:07 PM, Adam Gundry wrote: > (There is a plan to get rid of this subkinding in favour of normal > polymorphism, but it hasn't been implemented yet. See > https://ghc.haskell.org/trac/ghc/wiki/NoSubKinds for more details.) The NoSubKinds plan *is* implemented, in my long-running branch. (It would be hard to implement in normal GHC, as there's an assumption that all kind variables have sort BOX, which NoSubKinds violates.) My branch doesn't have a mechanism for user-declared levity-polymorphic things, but that feature could easily be designed and added. Indeed, I believe user-availability is a goal of NoSubKinds. It just isn't on my critical path, so I didn't do it (yet). Richard From hvr at gnu.org Mon Feb 2 08:37:58 2015 From: hvr at gnu.org (Herbert Valerio Riedel) Date: Mon, 02 Feb 2015 09:37:58 +0100 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: (Mark Lentczner's message of "Tue, 27 Jan 2015 19:31:29 -0800") References: Message-ID: <87h9v4vhcp.fsf@gnu.org> Hi Mark, On 2015-01-28 at 04:31:29 +0100, Mark Lentczner wrote: > I've just built a bindist under 10.10, but just normal not expressly llvm. > I'll test this in a bit then post it -- but might be sometime tomorrow > before it is up. How's progress on this btw? Are you also working on a GHC 7.8.4 OSX bindist by any chance? Cheers, hvr From hesselink at gmail.com Mon Feb 2 10:58:57 2015 From: hesselink at gmail.com (Erik Hesselink) Date: Mon, 2 Feb 2015 11:58:57 +0100 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: <87h9v4vhcp.fsf@gnu.org> References: <87h9v4vhcp.fsf@gnu.org> Message-ID: On Mon, Feb 2, 2015 at 9:37 AM, Herbert Valerio Riedel wrote: > Hi Mark, > > On 2015-01-28 at 04:31:29 +0100, Mark Lentczner wrote: >> I've just built a bindist under 10.10, but just normal not expressly llvm. >> I'll test this in a bit then post it -- but might be sometime tomorrow >> before it is up. > > How's progress on this btw? Are you also working on a GHC 7.8.4 OSX > bindist by any chance? I made a bindist of RC2 (just like I did for RC1) which is here [1]. This was built on 10.9, without anything special for llvm. If anyone wants me to try something or produce a different build, please let me know. Erik [1] https://docs.google.com/a/silk.co/uc?id=0B5E6EvOcuE0nVmJ3WElQZW81b1U&export=download From simonpj at microsoft.com Mon Feb 2 14:16:49 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 2 Feb 2015 14:16:49 +0000 Subject: GHC support for the new "record" package In-Reply-To: References: <54BECC45.6010906@gmail.com> <54C21FBF.4020809@gmail.com> <54C2219D.2080103@well-typed.com> <54C2C5EE.9030100@well-typed.com> <618BE556AADD624C9C918AA5D5911BEF562B4C2D@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562B6EA9@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562B75B2@DB3PRD3001MB020.064d.mgd.msft.net> <54C7554D.9080104@well-typed.com> <54C7679C.2080708@well-typed.com> <618BE556AADD624C9C918AA5D5911BEF562B7EC9@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562B8C6F@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562BCBF9@DB3PRD3001MB020.064d.mgd.msft.net> In scala Julien Truffaut has a library called Monocle, which aspires to be a port of the ideas of lens to Scala. Due to the vagaries of the language the only option they have open to them is to implement things the way you are looking at exploring here. It doesn't work out well. Vastly more effort yields a library full of boilerplate that handles a much smaller scope and yields no insight into why these things are related. I dispute nothing that you say. But I don?t think a Scala failure should discourage us. Scala doesn?t let you abstract over higher kinds (or at least it?s very tricky because of variance); and I?m pretty sure it doesn?t let you abstract over constraints. I?m not saying that these are enough; just that it shouldn?t necessarily discourage us too much. On one point: Isomorphisms and prisms overload the shape to look more like p a (f b) -> p s (f t), rather than (a -> f b) -> s -> f t. Indexing, which matters for folding and traversing over containers with keys overloads with a shape like p a (f b) -> s -> f t So maybe we?d need newtype SuperLens c p q s t a b = SL (forall f. c f => p a (f b) -> q s (f t)) You may say that the SuperLens newtype it is ?dangling there?, and you might be right, but it remains something that can drive a type-class story. You may well be right; but I?d be very interested in an investigation that followed it through. (Dan?s observations about And are well taken.) Simon From: Edward Kmett [mailto:ekmett at gmail.com] Sent: 29 January 2015 03:52 To: Simon Peyton Jones Cc: Dan Doel; ghc-devs at haskell.org Subject: Re: GHC support for the new "record" package Alas, the 'f' isn't the only thing in the lens library signatures that gets overloaded in practice. By the time you reach that level of generality, and add type-changing, the newtype is sort of just dangling there actively getting in the way and providing no actual encapsulation. Now, you could make up a bunch of individual ad hoc data types for all the different lens types we happen to know about today. However, it is deeply insightful that it is the form that lenses take that let us _find_ all the different lens-likes that we use today. Half of them we had no idea were out there until we spent time exploring the impact of the design we have. Switching to a representation where these things arise from O(n^2) ad-hoc rules rather than the existing relationships between mostly "common sense" classes seems like a poor trade. In scala Julien Truffaut has a library called Monocle, which aspires to be a port of the ideas of lens to Scala. Due to the vagaries of the language the only option they have open to them is to implement things the way you are looking at exploring here. It doesn't work out well. Vastly more effort yields a library full of boilerplate that handles a much smaller scope and yields no insight into why these things are related. -Edward On Wed, Jan 28, 2015 at 5:32 AM, Simon Peyton Jones > wrote: As soon as you have a distinct Lens type, and use something Category-like for composition, you are limiting yourself to composing two lenses to get back a lens (barring a terrible mptc 'solution'). And that is weak. The only reason I (personally) think lens pulls its weight, and is worth using (unlike every prior lens library, which I never bothered with), is the ability for lenses, prisms, ismorphisms, traversals, folds, etc. to properly degrade to one another and compose automatically.? Aha. I keep asking whether it?s just the cute ability to re-use (.) that justifies the lack of abstraction in the Lens type. But Dan?s comment has made me remember something from my own talk on the subject. Here are the types of lenses and traversals (2-parameter versions): type Lens? s a = forall f. Functor f => (a -> f a) -> (s -> f s) type Traversal? s a = forall f. Applicative f => (a -> f a) -> (s -> f s) Suppose we have ln1 :: Lens' s1 s2 tr1 :: Traversal' s1 s2 ln2 :: Lens' s2 a tr2 :: Traversal' s2 a Now these compositions are all well typed ln1 . ln2 :: Lens' s1 a tr1 . tr2 :: Traversal' s1 a tr1 . ln2 :: Traversal' s1 a ln1 . tr2 :: Traversal' s1 a which is quite remarkable. If Lens? and Traversal? were newtypes, you?d need four different operators. (I think that what Dan means by ?a terrible mptc solution? is trying to overload those four operators into one.) I don?t know if this exhausts the reasons that lenses are not abstract. I would love to know more, explained in a smilar style. Incidentally has anyone explored this? newtype PolyLens c s a = PL (forall f. c f => (a -> f a) -> s -> f s) I?ve just abstracted over the Functor/Applicative part, so that Lens? and Traversal? are both PolyLenses. Now perhaps we can do (.), with a type like (.) :: PolyLens c1 s1 s2 -> PolyLens c2 s2 a -> PolyLens (And c1 c2) s1 a where And is a type function type instance And Functor Applicative = Applicative etc I have no idea whether this could be made to work out, but it seems like an obvious avenue so I wonder if anyone has explored it. Simon From: Dan Doel [mailto:dan.doel at gmail.com] Sent: 28 January 2015 00:27 To: Edward Kmett Cc: Simon Peyton Jones; ghc-devs at haskell.org Subject: Re: GHC support for the new "record" package On Tue, Jan 27, 2015 at 6:47 PM, Edward Kmett > wrote: This works great for lenses that don't let you change types. ?This is not the only restriction required for this to be an acceptable solution. As soon as you have a distinct Lens type, and use something Category-like for composition, you are limiting yourself to composing two lenses to get back a lens (barring a terrible mptc 'solution'). And that is weak. The only reason I (personally) think lens pulls its weight, and is worth using (unlike every prior lens library, which I never bothered with), is the ability for lenses, prisms, ismorphisms, traversals, folds, etc. to properly degrade to one another and compose automatically. So if we're settling on a nominal Lens type in a proposal, then it is automatically only good for one thing to me: defining values of the better lens type.? -- Dan -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Feb 2 17:33:33 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 2 Feb 2015 17:33:33 +0000 Subject: Restricted Template Haskell In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF562BD03C@DB3PRD3001MB020.064d.mgd.msft.net> The new TH is already split into two parts as I?m sure you know ? Typed TH is for expressions only, and doesn?t have reify, nor any Q monad. ? Untyped TH is the wild west Typed TH may get some of what you want? Certainly you want to acknowledge the existing split in your own design. The proposal could do with examples to illustrate what the difficulties are. What bad things happen in the Q monad? Can you give examples of reasoning that would be valid in level 1 but not in level 2. etc. More precision please! Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Greg Weber Sent: 30 January 2015 23:39 To: ghc-devs at haskell.org; GHC users Cc: David Terei; Maxwell Swadling Subject: Restricted Template Haskell Hello GHC friends! I am starting up a proposal for variants of Template Haskell that restrict what operations are available. The goal is to make TH easier for users to reason about and to allow for an easier compilation story. Here is the proposal page: https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Restricted Right now the proposal does not have any details and the goal is to write out a clear specification. If this sounds interesting to you, let me know or leave some feedback on the wiki. Thanks, Greg Weber -------------- next part -------------- An HTML attachment was scrubbed... URL: From greg at gregweber.info Mon Feb 2 19:31:06 2015 From: greg at gregweber.info (Greg Weber) Date: Mon, 2 Feb 2015 11:31:06 -0800 Subject: Restricted Template Haskell In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562BD03C@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562BD03C@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Hi Simon, I am just starting the proposal: gathering interested parties and pointers to related information. Thanks for the pointer to Typed Template Haskell. I was actually unaware of the extent to which Typed Template Haskell is restricted. I have not seen any usage of Typed Template Haskell in the wild or been able to use it myself unfortunately due to backwards compatibility needs (once the next GHC release is out libraries will start to consider dropping 7.6 support and we will see more usage, although Ubuntu still ships 7.6 by default). I will study Typed Template Haskell. Greg Weber On Mon, Feb 2, 2015 at 9:33 AM, Simon Peyton Jones wrote: > The new TH is already split into two parts > as > I?m sure you know > > ? Typed TH is for expressions only, and doesn?t have reify, nor > any Q monad. > > ? Untyped TH is the wild west > > > > Typed TH may get some of what you want? Certainly you want to > acknowledge the existing split in your own design. > > > > The proposal could do with examples to illustrate what the difficulties > are. What bad things happen in the Q monad? Can you give examples of > reasoning that would be valid in level 1 but not in level 2. etc. More > precision please! > > > > Simon > > > > *From:* Glasgow-haskell-users [mailto: > glasgow-haskell-users-bounces at haskell.org] *On Behalf Of *Greg Weber > *Sent:* 30 January 2015 23:39 > *To:* ghc-devs at haskell.org; GHC users > *Cc:* David Terei; Maxwell Swadling > *Subject:* Restricted Template Haskell > > > > Hello GHC friends! > > > > I am starting up a proposal for variants of Template Haskell that restrict > what operations are available. The goal is to make TH easier for users to > reason about and to allow for an easier compilation story. > > > > Here is the proposal page: > > https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Restricted > > > > Right now the proposal does not have any details and the goal is to write > out a clear specification. > > If this sounds interesting to you, let me know or leave some feedback on > the wiki. > > > > > > Thanks, > > Greg Weber > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From greg at gregweber.info Tue Feb 3 03:41:42 2015 From: greg at gregweber.info (Greg Weber) Date: Mon, 2 Feb 2015 19:41:42 -0800 Subject: Restricted Template Haskell In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562BD03C@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: I would like to figure out how to improve the state of TTH documentation. The GHC wiki is usually for things that are changing, and the page is written in that future style, so it makes one wonder if all things are finished or if some things remain unfinished. Some "this is how it is" documentation in the user guide would seem more useful now. But I am not sure if the user guide [1] is even correct because it indicates a type of `Q (TExp a)` where I would expect just `TExp a` from reading the wiki [2]. [1] https://downloads.haskell.org/~ghc/7.8.4/docs/html/users_guide/template-haskell.html [2] https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/BlogPostChanges On Mon, Feb 2, 2015 at 11:31 AM, Greg Weber wrote: > Hi Simon, > > I am just starting the proposal: gathering interested parties and pointers > to related information. > Thanks for the pointer to Typed Template Haskell. I was actually unaware > of the extent to which Typed Template Haskell is restricted. I have not > seen any usage of Typed Template Haskell in the wild or been able to use it > myself unfortunately due to backwards compatibility needs (once the next > GHC release is out libraries will start to consider dropping 7.6 support > and we will see more usage, although Ubuntu still ships 7.6 by default). > I will study Typed Template Haskell. > > Greg Weber > > On Mon, Feb 2, 2015 at 9:33 AM, Simon Peyton Jones > wrote: > >> The new TH is already split into two parts >> as >> I?m sure you know >> >> ? Typed TH is for expressions only, and doesn?t have reify, nor >> any Q monad. >> >> ? Untyped TH is the wild west >> >> >> >> Typed TH may get some of what you want? Certainly you want to >> acknowledge the existing split in your own design. >> >> >> >> The proposal could do with examples to illustrate what the difficulties >> are. What bad things happen in the Q monad? Can you give examples of >> reasoning that would be valid in level 1 but not in level 2. etc. More >> precision please! >> >> >> >> Simon >> >> >> >> *From:* Glasgow-haskell-users [mailto: >> glasgow-haskell-users-bounces at haskell.org] *On Behalf Of *Greg Weber >> *Sent:* 30 January 2015 23:39 >> *To:* ghc-devs at haskell.org; GHC users >> *Cc:* David Terei; Maxwell Swadling >> *Subject:* Restricted Template Haskell >> >> >> >> Hello GHC friends! >> >> >> >> I am starting up a proposal for variants of Template Haskell that >> restrict what operations are available. The goal is to make TH easier for >> users to reason about and to allow for an easier compilation story. >> >> >> >> Here is the proposal page: >> >> https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Restricted >> >> >> >> Right now the proposal does not have any details and the goal is to write >> out a clear specification. >> >> If this sounds interesting to you, let me know or leave some feedback on >> the wiki. >> >> >> >> >> >> Thanks, >> >> Greg Weber >> >> >> >> >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Feb 3 11:44:35 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 3 Feb 2015 11:44:35 +0000 Subject: Restricted Template Haskell In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562BD03C@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562BDD0A@DB3PRD3001MB020.064d.mgd.msft.net> Greg (and everyone else) The TH documentation is even more woeful than I realised. At the very least there should be a section for typed TH and a section for untyped TH in the manual. If I volunteer to write it, it won?t get done. I?m in too many inner loops. But here?s an offer: if someone (or a little group) is willing to play author, I will review and correct. It could be a good way to learn the details! Ideally it would be good to have a compact specification in the user manual, with more detail on the Haskell wiki (where it?s easier for people to edit/improve). For the latter there is already a page here. I?d really appreciate help with this. Simon From: Greg Weber [mailto:greg at gregweber.info] Sent: 03 February 2015 03:42 To: Simon Peyton Jones Cc: ghc-devs at haskell.org; GHC users; David Terei; Maxwell Swadling Subject: Re: Restricted Template Haskell I would like to figure out how to improve the state of TTH documentation. The GHC wiki is usually for things that are changing, and the page is written in that future style, so it makes one wonder if all things are finished or if some things remain unfinished. Some "this is how it is" documentation in the user guide would seem more useful now. But I am not sure if the user guide [1] is even correct because it indicates a type of `Q (TExp a)` where I would expect just `TExp a` from reading the wiki [2]. [1] https://downloads.haskell.org/~ghc/7.8.4/docs/html/users_guide/template-haskell.html [2] https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/BlogPostChanges On Mon, Feb 2, 2015 at 11:31 AM, Greg Weber > wrote: Hi Simon, I am just starting the proposal: gathering interested parties and pointers to related information. Thanks for the pointer to Typed Template Haskell. I was actually unaware of the extent to which Typed Template Haskell is restricted. I have not seen any usage of Typed Template Haskell in the wild or been able to use it myself unfortunately due to backwards compatibility needs (once the next GHC release is out libraries will start to consider dropping 7.6 support and we will see more usage, although Ubuntu still ships 7.6 by default). I will study Typed Template Haskell. Greg Weber On Mon, Feb 2, 2015 at 9:33 AM, Simon Peyton Jones > wrote: The new TH is already split into two parts as I?m sure you know ? Typed TH is for expressions only, and doesn?t have reify, nor any Q monad. ? Untyped TH is the wild west Typed TH may get some of what you want? Certainly you want to acknowledge the existing split in your own design. The proposal could do with examples to illustrate what the difficulties are. What bad things happen in the Q monad? Can you give examples of reasoning that would be valid in level 1 but not in level 2. etc. More precision please! Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Greg Weber Sent: 30 January 2015 23:39 To: ghc-devs at haskell.org; GHC users Cc: David Terei; Maxwell Swadling Subject: Restricted Template Haskell Hello GHC friends! I am starting up a proposal for variants of Template Haskell that restrict what operations are available. The goal is to make TH easier for users to reason about and to allow for an easier compilation story. Here is the proposal page: https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Restricted Right now the proposal does not have any details and the goal is to write out a clear specification. If this sounds interesting to you, let me know or leave some feedback on the wiki. Thanks, Greg Weber -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Feb 4 12:31:17 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 4 Feb 2015 12:31:17 +0000 Subject: [GHC] #10052: Panic (something to do with floatExpr?) In-Reply-To: <044.712619dfc86074dec5613c292886ee1f@haskell.org> References: <044.712619dfc86074dec5613c292886ee1f@haskell.org> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562BEB16@DB3PRD3001MB020.064d.mgd.msft.net> Peter: Here's a bad crash, due to you. (Doing this by email because I'm offline.) The (Tick t e) case of FloatOut.floatExpr is incomplete. It simply panics in some cases. Could you fix this please? Either that case shouldn't happen, in which case Core Lint should check for it, and whoever is generating it should be fixed. Or it should happen, in which case floatExpr should do the right thing. Could you leave a Note to explain what is happening in the floatExpr (Tick ...) cases? Thanks Simon | -----Original Message----- | From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On Behalf Of | GHC | Sent: 31 January 2015 17:38 | Cc: ghc-tickets at haskell.org | Subject: [GHC] #10052: Panic (something to do with floatExpr?) | | #10052: Panic (something to do with floatExpr?) | -------------------------------------+----------------------------------- | -- | Reporter: edsko | Owner: | Type: bug | Status: new | Priority: normal | Milestone: | Component: Compiler | Version: 7.10.1-rc2 | Keywords: | Operating System: | Unknown/Multiple | Architecture: | Type of failure: None/Unknown | Unknown/Multiple | Blocked By: | Test Case: | Related Tickets: | Blocking: | | Differential Revisions: | | -------------------------------------+----------------------------------- | -- | Loading | | {{{ | main = let (x :: String) = "hello" in putStrLn x | }}} | | using a very simple driver for the GHC API (see T145.hs) causes a ghc | panic: | | {{{ | [1 of 1] Compiling Main ( T145-input.hs, interpreted ) | T145: T145: panic! (the 'impossible' happened) | (GHC version 7.10.0.20150128 for x86_64-apple-darwin): | floatExpr tick | <
> | | Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug | }}} | | This panic is arising in our test case for #8333, so it may be related | to | that bug. | | -- | Ticket URL: | GHC | The Glasgow Haskell Compiler | _______________________________________________ | ghc-tickets mailing list | ghc-tickets at haskell.org | http://www.haskell.org/mailman/listinfo/ghc-tickets From scpmw at leeds.ac.uk Wed Feb 4 17:24:11 2015 From: scpmw at leeds.ac.uk (Peter Wortmann) Date: Wed, 04 Feb 2015 18:24:11 +0100 Subject: [GHC] #10052: Panic (something to do with floatExpr?) In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562BEB16@DB3PRD3001MB020.064d.mgd.msft.net> References: <044.712619dfc86074dec5613c292886ee1f@haskell.org> <618BE556AADD624C9C918AA5D5911BEF562BEB16@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: We are clearly trying to float past a breakpoint here, which is simply impossible. Pretty sure this would have been a panic before my changes too (it would have tried to "mkNoCount" the breakpoint). Guess I was wrong reading a "breakpoints don't appear here" invariant out of that... The quick fix would be to drop all floats in-place: -- scoped, counting and unsplittable, can't be floated through | otherwise = floatBody tOP_LEVEL expr This fixes the panic, but is a bit awkward. Probably better to change SetLevels? Not a piece of code I'm very familiar with... Greetings, Peter On 04/02/2015 13:31, Simon Peyton Jones wrote: > Peter: > > Here's a bad crash, due to you. (Doing this by email because I'm offline.) > > The (Tick t e) case of FloatOut.floatExpr is incomplete. It simply panics in some cases. > > Could you fix this please? Either that case shouldn't happen, in which case Core Lint should check for it, and whoever is generating it should be fixed. Or it should happen, in which case floatExpr should do the right thing. > > Could you leave a Note to explain what is happening in the floatExpr (Tick ...) cases? > > Thanks > > Simon > > | -----Original Message----- > | From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On Behalf Of > | GHC > | Sent: 31 January 2015 17:38 > | Cc: ghc-tickets at haskell.org > | Subject: [GHC] #10052: Panic (something to do with floatExpr?) > | > | #10052: Panic (something to do with floatExpr?) > | -------------------------------------+----------------------------------- > | -- > | Reporter: edsko | Owner: > | Type: bug | Status: new > | Priority: normal | Milestone: > | Component: Compiler | Version: 7.10.1-rc2 > | Keywords: | Operating System: > | Unknown/Multiple > | Architecture: | Type of failure: None/Unknown > | Unknown/Multiple | Blocked By: > | Test Case: | Related Tickets: > | Blocking: | > | Differential Revisions: | > | -------------------------------------+----------------------------------- > | -- > | Loading > | > | {{{ > | main = let (x :: String) = "hello" in putStrLn x > | }}} > | > | using a very simple driver for the GHC API (see T145.hs) causes a ghc > | panic: > | > | {{{ > | [1 of 1] Compiling Main ( T145-input.hs, interpreted ) > | T145: T145: panic! (the 'impossible' happened) > | (GHC version 7.10.0.20150128 for x86_64-apple-darwin): > | floatExpr tick > | <
> > | > | Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > | }}} > | > | This panic is arising in our test case for #8333, so it may be related > | to > | that bug. > | > | -- > | Ticket URL: > | GHC > | The Glasgow Haskell Compiler > | _______________________________________________ > | ghc-tickets mailing list > | ghc-tickets at haskell.org > | http://www.haskell.org/mailman/listinfo/ghc-tickets > From simonpj at microsoft.com Wed Feb 4 20:24:10 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 4 Feb 2015 20:24:10 +0000 Subject: Partial type sigs Message-ID: <618BE556AADD624C9C918AA5D5911BEF562BF102@DB3PRD3001MB020.064d.mgd.msft.net> Thomas I was looking at Trac #10045. I know exactly what is going on, but my investigation triggered several questions. 1. What is the state of the ToDos on https://ghc.haskell.org/trac/ghc/wiki/PartialTypeSignatures? 2. Is a named wildcard supposed to have any scope? For example: f :: _a -> b -> _a f x y = x :: _a The _a in the signature is not supposed to have any lexical scope over the binding is it? That would be entirely inconsistent with the treatment of ordinary type variables (such as 'b' in the example) which only scope if you have an explicit 'forall b'. Assuming the answer is "no" (and I really think it should be no), what is the call to tcExtendTyVarEnv2 tvsAndNcs doing in TcBinds.tcRhs? I'm pretty certain it bring into scope only the sig_tvs, and NOT the sig_nwcs. 3. If that is true, I think we may not need the sig_nwcs field of TcSigInfo at all. 4. A TcSigInfo has a sig_id field, which is intended to give the fixed, fully-known polymorphic type of the function. This is used: * for polymorphic recursion * as the type of the function to use in the body of the let, even if typechecking the function itself fails. Neither of these makes sense for partial type sigs. (And in fact, using sig_id for a partial type sig is what gives rise to #10045.) So I'm pretty convinced that we should replace sig_id and sig_partial with a single field sig_id :: Maybe Id, which is Nothing for partial sigs, and (Just ty) for total sigs. I wanted to check with you before blundering in and doing this. Or you could. RSVP Thanks Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Feb 5 10:45:45 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 5 Feb 2015 10:45:45 +0000 Subject: [GHC] #10052: Panic (something to do with floatExpr?) In-Reply-To: References: <044.712619dfc86074dec5613c292886ee1f@haskell.org> <618BE556AADD624C9C918AA5D5911BEF562BEB16@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562BF911@DB3PRD3001MB020.064d.mgd.msft.net> (Simon Marlow, can you help?) I don't understand how breakpoints work. Why do you say "we are clearly trying to float past a breakpoint"? Why is it so clear? Why is it wrong to float a lazy thunk out of a breakpoint? The float-out pass really doesn't have anywhere else where we say "you really can't float anything out of this subexpression, not even top-level constant expressions". Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Peter | Wortmann | Sent: 04 February 2015 17:24 | To: ghc-devs at haskell.org | Subject: Re: [GHC] #10052: Panic (something to do with floatExpr?) | | | | We are clearly trying to float past a breakpoint here, which is simply | impossible. Pretty sure this would have been a panic before my changes | too (it would have tried to "mkNoCount" the breakpoint). Guess I was | wrong reading a "breakpoints don't appear here" invariant out of that... | | The quick fix would be to drop all floats in-place: | | -- scoped, counting and unsplittable, can't be floated through | | otherwise | = floatBody tOP_LEVEL expr | | This fixes the panic, but is a bit awkward. Probably better to change | SetLevels? Not a piece of code I'm very familiar with... | | Greetings, | Peter | | On 04/02/2015 13:31, Simon Peyton Jones wrote: | > Peter: | > | > Here's a bad crash, due to you. (Doing this by email because I'm | offline.) | > | > The (Tick t e) case of FloatOut.floatExpr is incomplete. It simply | panics in some cases. | > | > Could you fix this please? Either that case shouldn't happen, in which | case Core Lint should check for it, and whoever is generating it should | be fixed. Or it should happen, in which case floatExpr should do the | right thing. | > | > Could you leave a Note to explain what is happening in the floatExpr | (Tick ...) cases? | > | > Thanks | > | > Simon | > | > | -----Original Message----- | > | From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On Behalf | Of | > | GHC | > | Sent: 31 January 2015 17:38 | > | Cc: ghc-tickets at haskell.org | > | Subject: [GHC] #10052: Panic (something to do with floatExpr?) | > | | > | #10052: Panic (something to do with floatExpr?) | > | -------------------------------------+------------------------------- | ---- | > | -- | > | Reporter: edsko | Owner: | > | Type: bug | Status: new | > | Priority: normal | Milestone: | > | Component: Compiler | Version: 7.10.1-rc2 | > | Keywords: | Operating System: | > | Unknown/Multiple | > | Architecture: | Type of failure: | None/Unknown | > | Unknown/Multiple | Blocked By: | > | Test Case: | Related Tickets: | > | Blocking: | | > | Differential Revisions: | | > | -------------------------------------+------------------------------- | ---- | > | -- | > | Loading | > | | > | {{{ | > | main = let (x :: String) = "hello" in putStrLn x | > | }}} | > | | > | using a very simple driver for the GHC API (see T145.hs) causes a | ghc | > | panic: | > | | > | {{{ | > | [1 of 1] Compiling Main ( T145-input.hs, interpreted ) | > | T145: T145: panic! (the 'impossible' happened) | > | (GHC version 7.10.0.20150128 for x86_64-apple-darwin): | > | floatExpr tick | > | <
> | > | | > | Please report this as a GHC bug: | http://www.haskell.org/ghc/reportabug | > | }}} | > | | > | This panic is arising in our test case for #8333, so it may be | related | > | to | > | that bug. | > | | > | -- | > | Ticket URL: | > | GHC | > | The Glasgow Haskell Compiler | > | _______________________________________________ | > | ghc-tickets mailing list | > | ghc-tickets at haskell.org | > | http://www.haskell.org/mailman/listinfo/ghc-tickets | > | | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs From thomas.winant at cs.kuleuven.be Thu Feb 5 10:50:57 2015 From: thomas.winant at cs.kuleuven.be (Thomas Winant) Date: Thu, 05 Feb 2015 11:50:57 +0100 Subject: Partial type sigs In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562BF102@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562BF102@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <54D34B11.2010007@cs.kuleuven.be> On 02/04/2015 09:24 PM, Simon Peyton Jones wrote: > > Thomas > > I was looking at Trac #10045 > . I know exactly what > is going on, but my investigation triggered several questions. > I'll have a look too, but first my answers to your questions: > 1.What is the state of the ToDos on > https://ghc.haskell.org/trac/ghc/wiki/PartialTypeSignatures > ? > I've updated the TODOs on the wiki page, but I'll summarise the changes: * I've updated the user manual. * I have fixed a TODO in the code, see: http://ghc.haskell.org/trac/ghc/changeset/d108a19cf6cd802c30ff1fa2758dd6aa8c049ad0/ghc * You fixed the panic for TODO 1 (see link below), but we still don't get the error messages we (or I would) want when we change the type of the local binding to `_`. http://ghc.haskell.org/trac/ghc/changeset/28299d6827b334f5337bf5931124abc1e534f33f/ghc > 2.Is a named wildcard supposed to have any scope? For example: > > f :: _a -> b -> _a > > f x y = x :: _a > > The _a in the signature is not supposed to have any lexical scope over > the binding is it? That would be entirely inconsistent with the > treatment of ordinary type variables (such as ?b? in the example) > which only scope if you have an explicit ?forall b?. > > Assuming the answer is ?no? (and I really think it should be no), what > is the call to tcExtendTyVarEnv2 tvsAndNcs doing in TcBinds.tcRhs? > I?m pretty certain it bring into scope only the sig_tvs, and NOT the > sig_nwcs. > > 3.If that is true, I think we may not need the sig_nwcs field of > TcSigInfo at all. > Named wildcards follow the scoping behaviour of ScopedTypeVariables but without the forall. See the following example: {-# LANGUAGE PartialTypeSignatures, NamedWildCards #-} {-# OPTIONS_GHC -fno-warn-partial-type-signatures #-} module Scope where f :: _a -> _b -> _a f x y = x :: _b -- Note that this is not your example $ ghc -ddump-types > TYPE SIGNATURES > f :: forall w_a w_b. w_a -> w_b -> w_a > ... $ ghc -ddump-types -XScopedTypeVariables > TYPE SIGNATURES > f :: forall w_a. w_a -> w_a -> w_a > .. With scoped named wildcards, the second _b (with type _a) must be the same as the first _b and thus _b ~ _a, hence no w_b. That's why there is a call to tcExpandTyVarEnv2 in TcBinds.tcRhs and why we need the sig_nwcs field of TcSigInfo. > 4.A TcSigInfo has a sig_id field, which is intended to give the fixed, > fully-known polymorphic type of the function. This is used: > > ?for polymorphic recursion > > ?as the type of the function to use in the body of the let, even if > typechecking the function itself fails. > > Neither of these makes sense for partial type sigs. (And in fact, > using sig_id for a partial type sig is what gives rise to #10045.) So > I?m pretty convinced that we should replace sig_id and sig_partial > with a single field sig_id :: Maybe Id, which is Nothing for partial > sigs, and (Just ty) for total sigs. > What you say makes sense, but don't we already do something with the same effect (see link)? We only add monomorphic Ids of non-partial type signatures. Or am I missing something? http://git.haskell.org/ghc.git/blob/HEAD:/compiler/typecheck/TcBinds.hs#l1306 > I wanted to check with you before blundering in and doing this. Or > you could. > > RSVP > > Thanks > > Simon > Cheers, Thomas Disclaimer: http://www.kuleuven.be/cwis/email_disclaimer.htm -------------- next part -------------- An HTML attachment was scrubbed... URL: From scpmw at leeds.ac.uk Thu Feb 5 11:46:32 2015 From: scpmw at leeds.ac.uk (Peter Wortmann) Date: Thu, 05 Feb 2015 12:46:32 +0100 Subject: [GHC] #10052: Panic (something to do with floatExpr?) In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562BF911@DB3PRD3001MB020.064d.mgd.msft.net> References: <044.712619dfc86074dec5613c292886ee1f@haskell.org> <618BE556AADD624C9C918AA5D5911BEF562BEB16@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562BF911@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <54D35818.6090101@leeds.ac.uk> Simon Peyton Jones wrote: > Why do you say "we are clearly trying to float past a breakpoint"? Why is it so clear? It's the only kind of Tickish that is scoped, counting and not splittable. This means that we can't a) Simply float code out of it, because the payload must still be covered (scoped) b) Copy the tick, because it would change entry counts (here: duplicate breakpoints) > Why is it wrong to float a lazy thunk out of a breakpoint? Good questions - I haven't given breakpoint semantics a lot of thought, to be honest. My assumption was that most optimisation passes would never see them. And where they did, they should just leave them in peace as much as possible. For whatever it's worth, the source cautions against making breakpoints unscoped: -- Breakpoints are scoped: eventually we're going to do call -- stacks, but also this helps prevent the simplifier from moving -- breakpoints around and changing their result type (see #1531). Hm. We might try to make them pseudo-splittable, with non-counting breakpoints being NOPs for now? This might still allow us to implement breakpoint-based stack traces if we really want them... Greetings, Peter > Simon > > | -----Original Message----- > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Peter > | Wortmann > | Sent: 04 February 2015 17:24 > | To: ghc-devs at haskell.org > | Subject: Re: [GHC] #10052: Panic (something to do with floatExpr?) > | > | > | > | We are clearly trying to float past a breakpoint here, which is simply > | impossible. Pretty sure this would have been a panic before my changes > | too (it would have tried to "mkNoCount" the breakpoint). Guess I was > | wrong reading a "breakpoints don't appear here" invariant out of that... > | > | The quick fix would be to drop all floats in-place: > | > | -- scoped, counting and unsplittable, can't be floated through > | | otherwise > | = floatBody tOP_LEVEL expr > | > | This fixes the panic, but is a bit awkward. Probably better to change > | SetLevels? Not a piece of code I'm very familiar with... > | > | Greetings, > | Peter > | > | On 04/02/2015 13:31, Simon Peyton Jones wrote: > | > Peter: > | > > | > Here's a bad crash, due to you. (Doing this by email because I'm > | offline.) > | > > | > The (Tick t e) case of FloatOut.floatExpr is incomplete. It simply > | panics in some cases. > | > > | > Could you fix this please? Either that case shouldn't happen, in which > | case Core Lint should check for it, and whoever is generating it should > | be fixed. Or it should happen, in which case floatExpr should do the > | right thing. > | > > | > Could you leave a Note to explain what is happening in the floatExpr > | (Tick ...) cases? > | > > | > Thanks > | > > | > Simon > | > > | > | -----Original Message----- > | > | From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On Behalf > | Of > | > | GHC > | > | Sent: 31 January 2015 17:38 > | > | Cc: ghc-tickets at haskell.org > | > | Subject: [GHC] #10052: Panic (something to do with floatExpr?) > | > | > | > | #10052: Panic (something to do with floatExpr?) > | > | -------------------------------------+------------------------------- > | ---- > | > | -- > | > | Reporter: edsko | Owner: > | > | Type: bug | Status: new > | > | Priority: normal | Milestone: > | > | Component: Compiler | Version: 7.10.1-rc2 > | > | Keywords: | Operating System: > | > | Unknown/Multiple > | > | Architecture: | Type of failure: > | None/Unknown > | > | Unknown/Multiple | Blocked By: > | > | Test Case: | Related Tickets: > | > | Blocking: | > | > | Differential Revisions: | > | > | -------------------------------------+------------------------------- > | ---- > | > | -- > | > | Loading > | > | > | > | {{{ > | > | main = let (x :: String) = "hello" in putStrLn x > | > | }}} > | > | > | > | using a very simple driver for the GHC API (see T145.hs) causes a > | ghc > | > | panic: > | > | > | > | {{{ > | > | [1 of 1] Compiling Main ( T145-input.hs, interpreted ) > | > | T145: T145: panic! (the 'impossible' happened) > | > | (GHC version 7.10.0.20150128 for x86_64-apple-darwin): > | > | floatExpr tick > | > | <
> > | > | > | > | Please report this as a GHC bug: > | http://www.haskell.org/ghc/reportabug > | > | }}} > | > | > | > | This panic is arising in our test case for #8333, so it may be > | related > | > | to > | > | that bug. > | > | > | > | -- > | > | Ticket URL: > | > | GHC > | > | The Glasgow Haskell Compiler > | > | _______________________________________________ > | > | ghc-tickets mailing list > | > | ghc-tickets at haskell.org > | > | http://www.haskell.org/mailman/listinfo/ghc-tickets > | > > | > | _______________________________________________ > | ghc-devs mailing list > | ghc-devs at haskell.org > | http://www.haskell.org/mailman/listinfo/ghc-devs From merijn at inconsistent.nl Thu Feb 5 14:45:32 2015 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Thu, 5 Feb 2015 15:45:32 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion Message-ID: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> I've been repeatedly running into problems with overloaded literals and partial conversion functions, so I wrote up an initial proposal (https://ghc.haskell.org/trac/ghc/wiki/ValidateMonoLiterals) and I'd like to commence with the bikeshedding and hearing other opinions :) Cheers, Merijn -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From simonpj at microsoft.com Thu Feb 5 16:44:21 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 5 Feb 2015 16:44:21 +0000 Subject: [GHC] #10052: Panic (something to do with floatExpr?) In-Reply-To: <54D35818.6090101@leeds.ac.uk> References: <044.712619dfc86074dec5613c292886ee1f@haskell.org> <618BE556AADD624C9C918AA5D5911BEF562BEB16@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562BF911@DB3PRD3001MB020.064d.mgd.msft.net> <54D35818.6090101@leeds.ac.uk> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C007B@DB3PRD3001MB020.064d.mgd.msft.net> Peter, OK. This is really beyond my knowledge. Might you and Simon be able to work out something together? I can advise on FloatOut if necessary. Simon | -----Original Message----- | From: Peter Wortmann [mailto:scpmw at leeds.ac.uk] | Sent: 05 February 2015 11:47 | To: Simon Peyton Jones; Simon Marlow | Cc: ghc-devs at haskell.org | Subject: Re: [GHC] #10052: Panic (something to do with floatExpr?) | | | | Simon Peyton Jones wrote: | > Why do you say "we are clearly trying to float past a breakpoint"? Why | is it so clear? | | It's the only kind of Tickish that is scoped, counting and not | splittable. | | This means that we can't | | a) Simply float code out of it, because the payload must still be | covered (scoped) | | b) Copy the tick, because it would change entry counts (here: duplicate | breakpoints) | | > Why is it wrong to float a lazy thunk out of a breakpoint? | | Good questions - I haven't given breakpoint semantics a lot of thought, | to be honest. My assumption was that most optimisation passes would | never see them. And where they did, they should just leave them in peace | as much as possible. | | For whatever it's worth, the source cautions against making breakpoints | unscoped: | | -- Breakpoints are scoped: eventually we're going to do call | -- stacks, but also this helps prevent the simplifier from moving | -- breakpoints around and changing their result type (see #1531). | | Hm. We might try to make them pseudo-splittable, with non-counting | breakpoints being NOPs for now? This might still allow us to implement | breakpoint-based stack traces if we really want them... | | Greetings, | Peter | | > Simon | > | > | -----Original Message----- | > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of | Peter | > | Wortmann | > | Sent: 04 February 2015 17:24 | > | To: ghc-devs at haskell.org | > | Subject: Re: [GHC] #10052: Panic (something to do with floatExpr?) | > | | > | | > | | > | We are clearly trying to float past a breakpoint here, which is | simply | > | impossible. Pretty sure this would have been a panic before my | changes | > | too (it would have tried to "mkNoCount" the breakpoint). Guess I was | > | wrong reading a "breakpoints don't appear here" invariant out of | that... | > | | > | The quick fix would be to drop all floats in-place: | > | | > | -- scoped, counting and unsplittable, can't be floated through | > | | otherwise | > | = floatBody tOP_LEVEL expr | > | | > | This fixes the panic, but is a bit awkward. Probably better to change | > | SetLevels? Not a piece of code I'm very familiar with... | > | | > | Greetings, | > | Peter | > | | > | On 04/02/2015 13:31, Simon Peyton Jones wrote: | > | > Peter: | > | > | > | > Here's a bad crash, due to you. (Doing this by email because I'm | > | offline.) | > | > | > | > The (Tick t e) case of FloatOut.floatExpr is incomplete. It simply | > | panics in some cases. | > | > | > | > Could you fix this please? Either that case shouldn't happen, in | which | > | case Core Lint should check for it, and whoever is generating it | should | > | be fixed. Or it should happen, in which case floatExpr should do the | > | right thing. | > | > | > | > Could you leave a Note to explain what is happening in the | floatExpr | > | (Tick ...) cases? | > | > | > | > Thanks | > | > | > | > Simon | > | > | > | > | -----Original Message----- | > | > | From: ghc-tickets [mailto:ghc-tickets-bounces at haskell.org] On | Behalf | > | Of | > | > | GHC | > | > | Sent: 31 January 2015 17:38 | > | > | Cc: ghc-tickets at haskell.org | > | > | Subject: [GHC] #10052: Panic (something to do with floatExpr?) | > | > | | > | > | #10052: Panic (something to do with floatExpr?) | > | > | -------------------------------------+--------------------------- | ---- | > | ---- | > | > | -- | > | > | Reporter: edsko | Owner: | > | > | Type: bug | Status: new | > | > | Priority: normal | Milestone: | > | > | Component: Compiler | Version: | 7.10.1-rc2 | > | > | Keywords: | Operating System: | > | > | Unknown/Multiple | > | > | Architecture: | Type of failure: | > | None/Unknown | > | > | Unknown/Multiple | Blocked By: | > | > | Test Case: | Related Tickets: | > | > | Blocking: | | > | > | Differential Revisions: | | > | > | -------------------------------------+--------------------------- | ---- | > | ---- | > | > | -- | > | > | Loading | > | > | | > | > | {{{ | > | > | main = let (x :: String) = "hello" in putStrLn x | > | > | }}} | > | > | | > | > | using a very simple driver for the GHC API (see T145.hs) causes | a | > | ghc | > | > | panic: | > | > | | > | > | {{{ | > | > | [1 of 1] Compiling Main ( T145-input.hs, interpreted | ) | > | > | T145: T145: panic! (the 'impossible' happened) | > | > | (GHC version 7.10.0.20150128 for x86_64-apple-darwin): | > | > | floatExpr tick | > | > | <
> | > | > | | > | > | Please report this as a GHC bug: | > | http://www.haskell.org/ghc/reportabug | > | > | }}} | > | > | | > | > | This panic is arising in our test case for #8333, so it may be | > | related | > | > | to | > | > | that bug. | > | > | | > | > | -- | > | > | Ticket URL: | > | > | GHC | > | > | The Glasgow Haskell Compiler | > | > | _______________________________________________ | > | > | ghc-tickets mailing list | > | > | ghc-tickets at haskell.org | > | > | http://www.haskell.org/mailman/listinfo/ghc-tickets | > | > | > | | > | _______________________________________________ | > | ghc-devs mailing list | > | ghc-devs at haskell.org | > | http://www.haskell.org/mailman/listinfo/ghc-devs From simonpj at microsoft.com Thu Feb 5 16:44:23 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 5 Feb 2015 16:44:23 +0000 Subject: Partial type sigs In-Reply-To: <54D34B11.2010007@cs.kuleuven.be> References: <618BE556AADD624C9C918AA5D5911BEF562BF102@DB3PRD3001MB020.064d.mgd.msft.net> <54D34B11.2010007@cs.kuleuven.be> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C00D7@DB3PRD3001MB020.064d.mgd.msft.net> Named wildcards follow the scoping behaviour of ScopedTypeVariables but without the forall. See the following example: {-# LANGUAGE PartialTypeSignatures, NamedWildCards #-} {-# OPTIONS_GHC -fno-warn-partial-type-signatures #-} module Scope where f :: _a -> _b -> _a f x y = x :: _b I really don't like this behaviour! 1. It is entirely undocumented, in the manual or the wiki page, I think. 2. it is inconsistent with the lexical scoping rules for ordinary scoped type variables. 3. It interferes with generalisation. For (3), consider let f :: _a -> _a f xs = reverse xs in (f True, f 'x') Here, f gets the type f :: forall b. [b] -> [b], and _a is unifed with [b]. So it simply doesn't make sense for _a to appear in the body. What would it mean to say let f :: _a -> _a f xs = reverse xs in (f (True :: _a), f 'x') Does this mean we *shouldn't* generalise as we usually would? I think of a partial signature as perhaps constraining the shape of the type a bit, but not affecting generalisation. It would be hard to predict exactly how it was supposed to affect generalisation.... e.g. .what if _a in the above example did not, after all, appear in the body of the let? I urge (strongly) that we back off from this and say that named wildcards scope only over the type signature in which they appear. OK? The implementation gets simpler too. RSVP. What you say makes sense, but don't we already do something with the same effect (see link)? We only add monomorphic Ids of non-partial type signatures. Or am I missing something? http://git.haskell.org/ghc.git/blob/HEAD:/compiler/typecheck/TcBinds.hs#l1306 That's true, but we also (wrongly) bring the polymorphic Id into scope (TcBinds line 313). We should only do that for full (not partial) type sigs. But my point is that the sig_id field never makes sense of sig_partial is true. (Correct?) So we should rule it out structurally (via the Maybe) rather than rely on an unstated invariant. Simon From: Thomas Winant [mailto:thomas.winant at cs.kuleuven.be] Sent: 05 February 2015 10:51 To: Simon Peyton Jones Cc: ghc-devs at haskell.org; Dominique Devriese; Frank Piessens Subject: Re: Partial type sigs On 02/04/2015 09:24 PM, Simon Peyton Jones wrote: Thomas I was looking at Trac #10045. I know exactly what is going on, but my investigation triggered several questions. I'll have a look too, but first my answers to your questions: 1. What is the state of the ToDos on https://ghc.haskell.org/trac/ghc/wiki/PartialTypeSignatures? I've updated the TODOs on the wiki page, but I'll summarise the changes: * I've updated the user manual. * I have fixed a TODO in the code, see: http://ghc.haskell.org/trac/ghc/changeset/d108a19cf6cd802c30ff1fa2758dd6aa8c049ad0/ghc * You fixed the panic for TODO 1 (see link below), but we still don't get the error messages we (or I would) want when we change the type of the local binding to `_`. http://ghc.haskell.org/trac/ghc/changeset/28299d6827b334f5337bf5931124abc1e534f33f/ghc 2. Is a named wildcard supposed to have any scope? For example: f :: _a -> b -> _a f x y = x :: _a The _a in the signature is not supposed to have any lexical scope over the binding is it? That would be entirely inconsistent with the treatment of ordinary type variables (such as 'b' in the example) which only scope if you have an explicit 'forall b'. Assuming the answer is "no" (and I really think it should be no), what is the call to tcExtendTyVarEnv2 tvsAndNcs doing in TcBinds.tcRhs? I'm pretty certain it bring into scope only the sig_tvs, and NOT the sig_nwcs. 3. If that is true, I think we may not need the sig_nwcs field of TcSigInfo at all. Named wildcards follow the scoping behaviour of ScopedTypeVariables but without the forall. See the following example: {-# LANGUAGE PartialTypeSignatures, NamedWildCards #-} {-# OPTIONS_GHC -fno-warn-partial-type-signatures #-} module Scope where f :: _a -> _b -> _a f x y = x :: _b -- Note that this is not your example $ ghc -ddump-types > TYPE SIGNATURES > f :: forall w_a w_b. w_a -> w_b -> w_a > ... $ ghc -ddump-types -XScopedTypeVariables > TYPE SIGNATURES > f :: forall w_a. w_a -> w_a -> w_a > .. With scoped named wildcards, the second _b (with type _a) must be the same as the first _b and thus _b ~ _a, hence no w_b. That's why there is a call to tcExpandTyVarEnv2 in TcBinds.tcRhs and why we need the sig_nwcs field of TcSigInfo. 4. A TcSigInfo has a sig_id field, which is intended to give the fixed, fully-known polymorphic type of the function. This is used: * for polymorphic recursion * as the type of the function to use in the body of the let, even if typechecking the function itself fails. Neither of these makes sense for partial type sigs. (And in fact, using sig_id for a partial type sig is what gives rise to #10045.) So I'm pretty convinced that we should replace sig_id and sig_partial with a single field sig_id :: Maybe Id, which is Nothing for partial sigs, and (Just ty) for total sigs. What you say makes sense, but don't we already do something with the same effect (see link)? We only add monomorphic Ids of non-partial type signatures. Or am I missing something? http://git.haskell.org/ghc.git/blob/HEAD:/compiler/typecheck/TcBinds.hs#l1306 I wanted to check with you before blundering in and doing this. Or you could. RSVP Thanks Simon Cheers, Thomas Disclaimer: http://www.kuleuven.be/cwis/email_disclaimer.htm for more information. -------------- next part -------------- An HTML attachment was scrubbed... URL: From dominique.devriese at cs.kuleuven.be Thu Feb 5 20:12:34 2015 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Thu, 5 Feb 2015 21:12:34 +0100 Subject: Partial type sigs In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C00D7@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562BF102@DB3PRD3001MB020.064d.mgd.msft.net> <54D34B11.2010007@cs.kuleuven.be> <618BE556AADD624C9C918AA5D5911BEF562C00D7@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Simon, 2015-02-05 17:44 GMT+01:00 Simon Peyton Jones : > 3. It interferes with generalisation. > > For (3), consider > > let f :: _a -> _a > > f xs = reverse xs > > in (f True, f ?x?) > > Here, f gets the type f :: forall b. [b] -> [b], and _a is unifed with [b]. > > So it simply doesn?t make sense for _a to appear in the body. What would it > mean to say > > let f :: _a -> _a > > f xs = reverse xs > > in (f (True :: _a), f ?x?) Isn't this a different case than Thomas' example? As I understand it, an equivalent of his example would have the wildcard in scope in the body of f, not in the body of the let. Something like this: let f :: _a -> _a f xs = reverse (xs :: _a) in (f [True], f "x") or let f :: _a -> _a f xs = let ys :: _a ys = tail xs in reverse ys in (f [True], f "x") I agree with what you say about _a being in scope in the body of the if, but I don't see a problem with _a being in scope in the body of f. Do you? Note also that I haven't yet checked which of both is actually implemented. Regards, Dominique From simonpj at microsoft.com Thu Feb 5 21:30:10 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 5 Feb 2015 21:30:10 +0000 Subject: Partial type sigs In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562BF102@DB3PRD3001MB020.064d.mgd.msft.net> <54D34B11.2010007@cs.kuleuven.be> <618BE556AADD624C9C918AA5D5911BEF562C00D7@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C0376@DB3PRD3001MB020.064d.mgd.msft.net> Oh gosh you are absolutely right. Ordinary, lexically scoped type variables only scope over the RHS of the relevant binding, not the body of the let. I was completely wrong about that. In which case my objection is much milder: - the inconsistency of treatment wrt ordinary type variables (which require a forall; and yes, you can't give a forall for wildcards) - the lack of documentation The system would be simpler without this. So, is it really important? If so, we could add it later. Sorry to make such a misleading post. Simon | -----Original Message----- | From: dominique.devriese at gmail.com [mailto:dominique.devriese at gmail.com] | On Behalf Of Dominique Devriese | Sent: 05 February 2015 20:13 | To: Simon Peyton Jones | Cc: Thomas Winant; ghc-devs at haskell.org; Frank Piessens | Subject: Re: Partial type sigs | | Simon, | | 2015-02-05 17:44 GMT+01:00 Simon Peyton Jones : | > 3. It interferes with generalisation. | > | > For (3), consider | > | > let f :: _a -> _a | > | > f xs = reverse xs | > | > in (f True, f ?x?) | > | > Here, f gets the type f :: forall b. [b] -> [b], and _a is unifed with | [b]. | > | > So it simply doesn?t make sense for _a to appear in the body. What | would it | > mean to say | > | > let f :: _a -> _a | > | > f xs = reverse xs | > | > in (f (True :: _a), f ?x?) | | Isn't this a different case than Thomas' example? As I understand it, | an equivalent of his example would have the wildcard in scope in the | body of f, not in the body of the let. Something like this: | | let f :: _a -> _a | f xs = reverse (xs :: _a) | in (f [True], f "x") | | or | | let f :: _a -> _a | f xs = let ys :: _a | ys = tail xs | in reverse ys | in (f [True], f "x") | | I agree with what you say about _a being in scope in the body of the | if, but I don't see a problem with _a being in scope in the body of f. | Do you? | | Note also that I haven't yet checked which of both is actually | implemented. | | Regards, | Dominique From simonpj at microsoft.com Thu Feb 5 21:48:13 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 5 Feb 2015 21:48:13 +0000 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> I'm all for it. Syntax sounds like the main difficulty. Today you could use quasiquotatoin [even| 38 |] and get the same effect as $$(validate 38). But it's still noisy. So: what is the non-noisy scheme you want to propose? You don't quite get to that in the wiki page! Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Merijn | Verstraaten | Sent: 05 February 2015 14:46 | To: ghc-devs at haskell.org; GHC users | Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion | | I've been repeatedly running into problems with overloaded literals and | partial conversion functions, so I wrote up an initial proposal | (https://ghc.haskell.org/trac/ghc/wiki/ValidateMonoLiterals) and I'd like | to commence with the bikeshedding and hearing other opinions :) | | Cheers, | Merijn From david.feuer at gmail.com Fri Feb 6 06:05:35 2015 From: david.feuer at gmail.com (David Feuer) Date: Fri, 6 Feb 2015 01:05:35 -0500 Subject: Merge FlexibleContexts with FlexibleInstances? Message-ID: In my limited experience thus far, it seems to me that a substantial majority of modules that start out needing one of these end up needing the other one too. They appear to be two sides of the same coin, each allowing for (slightly) more powerful termination checking. Should the two just be made synonyms, to cut down a tiny bit on the boilerplate LANGUAGE pragmas? -------------- next part -------------- An HTML attachment was scrubbed... URL: From hvriedel at gmail.com Fri Feb 6 07:48:58 2015 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Fri, 06 Feb 2015 08:48:58 +0100 Subject: Merge FlexibleContexts with FlexibleInstances? In-Reply-To: (David Feuer's message of "Fri, 6 Feb 2015 01:05:35 -0500") References: Message-ID: <87386j8oph.fsf@gmail.com> On 2015-02-06 at 07:05:35 +0100, David Feuer wrote: > In my limited experience thus far, it seems to me that a substantial > majority of modules that start out needing one of these end up needing the > other one too. They appear to be two sides of the same coin, each allowing > for (slightly) more powerful termination checking. Should the two just be > made synonyms, to cut down a tiny bit on the boilerplate LANGUAGE pragmas? Otoh, FlexibleInstances is only needed if you define instances, while FlexibleContexts can also be required with code not defining any instances (and GHC 7.10 requires FlexibleContexts more often now for inferred type-signatures which couldn't be written w/o FlexibleContexts) Cheers, hvr From Thomas.Winant at cs.kuleuven.be Fri Feb 6 09:34:23 2015 From: Thomas.Winant at cs.kuleuven.be (Thomas Winant) Date: Fri, 06 Feb 2015 10:34:23 +0100 Subject: Partial type sigs In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C0376@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562BF102@DB3PRD3001MB020.064d.mgd.msft.net> <54D34B11.2010007@cs.kuleuven.be> <618BE556AADD624C9C918AA5D5911BEF562C00D7@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C0376@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: What Dominique said is right, and it is also the way it is actually implemented. On 2015-02-05 22:30, Simon Peyton Jones wrote: > Oh gosh you are absolutely right. Ordinary, lexically scoped type > variables only scope over the RHS of the relevant binding, not the > body of the let. I was completely wrong about that. > > In which case my objection is much milder: > - the inconsistency of treatment wrt ordinary type variables > (which require a forall; and yes, you can't give a forall for > wildcards) True. It is understandable that is surprising that enabling an extension that doesn't have wildcards (or anything similar) in its name affects the behaviour of wildcards. > - the lack of documentation I will take care of this. It is already on the wiki page, but it is indeed missing from the user manual. > The system would be simpler without this. So, is it really important? > If so, we could add it later. I'm not so sure it would make things much simpler. Wildcards still need to be stored in the TcSigInfo because we need to emit insoluble hole constraints for them. We wouldn't need to bring them in scope or check whether they're already in scope in a couple of places, but to me, that doesn't seem like a good reason. If we were to remove this behaviour, and add it back later, I suppose something would have to be changed by then, but what? A forall-construct for wildcards? I do believe this behaviour is useful, we would lose expressiveness if we were to remove it. Note that we don't have the same problem with backwards compatibility that ScopedTypeVariables had, that requires the user to explicitly indicate with a forall which type variables to lexically scope to avoid breaking existing programs. We might as well make named wildcards lexically scoped by default, not even opt-out (as was the case in my initial proposal). About using a Maybe for sig_id to fix 10045: I tried it out, and your solution does indeed fix it. In order for TcSigInfo to still implement NamedThing, I used an 'Either Name TcId' instead of a 'Maybe TcId'. Do you prefer a separate data type for this instead of an Either? (Please come up with a good name for it in that case :) Unfortunately, some of my tests started failing, so I'll post something on Phabricator as soon as I have worked out the kinks. Cheers, Thomas > Sorry to make such a misleading post. > > Simon > > | -----Original Message----- > | From: dominique.devriese at gmail.com > [mailto:dominique.devriese at gmail.com] > | On Behalf Of Dominique Devriese > | Sent: 05 February 2015 20:13 > | To: Simon Peyton Jones > | Cc: Thomas Winant; ghc-devs at haskell.org; Frank Piessens > | Subject: Re: Partial type sigs > | > | Simon, > | > | 2015-02-05 17:44 GMT+01:00 Simon Peyton Jones > : > | > 3. It interferes with generalisation. > | > > | > For (3), consider > | > > | > let f :: _a -> _a > | > > | > f xs = reverse xs > | > > | > in (f True, f ?x?) > | > > | > Here, f gets the type f :: forall b. [b] -> [b], and _a is unifed > with > | [b]. > | > > | > So it simply doesn?t make sense for _a to appear in the body. What > | would it > | > mean to say > | > > | > let f :: _a -> _a > | > > | > f xs = reverse xs > | > > | > in (f (True :: _a), f ?x?) > | > | Isn't this a different case than Thomas' example? As I understand it, > | an equivalent of his example would have the wildcard in scope in the > | body of f, not in the body of the let. Something like this: > | > | let f :: _a -> _a > | f xs = reverse (xs :: _a) > | in (f [True], f "x") > | > | or > | > | let f :: _a -> _a > | f xs = let ys :: _a > | ys = tail xs > | in reverse ys > | in (f [True], f "x") > | > | I agree with what you say about _a being in scope in the body of the > | if, but I don't see a problem with _a being in scope in the body of > f. > | Do you? > | > | Note also that I haven't yet checked which of both is actually > | implemented. > | > | Regards, > | Dominique Disclaimer: http://www.kuleuven.be/cwis/email_disclaimer.htm From dreixel at gmail.com Fri Feb 6 09:58:28 2015 From: dreixel at gmail.com (=?UTF-8?Q?Jos=C3=A9_Pedro_Magalh=C3=A3es?=) Date: Fri, 6 Feb 2015 09:58:28 +0000 Subject: Generic instances for GHC AST In-Reply-To: References: Message-ID: I have nothing against this. If the unboxed types are a problem for the automatic Generic derivation, a manual instance could be written instead. Cheers, Pedro On Wed, Jan 14, 2015 at 9:03 PM, Alan & Kim Zimmerman wrote: > At the moment every part of the GHC AST derives instances of Data and > Typeable. > > There are no instances of Generic. > > If I try to standalone derive these, the derivation eventually fails for > > deriving instance Generic (Name) > > because the constructors are not all in scope. > > So, does it make sense in GHC to at least derive Generic for the items > that are opaque, and at most to do so for the whole AST. > > I know there were some concerns earlier about too many instances being > derived, and its impact on compilation time and memory, so the minimal > version may be best. > > This will allow the new generation libraries built around Generics to > perform on GHC data structures too. > > Alan > > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From merijn at inconsistent.nl Fri Feb 6 10:07:07 2015 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Fri, 6 Feb 2015 11:07:07 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> And no one of my proofreaders noticed that >.> I would propose to have the extension replace the 'fromString "foo"', 'fromIntegral 5' and 'fromList [1,2,3]' calls (for monomorphic cases) in the AST with the relevant Typed TH splice. I considered quasi-quotation initially too, but there's no quasi quotation syntax for Typed TH. I'm guessing that's just an oversight, but I'd really be in favour of adding a typed quasiquoter too. Similarly to thinking we should have an easier way to obtain Lift instances since, to me at least, it seems that the Lift instance for most ADTs should be fairly trivial? I'll quickly clarify the proposal on the wiki :) Cheers, Merijn > On 5 Feb 2015, at 22:48, Simon Peyton Jones wrote: > > I'm all for it. Syntax sounds like the main difficulty. Today you could use quasiquotatoin > [even| 38 |] > and get the same effect as $$(validate 38). But it's still noisy. > > So: what is the non-noisy scheme you want to propose? You don't quite get to that in the wiki page! > > Simon > > | -----Original Message----- > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Merijn > | Verstraaten > | Sent: 05 February 2015 14:46 > | To: ghc-devs at haskell.org; GHC users > | Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion > | > | I've been repeatedly running into problems with overloaded literals and > | partial conversion functions, so I wrote up an initial proposal > | (https://ghc.haskell.org/trac/ghc/wiki/ValidateMonoLiterals) and I'd like > | to commence with the bikeshedding and hearing other opinions :) > | > | Cheers, > | Merijn -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From simonpj at microsoft.com Fri Feb 6 10:28:58 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 6 Feb 2015 10:28:58 +0000 Subject: Partial type sigs In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562BF102@DB3PRD3001MB020.064d.mgd.msft.net> <54D34B11.2010007@cs.kuleuven.be> <618BE556AADD624C9C918AA5D5911BEF562C00D7@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C0376@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C0847@DB3PRD3001MB020.064d.mgd.msft.net> | avoid breaking existing programs. We might as well make named | wildcards lexically scoped by default, not even opt-out (as was the | case in my initial proposal). I don't object strongly, so long as the user manual is very clear on the question, and mentions the inconsistency with ordinary type variables. | About using a Maybe for sig_id to fix 10045: I tried it out, and your | solution does indeed fix it. In order for TcSigInfo to still implement | NamedThing, I used an 'Either Name TcId' instead of a 'Maybe TcId'. Do | you prefer a separate data type for this instead of an Either? (Please | come up with a good name for it in that case :) Better: * Remove instance NamedThing TcSigInfo * Add a field sig_name :: Name, and use it instead of getName in tcTySigs Comment that if sig_id = Just f, then sig_name = idName f * Leave the sig_id field as (Maybe TcId). It needs a pretty big comment. Actually sig_poly_id would be a better name for the field. | Unfortunately, some of my tests started failing, so I'll post | something on Phabricator as soon as I have worked out the kinks. OK thank you. Ping me when ready Simon | | | Cheers, | Thomas | | | | > Sorry to make such a misleading post. | > | > Simon | > | > | -----Original Message----- | > | From: dominique.devriese at gmail.com | > [mailto:dominique.devriese at gmail.com] | > | On Behalf Of Dominique Devriese | > | Sent: 05 February 2015 20:13 | > | To: Simon Peyton Jones | > | Cc: Thomas Winant; ghc-devs at haskell.org; Frank Piessens | > | Subject: Re: Partial type sigs | > | | > | Simon, | > | | > | 2015-02-05 17:44 GMT+01:00 Simon Peyton Jones | > : | > | > 3. It interferes with generalisation. | > | > | > | > For (3), consider | > | > | > | > let f :: _a -> _a | > | > | > | > f xs = reverse xs | > | > | > | > in (f True, f ?x?) | > | > | > | > Here, f gets the type f :: forall b. [b] -> [b], and _a is | unifed | > with | > | [b]. | > | > | > | > So it simply doesn?t make sense for _a to appear in the body. | > | > What | > | would it | > | > mean to say | > | > | > | > let f :: _a -> _a | > | > | > | > f xs = reverse xs | > | > | > | > in (f (True :: _a), f ?x?) | > | | > | Isn't this a different case than Thomas' example? As I understand | > | it, an equivalent of his example would have the wildcard in scope | in | > | the body of f, not in the body of the let. Something like this: | > | | > | let f :: _a -> _a | > | f xs = reverse (xs :: _a) | > | in (f [True], f "x") | > | | > | or | > | | > | let f :: _a -> _a | > | f xs = let ys :: _a | > | ys = tail xs | > | in reverse ys | > | in (f [True], f "x") | > | | > | I agree with what you say about _a being in scope in the body of | the | > | if, but I don't see a problem with _a being in scope in the body | of | > f. | > | Do you? | > | | > | Note also that I haven't yet checked which of both is actually | > | implemented. | > | | > | Regards, | > | Dominique | | Disclaimer: http://www.kuleuven.be/cwis/email_disclaimer.htm From alan.zimm at gmail.com Fri Feb 6 10:42:39 2015 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Fri, 6 Feb 2015 12:42:39 +0200 Subject: Generic instances for GHC AST In-Reply-To: References: Message-ID: Hi Pedro That makes sense. I hit a mental block as to how to turn the generic representation back into the original type, but obviously if you know what you want to turn it into, the type-specific instance will be used. Alan On Fri, Feb 6, 2015 at 11:58 AM, Jos? Pedro Magalh?es wrote: > I have nothing against this. > > If the unboxed types are a problem for the automatic Generic derivation, a > manual instance could be written instead. > > > Cheers, > Pedro > > On Wed, Jan 14, 2015 at 9:03 PM, Alan & Kim Zimmerman > wrote: > >> At the moment every part of the GHC AST derives instances of Data and >> Typeable. >> >> There are no instances of Generic. >> >> If I try to standalone derive these, the derivation eventually fails for >> >> deriving instance Generic (Name) >> >> because the constructors are not all in scope. >> >> So, does it make sense in GHC to at least derive Generic for the items >> that are opaque, and at most to do so for the whole AST. >> >> I know there were some concerns earlier about too many instances being >> derived, and its impact on compilation time and memory, so the minimal >> version may be best. >> >> This will allow the new generation libraries built around Generics to >> perform on GHC data structures too. >> >> Alan >> >> >> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://www.haskell.org/mailman/listinfo/ghc-devs >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dominique.devriese at cs.kuleuven.be Fri Feb 6 12:13:33 2015 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Fri, 6 Feb 2015 13:13:33 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> Message-ID: Merijn, Perhaps only for the sake of discussion: have you considered doing something at the type-level instead of using TH? I mean that you could change the type of 42 from `forall a. Num a => a` to `forall a. HasIntLiteral a '42 => a` where HasIntegerLiteral is a type class of kind `* -> 'Integer -> Constraint` and people can instantiate it for their types: class HasIntegerLiteral (a :: *) (k :: 'Integer) where literal :: a The desugarer could then just generate an invocation of "literal". An advantage would be that you don't need TH (although you do need DataKinds and type-level computation). Specifically, type-checking remains decidable and you can do it in safe haskell and so on. I haven't thought this through very far, so there may be other advantages/disadvantages/glaring-holes-in-the-idea that I'm missing. Regards, Dominique 2015-02-06 11:07 GMT+01:00 Merijn Verstraaten : > And no one of my proofreaders noticed that >.> > > I would propose to have the extension replace the 'fromString "foo"', 'fromIntegral 5' and 'fromList [1,2,3]' calls (for monomorphic cases) in the AST with the relevant Typed TH splice. > > I considered quasi-quotation initially too, but there's no quasi quotation syntax for Typed TH. I'm guessing that's just an oversight, but I'd really be in favour of adding a typed quasiquoter too. Similarly to thinking we should have an easier way to obtain Lift instances since, to me at least, it seems that the Lift instance for most ADTs should be fairly trivial? > > I'll quickly clarify the proposal on the wiki :) > > Cheers, > Merijn > >> On 5 Feb 2015, at 22:48, Simon Peyton Jones wrote: >> >> I'm all for it. Syntax sounds like the main difficulty. Today you could use quasiquotatoin >> [even| 38 |] >> and get the same effect as $$(validate 38). But it's still noisy. >> >> So: what is the non-noisy scheme you want to propose? You don't quite get to that in the wiki page! >> >> Simon >> >> | -----Original Message----- >> | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Merijn >> | Verstraaten >> | Sent: 05 February 2015 14:46 >> | To: ghc-devs at haskell.org; GHC users >> | Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion >> | >> | I've been repeatedly running into problems with overloaded literals and >> | partial conversion functions, so I wrote up an initial proposal >> | (https://ghc.haskell.org/trac/ghc/wiki/ValidateMonoLiterals) and I'd like >> | to commence with the bikeshedding and hearing other opinions :) >> | >> | Cheers, >> | Merijn > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > From merijn at inconsistent.nl Fri Feb 6 12:45:40 2015 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Fri, 6 Feb 2015 13:45:40 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> Message-ID: <507A1EEF-5C0D-4C5E-B842-B14860DBDA9F@inconsistent.nl> Hi Dominique, I don't see how that would replace the usecase I describe? I'll give you a more concrete example from a library I'm working on. I'm working on a Haskell implementation of ZeroMQ, the ZMTP protocol lets sockets be named by a "binary identifier with length <= 255 and NOT starting with a NUL byte". As a programmer using this library I would have to write these socket identifiers in my source code. Now I have four options: 1) The library just doesn't validate identifiers to be compatible with the protocol (awful!) 2) My library produces a runtime error on every single invocation of the program (if it doesn't satisfy the constraints it will never successfully work) 3) I require a newtype'd input type with a smart constructor, which means the programmer still has to handle the "error" case even though it should never happen for literals written in the source. 4) Using a trick like what I desribed, the above newtype and smart constructor, and check at compile time that it is correct. To be honest, I don't even see how your example would generalise to the rather trivial example using Even? For example, suppose we have "foo :: Even -> SomeData" how would I write "foo 2" using your idea in a way that, at compile time, checks that I'm not passing an invalid literal to foo? As a further aside, your "type checking remains decidable" comment seems to imply that you think that type checking becomes undecidable with what I propose? Can you explain how that could be, considering that it already works in GHC, albeit in a very cumbersome way? As for working with Safe Haskell, I'm all for better Safe Haskell support in TH, but unfortunately I'm already worried about my ability to tackle this proposal, let alone something more ambitious like making TH work better with Safe Haskell, I'll leave that task for someone more familiar with GHC. Cheers, Merijn > On 6 Feb 2015, at 13:13, Dominique Devriese wrote: > > Merijn, > > Perhaps only for the sake of discussion: have you considered doing > something at the type-level instead of using TH? I mean that you could > change the type of 42 from `forall a. Num a => a` to `forall a. > HasIntLiteral a '42 => a` where HasIntegerLiteral is a type class of > kind `* -> 'Integer -> Constraint` and people can instantiate it for > their types: > > class HasIntegerLiteral (a :: *) (k :: 'Integer) where > literal :: a > > The desugarer could then just generate an invocation of "literal". > > An advantage would be that you don't need TH (although you do need > DataKinds and type-level computation). Specifically, type-checking > remains decidable and you can do it in safe haskell and so on. I > haven't thought this through very far, so there may be other > advantages/disadvantages/glaring-holes-in-the-idea that I'm missing. > > Regards, > Dominique > > 2015-02-06 11:07 GMT+01:00 Merijn Verstraaten : >> And no one of my proofreaders noticed that >.> >> >> I would propose to have the extension replace the 'fromString "foo"', 'fromIntegral 5' and 'fromList [1,2,3]' calls (for monomorphic cases) in the AST with the relevant Typed TH splice. >> >> I considered quasi-quotation initially too, but there's no quasi quotation syntax for Typed TH. I'm guessing that's just an oversight, but I'd really be in favour of adding a typed quasiquoter too. Similarly to thinking we should have an easier way to obtain Lift instances since, to me at least, it seems that the Lift instance for most ADTs should be fairly trivial? >> >> I'll quickly clarify the proposal on the wiki :) >> >> Cheers, >> Merijn >> >>> On 5 Feb 2015, at 22:48, Simon Peyton Jones wrote: >>> >>> I'm all for it. Syntax sounds like the main difficulty. Today you could use quasiquotatoin >>> [even| 38 |] >>> and get the same effect as $$(validate 38). But it's still noisy. >>> >>> So: what is the non-noisy scheme you want to propose? You don't quite get to that in the wiki page! >>> >>> Simon >>> >>> | -----Original Message----- >>> | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Merijn >>> | Verstraaten >>> | Sent: 05 February 2015 14:46 >>> | To: ghc-devs at haskell.org; GHC users >>> | Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion >>> | >>> | I've been repeatedly running into problems with overloaded literals and >>> | partial conversion functions, so I wrote up an initial proposal >>> | (https://ghc.haskell.org/trac/ghc/wiki/ValidateMonoLiterals) and I'd like >>> | to commence with the bikeshedding and hearing other opinions :) >>> | >>> | Cheers, >>> | Merijn >> >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users >> -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From adam at well-typed.com Fri Feb 6 13:20:24 2015 From: adam at well-typed.com (Adam Gundry) Date: Fri, 06 Feb 2015 13:20:24 +0000 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> Message-ID: <54D4BF98.3020104@well-typed.com> Hi Dominique, On 06/02/15 12:13, Dominique Devriese wrote: > Perhaps only for the sake of discussion: have you considered doing > something at the type-level instead of using TH? I mean that you could > change the type of 42 from `forall a. Num a => a` to `forall a. > HasIntLiteral a '42 => a` where HasIntegerLiteral is a type class of > kind `* -> 'Integer -> Constraint` and people can instantiate it for > their types: > > class HasIntegerLiteral (a :: *) (k :: 'Integer) where > literal :: a > > The desugarer could then just generate an invocation of "literal". > > An advantage would be that you don't need TH (although you do need > DataKinds and type-level computation). Specifically, type-checking > remains decidable and you can do it in safe haskell and so on. I > haven't thought this through very far, so there may be other > advantages/disadvantages/glaring-holes-in-the-idea that I'm missing. Interestingly, the string version of this would be remarkably similar to the IV class [1] that came up in the redesign of OverloadedRecordFields: class IV (x :: Symbol) a where iv :: a though in this case the plan was to have a special syntax for such literals (e.g. #x). It seems to me that what you would describe would work, and the avoidance of TH is a merit, but the downside is the complexity of implementing even relatively simple validation at the type level (as opposed to just reusing a term-level function). For Merijn's Even example I guess one could do something like this in current GHC: type family IsEven (n :: Nat) :: Bool where IsEven 0 = True IsEven 1 = False IsEven n = n - 2 instance (KnownNat n, IsEven n ~ True) => HasIntegerLiteral Even n where literal = Even (natVal (Proxy :: Proxy n)) but anything interesting to do with strings (e.g. checking that ByteStrings are ASCII) is rather out of reach at present. Adam [1] https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Redesign#Implicitvalues -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From dominique.devriese at cs.kuleuven.be Fri Feb 6 13:41:30 2015 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Fri, 6 Feb 2015 14:41:30 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: <507A1EEF-5C0D-4C5E-B842-B14860DBDA9F@inconsistent.nl> References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <507A1EEF-5C0D-4C5E-B842-B14860DBDA9F@inconsistent.nl> Message-ID: Hi Merijn, 2015-02-06 13:45 GMT+01:00 Merijn Verstraaten : > I don't see how that would replace the usecase I describe? I've written out the Even use case a bit, to hopefully clarify my suggestion. The code is a bit cumbersome and inefficient because I can't use GHC type-lits because some type-level primitives seem to be missing (modulo specifically). Type-level Integers (i.e. a kind with *negative* numbers and literals) would probably also be required for an actual solution. {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DataKinds, KindSignatures, ExplicitForAll, PolyKinds, ScopedTypeVariables, ConstraintKinds, TypeFamilies, GADTs, FlexibleContexts #-} module ValidateMonoLiterals where data Nat where Zero :: Nat Suc :: Nat -> Nat class KnownNat (n :: Nat) where natSing :: forall proxy. proxy n -> Integer instance KnownNat Zero where natSing _ = 0 instance KnownNat k => KnownNat (Suc k) where natSing _ = natSing (Proxy :: Proxy k) + 1 data Proxy (t :: k) = Proxy class HasNatLiteral a (k :: Nat) where literal :: Proxy k -> a data Even = Even Integer class CheckEven (k :: Nat) where instance CheckEven Zero instance CheckEven k => CheckEven (Suc (Suc k)) where instance (KnownNat k, CheckEven k) => HasNatLiteral Even (k :: Nat) where literal _ = Even (fromInteger (natSing (Proxy :: Proxy k))) instance (KnownNat k) => HasNatLiteral Integer k where literal _ = natSing (Proxy :: Proxy k) four :: HasNatLiteral n (Suc (Suc (Suc (Suc Zero)))) => n four = literal (Proxy :: Proxy (Suc (Suc (Suc (Suc Zero))))) three :: HasNatLiteral n (Suc (Suc (Suc Zero))) => n three = literal (Proxy :: Proxy (Suc (Suc (Suc Zero)))) fourI :: Integer fourI = four fourEI :: Even fourEI = four -- fails with "No instance for CheckEven (Suc Zero)" -- threeEI :: Even -- threeEI = three > I'll give you a more concrete example from a library I'm working on. I'm working on a Haskell implementation of ZeroMQ, the ZMTP protocol lets sockets be named by a "binary identifier with length <= 255 and NOT starting with a NUL byte". As a programmer using this library I would have to write these socket identifiers in my source code. Now I have four options: > 1) The library just doesn't validate identifiers to be compatible with the protocol (awful!) > > 2) My library produces a runtime error on every single invocation of the program (if it doesn't satisfy the constraints it will never successfully work) > > 3) I require a newtype'd input type with a smart constructor, which means the programmer still has to handle the "error" case even though it should never happen for literals written in the source. > > 4) Using a trick like what I desribed, the above newtype and smart constructor, and check at compile time that it is correct. Well, I think my suggestion could be used as another alternative. As I mentioned, the compiler could translate the literal 42 to an appropriately typed invocation of HasNatLiteral.literal, so that you could also just write 42 but get the additional compile-time checking. > To be honest, I don't even see how your example would generalise to the rather trivial example using Even? For example, suppose we have "foo :: Even -> SomeData" how would I write "foo 2" using your idea in a way that, at compile time, checks that I'm not passing an invalid literal to foo? See above: the type of foo doesn't change w.r.t. your approach. > As a further aside, your "type checking remains decidable" comment seems to imply that you think that type checking becomes undecidable with what I propose? Can you explain how that could be, considering that it already works in GHC, albeit in a very cumbersome way? What I mean is that meta-programs invoked through TH can always fail to terminate (even though the ones you are using in your example are terminating). Consider what happens if you change the definition of your validate to this (or someone else implements your validateInteger like this for a type): validate :: forall a . Validate a => Integer -> Q (TExp a) validate i = validate (i+1) Regards, Dominique From dominique.devriese at cs.kuleuven.be Fri Feb 6 13:49:29 2015 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Fri, 6 Feb 2015 14:49:29 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: <54D4BF98.3020104@well-typed.com> References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> Message-ID: 2015-02-06 14:20 GMT+01:00 Adam Gundry : > It seems to me that what you would describe would work, and the > avoidance of TH is a merit, but the downside is the complexity of > implementing even relatively simple validation at the type level (as > opposed to just reusing a term-level function). For Merijn's Even > example I guess one could do something like this in current GHC: > > type family IsEven (n :: Nat) :: Bool where > IsEven 0 = True > IsEven 1 = False > IsEven n = n - 2 > > instance (KnownNat n, IsEven n ~ True) > => HasIntegerLiteral Even n where > literal = Even (natVal (Proxy :: Proxy n)) > > but anything interesting to do with strings (e.g. checking that > ByteStrings are ASCII) is rather out of reach at present. 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 ... Regards, Dominique From hesselink at gmail.com Fri Feb 6 13:55:59 2015 From: hesselink at gmail.com (Erik Hesselink) Date: Fri, 6 Feb 2015 14:55:59 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> Message-ID: On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese 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 From merijn at inconsistent.nl Fri Feb 6 15:53:56 2015 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Fri, 6 Feb 2015 16:53:56 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> Message-ID: <6C1707A8-8B1F-4F7D-B6FF-A453078AA354@inconsistent.nl> While I am certainly in favour of better and more flexible approaches to enforcing this in the type system (I'm a big fan of all the dependent Haskell/singletons stuff), I don't think this is an appropriate solution here. First off, a lot of interesting and important cases can't feasibly be solved right now (i.e., most things involving strings/lists). More importantly, I think the examples given in this thread so far are FAR beyond the capabilities of beginner/intermediate haskellers, whereas implementing a terminating "String -> Maybe a" is fairly trivial. So in terms of pragmatical usability I think the TH approach is easier to implement in GHC, easier to use by end users and more flexible and powerful than the suggested type families/DataKinds. I'm all in favour of some of the below directions, but pragmatically I think it'll be a while before any of those problems are usable by any beginners. I also realise a lot of people prefer avoiding TH if at all possible, but given that this is an extension that people have to opt into that won't otherwise affect their code, I think that's acceptable. Personally, I'd gladly use TH in exchange for this sort of checking and I've talked to several others that would to. Cheers, Merijn > On 6 Feb 2015, at 14:55, Erik Hesselink wrote: > > On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese > 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 > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From merijn at inconsistent.nl Fri Feb 6 16:16:43 2015 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Fri, 6 Feb 2015 17:16:43 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> Message-ID: <75993583-3304-4CBF-B58D-FE58A2DA6233@inconsistent.nl> 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 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 wrote: > On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese > 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 at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From duncan at well-typed.com Fri Feb 6 16:55:44 2015 From: duncan at well-typed.com (Duncan Coutts) Date: Fri, 06 Feb 2015 16:55:44 +0000 Subject: Can't install packages with my inplace compiler In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF3F3946FF@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF3F38F616@DB3PRD3001MB020.064d.mgd.msft.net> <87ioiv1ac9.fsf@gmail.com> <618BE556AADD624C9C918AA5D5911BEF3F390912@DB3PRD3001MB020.064d.mgd.msft.net> <1415126925-sup-4219@sabre> <618BE556AADD624C9C918AA5D5911BEF3F392330@DB3PRD3001MB020.064d.mgd.msft.net> <1415180472.6486.50.camel@dunky.localdomain> <618BE556AADD624C9C918AA5D5911BEF3F3946FF@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <1423241744.30868.29.camel@dunky.localdomain> On Wed, 2014-11-05 at 09:50 +0000, Simon Peyton Jones wrote: > | Actually I'd suggest you use the Cabal and cabal-install that are part > | of the ghc source tree, rather than Cabal/cabal-install HEAD. The two > | are not always the same. > > Aha ok, thank you. How exactly do I do that? Where is the executable > cabal-install in the tree? IN inplace/bin I see an executable > ghc-cabal. Is that it? > > Alternatively, "Plan B" on > https://ghc.haskell.org/trac/ghc/wiki/Debugging/InstallingPackagesInplace > (which I confess I'd forgotten about) describes a different plan that > doesn't mention cabal-install at all. Is that better? To follow up on a rather old thread: I included a little backwards compatibility hack (which I think made it into RC2) so that other users will not hit this, so that they can continue to use an old version of cabal-install with 7.10. For context, the error you and others were seeing was: > ghc-stage2: ghc no longer supports single-file style package databases > (dist/package.conf.inplace) use 'ghc-pkg init' to create the database > with the correct format. -- Duncan Coutts, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From dan.doel at gmail.com Fri Feb 6 17:24:53 2015 From: dan.doel at gmail.com (Dan Doel) Date: Fri, 6 Feb 2015 12:24:53 -0500 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> <75993583-3304-4CBF-B58D-FE58A2DA6233@inconsistent.nl> Message-ID: Assuming a separate syntax, I believe that the criterion would be as simple as ensuring that no ValidateFoo constraints are left outstanding. The syntax would add the relevant validate call, and type variables involved in a ValidateFoo constraint would not be generalizable, and would have to be defaulted or inferred from elsewhere, similar to the monomorphism restriction. I'm not sure how difficult that would be to implement. I'm not terribly gung ho on this, though. It feels very ad hoc. Making validation vs. non-validation syntactic rather than just based on polymorphism seems somewhat less so, though; so I'd prefer that direction. Finding unused syntax is always a problem, of course. On Fri, Feb 6, 2015 at 11:38 AM, Ryan Trinkle wrote: > 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 < > merijn at 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 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 >> wrote: >> > On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese >> > 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 at haskell.org >> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users >> >> > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at well-typed.com Fri Feb 6 20:31:38 2015 From: adam at well-typed.com (Adam Gundry) Date: Fri, 06 Feb 2015 20:31:38 +0000 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> <75993583-3304-4CBF-B58D-FE58A2DA6233@inconsistent.nl> Message-ID: <54D524AA.5070608@well-typed.com> If we go for a separate syntax, what do we gain over normal quasiquotes or $$(validate x)? Sure, literals could be made a little more beautiful, but I'm not sure it justifies stealing more syntax (and what would that syntax be?). Without a separate syntax, I'm not sure I understand the original proposal. The wiki page says "GHC would replace fromString/fromInteger/fromList expressions originating from literals with a Typed TH splice along the lines of validate for all monomorphic cases." What does "all monomorphic cases" mean? Is the idea what GHC would typecheck an expression involving a literal integer, determine that the occurrence had type Even, then evaluate the TH splice *after* typechecking? Whereas if the occurrence had a non-ground type, it would do something else? None of this is particularly persuasive, I'm afraid. Is it worthwhile introducing something new just to avoid having to write a quasiquote? I *am* attracted to the idea of indexed classes in place of IsString/Num class KnownSymbol s => IsIndexedString (a :: *) (s :: Symbol) where fromIndexedString :: a class KnownInteger i => IsIndexedInteger (a :: *) (i :: Integer) where fromIndexedInteger :: a These have a smooth upgrade path from the existing class instances via default fromIndexedString :: (KnownSymbol s, IsString a) => a fromIndexedString = fromString (symbolVal (Proxy :: Proxy s)) default fromIndexedInteger :: (KnownInteger i, Num a) => a fromIndexedInteger = fromInteger (integerVal (Proxy :: Proxy i)) and other instances can take advantage of the additional type information. perhaps we need to bring Dependent Haskell a bit closer before this is justifiable... Adam On 06/02/15 17:24, Dan Doel wrote: > Assuming a separate syntax, I believe that the criterion would be as > simple as ensuring that no ValidateFoo constraints are left outstanding. > The syntax would add the relevant validate call, and type variables > involved in a ValidateFoo constraint would not be generalizable, and > would have to be defaulted or inferred from elsewhere, similar to the > monomorphism restriction. I'm not sure how difficult that would be to > implement. > > I'm not terribly gung ho on this, though. It feels very ad hoc. Making > validation vs. non-validation syntactic rather than just based on > polymorphism seems somewhat less so, though; so I'd prefer that > direction. Finding unused syntax is always a problem, of course. -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From gershomb at gmail.com Fri Feb 6 20:54:12 2015 From: gershomb at gmail.com (Gershom B) Date: Fri, 6 Feb 2015 15:54:12 -0500 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion Message-ID: I recall having some discussions with Mathieu Boespflug regarding how the static pointers work could be of use here. (And also Richard Eisenberg?) In particular, we want to demand a special property of our validation functions -- that they can safely be used at compile-time without necessarily "linking in the world" and invoking the whole of template haskell. A function that is "static" should in a sense have this sort of property? And so requiring that our validation functions be static seems like a useful thing from an implementation standpoint. Static semantics might also help "force the thunk" on what the correct relationship to polymorphism is. I guess the remaining question is then where to add them. I suppose we could stick them with special semantics on Num and IsString or the like and do it by magic? Alternately we could maybe have a whole class of "compile-time static functions" that we just explicitly use, and all have the property that they have type "a -> a" for some concrete "a", and that the value they are applied to is static. These functions are then applied at compile time, and forced to whnf. If they toss an error it is a compile error, otherwise they are not present in the generated code. There are other design variations possible, but that one feels pretty neat to me, if feasible. So then I could write foo :: Even foo = even 6 for example, and get errors at compile-time. On top of this we could add a special way to augment Num, IsString, etc with such methods to yield the desired: foo :: Even foo = 6 -gershom -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Feb 6 22:16:33 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 6 Feb 2015 17:16:33 -0500 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> <75993583-3304-4CBF-B58D-FE58A2DA6233@inconsistent.nl> Message-ID: Its worth pointing out that when / if luites out of process TH design happens for ghc, TH will be usable in cross compile builds of ghc as well. So we shouldn't let that constraint we have for now dictate future tooling ideas. On Feb 6, 2015 3:50 PM, "Evan Laforge" wrote: > Would it be feasible to make a lighter-weight mode for quasiquotes > that doesn't require the whole "load the module in ghci" runaround? > If it didn't need to do that, there wouldn't be much downside to > turning it on everywhere. And it would enable lots of QQ conveniences > that at least I don't think its worth enabling TH for, due to the ghci > hassle. > > Greg Weber recently asked for input on the idea of restricted TH > modes, this seems related. > > If a splice was pure and had no non-Prelude dependencies, could it be > run without ghci loading and stage restrictions? > > I think it's really awkward how numeric literals use fromInteger and > fromRational, and those functions are grouped into Num and Fractional. > So if you want to use (+), you also have to accept literals, which > means you have to accept anything anyone might type. Has there been > any kind of proposal to split fromInteger and fromRational into their > own typeclasses analogous to IsString? > > On Fri, Feb 6, 2015 at 9:24 AM, Dan Doel wrote: > > Assuming a separate syntax, I believe that the criterion would be as > simple > > as ensuring that no ValidateFoo constraints are left outstanding. The > syntax > > would add the relevant validate call, and type variables involved in a > > ValidateFoo constraint would not be generalizable, and would have to be > > defaulted or inferred from elsewhere, similar to the monomorphism > > restriction. I'm not sure how difficult that would be to implement. > > > > I'm not terribly gung ho on this, though. It feels very ad hoc. Making > > validation vs. non-validation syntactic rather than just based on > > polymorphism seems somewhat less so, though; so I'd prefer that > direction. > > Finding unused syntax is always a problem, of course. > > > > On Fri, Feb 6, 2015 at 11:38 AM, Ryan Trinkle > > wrote: > >> > >> 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 > >> 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 > 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 > >>> > wrote: > >>> > On Fri, Feb 6, 2015 at 2:49 PM, Dominique Devriese > >>> > 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 at haskell.org > >>> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > >>> > >>> _______________________________________________ > >>> Glasgow-haskell-users mailing list > >>> Glasgow-haskell-users at haskell.org > >>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > >>> > >> > >> > >> _______________________________________________ > >> Glasgow-haskell-users mailing list > >> Glasgow-haskell-users at haskell.org > >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > >> > > > > > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From eyeinsky9 at gmail.com Fri Feb 6 22:25:34 2015 From: eyeinsky9 at gmail.com (Carl Eyeinsky) Date: Sat, 7 Feb 2015 00:25:34 +0200 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> Message-ID: Hi * for what it's worth, I really like the idea. Its purpose is clear, it's easy to use, it's straightforward to understand, and it seems there are only benefits that come with it. I at least would be an immediate user, as it gives a compile-time fence to custom hard-coded stuff. E.g. it is sometimes simpler and nicer to put something in a string literal rather than an explicit AST. (Just my 2 cents -- I'm not a TH expert.) On Thu, Feb 5, 2015 at 4:45 PM, Merijn Verstraaten wrote: > I've been repeatedly running into problems with overloaded literals and > partial conversion functions, so I wrote up an initial proposal ( > https://ghc.haskell.org/trac/ghc/wiki/ValidateMonoLiterals) and I'd like > to commence with the bikeshedding and hearing other opinions :) > > Cheers, > Merijn > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > > -- Carl Eyeinsky -------------- next part -------------- An HTML attachment was scrubbed... URL: From tuncer.ayaz at gmail.com Sat Feb 7 13:01:11 2015 From: tuncer.ayaz at gmail.com (Tuncer Ayaz) Date: Sat, 7 Feb 2015 14:01:11 +0100 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: References: Message-ID: On Wed, Jan 28, 2015 at 11:45 AM, Tuncer Ayaz wrote: > With all three listed build.mk settings, I'm unable to make install: > > arch: linux-amd64 > > I had no problem building rc1 (7.10.0.20141222). > > # config 1 > BuildFlavour = perf > V = 0 > GhcLibWays = v > DYNAMIC_GHC_PROGRAMS = NO > DYNAMIC_BY_DEFAULT = NO > GhcHcOpts= > > # config 2 > BuildFlavour = perf > V = 0 > DYNAMIC_GHC_PROGRAMS = NO > DYNAMIC_BY_DEFAULT = NO > GhcHcOpts= > > # config 3 > BuildFlavour = perf > V = 0 > DYNAMIC_GHC_PROGRAMS = NO > DYNAMIC_BY_DEFAULT = NO > > # copy config to mk/build.mk > $ perl boot > $ ./configure --prefix=/usr/local/ghc/7.10.0.20150123 > $ make install > > [...] > > Installing library in > /usr/local/ghc/7.10.0.20150123/lib/ghc-7.10.0.20150123/ghcpr_FgrV6cgh2JHBlbcx1OSlwt > ghc-cabal: dist-install/build/HSghcpr_FgrV6cgh2JHBlbcx1OSlwt.o: does not exist > ghc.mk:918: recipe for target 'install_packages' failed > make[1]: *** [install_packages] Error 1 > Makefile:71: recipe for target 'install' failed > make: *** [install] Error 2 So, am I alone in encountering this issue with RC2 but not RC1? From petersen at fedoraproject.org Sat Feb 7 14:26:41 2015 From: petersen at fedoraproject.org (Jens Petersen) Date: Sat, 7 Feb 2015 15:26:41 +0100 Subject: ghc-7.8 in Fedora Rawhide Message-ID: The Fedora Haskell SIG is pleased to announce the arrival of GHC 7.8 in the Fedora 22 Rawhide development tree. - the GHC version is 7.8.4: we are no longer following haskell-platform strictly, - over 120 Haskell packages have been updated to their latest versions, including pandoc-1.13.2. There are currently still a few issues in Rawhide: - a few packages have not yet been rebuilt/updated with ghc-7.8.4: - errors: bustle, ghc-ForSyde, ghc-type-level, ghc-parameterized-data - new deps needed: hledger, Agda, leksah, cab - also on ARMv7 the RTS seems to have some strange problems leading to crashes which is under investagation: no idris build on armv7: < https://ghc.haskell.org/trac/ghc/ticket/10029>. Thanks, Jens -------------- next part -------------- An HTML attachment was scrubbed... URL: From george.colpitts at gmail.com Sat Feb 7 15:10:23 2015 From: george.colpitts at gmail.com (George Colpitts) Date: Sat, 7 Feb 2015 11:10:23 -0400 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: References: <87h9v4vhcp.fsf@gnu.org> Message-ID: Thanks Eric, I have the same problem with this as the RC2 I build from source, i.e. Mac specific bug https://ghc.haskell.org/trac/ghc/ticket/10053 : error in ghci calling main after loading compiled code -- Too late for parseStaticFlags: call it before runGhc or runGhcT I have a file mainbug.hs that consists of main = print "hello" I can reproduce it as follows: ghc -dynamic mainbug.hs [1 of 1] Compiling Main ( mainbug.hs, mainbug.o ) Linking mainbug ... bash-3.2$ ghci GHCi, version 7.10.0.20150123: http://www.haskell.org/ghc/ :? for help Prelude> :load mainbug Ok, modules loaded: Main. Prelude Main> :show modules Main ( mainbug.hs, mainbug.o ) Prelude Main> main Too late for parseStaticFlags: call it before runGhc or runGhcT *** Exception: ExitFailure 1 Loading it interpreted works fine: rm mainbug.o bash-3.2$ ghci GHCi, version 7.10.0.20150123: http://www.haskell.org/ghc/ :? for help Prelude> :load mainbug [1 of 1] Compiling Main ( mainbug.hs, interpreted ) Ok, modules loaded: Main. *Main> main "hello" Can anybody else reproduce this bug on their Mac? On Mon, Feb 2, 2015 at 6:58 AM, Erik Hesselink wrote: > On Mon, Feb 2, 2015 at 9:37 AM, Herbert Valerio Riedel > wrote: > > Hi Mark, > > > > On 2015-01-28 at 04:31:29 +0100, Mark Lentczner wrote: > >> I've just built a bindist under 10.10, but just normal not expressly > llvm. > >> I'll test this in a bit then post it -- but might be sometime tomorrow > >> before it is up. > > > > How's progress on this btw? Are you also working on a GHC 7.8.4 OSX > > bindist by any chance? > > I made a bindist of RC2 (just like I did for RC1) which is here [1]. > This was built on 10.9, without anything special for llvm. If anyone > wants me to try something or produce a different build, please let me > know. > > Erik > > [1] > https://docs.google.com/a/silk.co/uc?id=0B5E6EvOcuE0nVmJ3WElQZW81b1U&export=download > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From iavor.diatchki at gmail.com Sat Feb 7 20:11:23 2015 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Sat, 7 Feb 2015 12:11:23 -0800 Subject: Question about implementing `Typeable` (with kinds) Message-ID: Hello, I started adding custom solving for `Typeable` constraints, to work around the problem where kind parameters were missing from the representation of types. The idea is as follows: 1. Add a new filed to `TypeRep` that remembers _kind_ parameters: TypeRep Fingerprint TyCon [TypeRep]{-kinds-} [TypeRep]{-types-} 2. Modify the constraint solver, to solve constraints like this: - Kind-polymorphic type constructors don't get `Typeable` instances on their own - GHC can solve `Typeable` constraints on _*concrete uses*_ of polymorphic type constructors. More precisely, GHC can solve constraints of the form `Typeable k (TC @ ks)`, as long as: (1) `k` is not a forall kind, (2) the `ks` are all concrete kinds (i.e., they have no free kind variables). This all seems fairly straight-forward, but I got stuck on the actual implementation, in particular: *what `EvTerm` should I use when discharging a `Typeable` constraint?* I can create a an `HsSyn` value for the required method (i.e., a function of type `Proxy# t -> TypeRep`). I can also cast this into a `Typeable` dictionary value. The issue is that I am left with an `HsSyn` expression, and not an `EvTerm`. So is there a way to treat an arbitrary expression as an `EvTerm`? In the implementation of the type-lits, I just added custom evidence, but this does not scale well (also, in that case the evidence is just a simple value, while here it is a bit more complex). Suggestions would be most appreciated! -Iavor -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Sun Feb 8 01:08:19 2015 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sat, 7 Feb 2015 20:08:19 -0500 Subject: Question about implementing `Typeable` (with kinds) In-Reply-To: References: Message-ID: Thanks, Iavor, for doing this! On Feb 7, 2015, at 3:11 PM, Iavor Diatchki wrote: > 1. Add a new filed to `TypeRep` that remembers _kind_ parameters: > > TypeRep Fingerprint TyCon [TypeRep]{-kinds-} [TypeRep]{-types-} Perhaps change to use record syntax? With two `[TypeRep]` parameters, it could get confusing. > > 2. Modify the constraint solver, to solve constraints like this: > - Kind-polymorphic type constructors don't get `Typeable` instances on their own > - GHC can solve `Typeable` constraints on _concrete uses_ of polymorphic type constructors. > More precisely, GHC can solve constraints of the form `Typeable k (TC @ ks)`, as long as: > (1) `k` is not a forall kind, > (2) the `ks` are all concrete kinds (i.e., they have no free kind variables). > > This all seems fairly straight-forward, but I got stuck on the actual implementation, in particular: > > what `EvTerm` should I use when discharging a `Typeable` constraint? > > I can create a an `HsSyn` value for the required method (i.e., a function of type `Proxy# t -> TypeRep`). > I can also cast this into a `Typeable` dictionary value. > The issue is that I am left with an `HsSyn` expression, and not an `EvTerm`. > > So is there a way to treat an arbitrary expression as an `EvTerm`? > > In the implementation of the type-lits, I just added custom evidence, but this does not scale well (also, in that case the evidence is just a simple value, while here > it is a bit more complex). > > Suggestions would be most appreciated! Seems to me that adding another constructor of EvTerm is the way forward. I agree that the approach doesn't scale, but I think that any custom behavior in the solver is going to need some custom support. However, perhaps there is a better way, such as encoding either an HsExpr or a CoreExpr into an EvTerm somehow... Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Mon Feb 9 02:51:43 2015 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sun, 8 Feb 2015 21:51:43 -0500 Subject: stack traces when debugging GHC Message-ID: Hi devs, I've just made a miraculous discovery and I want to share! It has happened many times that I create some bizarre error in GHC and have no clue where it comes from. In the past, I've ended up using pprTrace to label all calls of the failing function, sometimes recursively, until I get an idea of what's going on. This is terribly painful. And then, I noticed that the function Debug.Trace.traceStack (just in the `base` package, not part of GHC) will print out a stack trace, when profiling is enabled. So, I tried building a profiled build of GHC, with -DDEBUG and -fprof-auto (just by editing the "prof" section of build.mk). And then, voila, ASSERTs now print stack traces! And, with a small change in Outputable, I can get pprTrace to print stack traces, too! Hooray! I'd love to put this on the wiki. Any clue where this might be found? Richard From austin at well-typed.com Mon Feb 9 08:44:51 2015 From: austin at well-typed.com (Austin Seipp) Date: Mon, 9 Feb 2015 02:44:51 -0600 Subject: stack traces when debugging GHC In-Reply-To: References: Message-ID: Looks like you want https://ghc.haskell.org/trac/ghc/wiki/Debugging/Compiler - the first section mentions -DDEBUG, but not -fprof-auto. Probably worth adding a few sentences about what you've found to the top of the page. Thanks! On Sun, Feb 8, 2015 at 8:51 PM, Richard Eisenberg wrote: > Hi devs, > > I've just made a miraculous discovery and I want to share! > > It has happened many times that I create some bizarre error in GHC and have no clue where it comes from. In the past, I've ended up using pprTrace to label all calls of the failing function, sometimes recursively, until I get an idea of what's going on. This is terribly painful. And then, I noticed that the function Debug.Trace.traceStack (just in the `base` package, not part of GHC) will print out a stack trace, when profiling is enabled. So, I tried building a profiled build of GHC, with -DDEBUG and -fprof-auto (just by editing the "prof" section of build.mk). > > And then, voila, ASSERTs now print stack traces! And, with a small change in Outputable, I can get pprTrace to print stack traces, too! Hooray! > > I'd love to put this on the wiki. Any clue where this might be found? > > Richard > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From merijn at inconsistent.nl Mon Feb 9 09:47:56 2015 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Mon, 9 Feb 2015 10:47:56 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: <54D524AA.5070608@well-typed.com> References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> <75993583-3304-4CBF-B58D-FE58A2DA6233@inconsistent.nl> <54D524AA.5070608@well-typed.com> Message-ID: Hi Adam, > On 6 Feb 2015, at 21:31, Adam Gundry wrote: > What does "all monomorphic cases" mean? Is the idea what GHC > would typecheck an expression involving a literal integer, determine > that the occurrence had type Even, then evaluate the TH splice *after* > typechecking? Whereas if the occurrence had a non-ground type, it would > do something else? Yes, Typed TH already runs *after* type checking, which is what allows you to do validation based on the resulting type. The main reason why I was only proposing to do this for monomorphic values is, because, how could you possible validate a polymorphic literal? Which validation function would you use? You could ban polymorphic literals, but that'd involve eliminating most uses of polymorphic Num functions (as I mentioned as another email), which would break so much code it would render the extension unusable in "real" code. I'm open to better ideas on how to tackle this, the main reason I started this discussion is because I don't really like this "polymorphic literals fail at compile time" thing either. I just don't see how to solve it without going all dependent types on the problem. > None of this is particularly persuasive, I'm afraid. Is it worthwhile > introducing something new just to avoid having to write a quasi quote? Actually, I would be mildly ok with quasi quoters, BUT there currently is no Typed TH quasi quoter (as mentioned on the wiki page), additionally, such a quoter does not have access to Lift instances for all but a handful of datatypes until we have a more comprehensive way to generate Lift instances. I think both of these points are also highly relevant for this dicussion. > I *am* attracted to the idea of indexed classes in place of IsString/Num > > class KnownSymbol s => IsIndexedString (a :: *) (s :: Symbol) where > fromIndexedString :: a > > class KnownInteger i => IsIndexedInteger (a :: *) (i :: Integer) where > fromIndexedInteger :: a > These have a smooth upgrade path from the existing class instances via > > default fromIndexedString :: (KnownSymbol s, IsString a) => a > fromIndexedString = fromString (symbolVal (Proxy :: Proxy s)) > > default fromIndexedInteger :: (KnownInteger i, Num a) => a > fromIndexedInteger = fromInteger (integerVal (Proxy :: Proxy i)) > > and other instances can take advantage of the additional type > information. perhaps we need to bring Dependent Haskell a bit closer > before this is justifiable... The main reason I don't like the "dependent haskell" approach or your approach is how much boiler plate it introduces for beginners. ANYONE knows how to write a "String -> Maybe a" function, I barely know how to use your example and I'm very comfortable with the type families/datakinds stuff, how would "ordinary haskellers" use that? Not to mention, how would I use your "IsIndexedString" in real code? It seems you'd need at least a FunDep + cumbersome annotation? Not to mention that it still performs the conversion at runtime (I would *much* rather have a Lift based approach that just splices finished conversions into the resulting program. Cheers, Merijn -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From merijn at inconsistent.nl Mon Feb 9 09:51:38 2015 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Mon, 9 Feb 2015 10:51:38 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: Message-ID: <3437619D-A7C0-4AC2-9BE6-4AB05E0FFE86@inconsistent.nl> This sounds rather similar to C++'s constexpr functions and I would totally be in favour for that sort of thing, but I figured that reusing Typed TH would be a less cumbersome way to implement this. If people are in favour of a more elaborate approach, I'm all ears, but I fear that might be out of my league to implement :) Cheers, Merijn > On 6 Feb 2015, at 21:54, Gershom B wrote: > > I recall having some discussions with Mathieu Boespflug regarding how the static pointers work could be of use here. (And also Richard Eisenberg?) In particular, we want to demand a special property of our validation functions -- that they can safely be used at compile-time without necessarily "linking in the world" and invoking the whole of template haskell. > > A function that is "static" should in a sense have this sort of property? And so requiring that our validation functions be static seems like a useful thing from an implementation standpoint. Static semantics might also help "force the thunk" on what the correct relationship to polymorphism is. > > I guess the remaining question is then where to add them. I suppose we could stick them with special semantics on Num and IsString or the like and do it by magic? > > Alternately we could maybe have a whole class of "compile-time static functions" that we just explicitly use, and all have the property that they have type "a -> a" for some concrete "a", and that the value they are applied to is static. These functions are then applied at compile time, and forced to whnf. If they toss an error it is a compile error, otherwise they are not present in the generated code. > > There are other design variations possible, but that one feels pretty neat to me, if feasible. > > So then I could write > > foo :: Even > foo = even 6 > > for example, and get errors at compile-time. > > On top of this we could add a special way to augment Num, IsString, etc with such methods to yield the desired: > > foo :: Even > foo = 6 > > -gershom > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From mail at joachim-breitner.de Mon Feb 9 10:07:56 2015 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 09 Feb 2015 11:07:56 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: Message-ID: <1423476476.1952.7.camel@joachim-breitner.de> Hi, Am Freitag, den 06.02.2015, 15:54 -0500 schrieb Gershom B: > I guess the remaining question is then where to add them. I suppose we > could stick them with special semantics on Num and IsString or the > like and do it by magic? > speaking about magic. This reminds me of https://ghc.haskell.org/trac/ghc/ticket/9180 which would add a function staticError that, if present in the core after RULES had processed, would emit a library author defined error at compile time. So if you can implement your validation in terms of RULES, then you can have RULES insert staticError expressions in the code if validation fails. In order to be useful for your purpose, you probably need the RULES mechanism beefed up a bit, e.g. to allow implications, ?magic? predicates like "isLiteral" and some level of evaluation that might be beyond what?s possible now, and eventually lead to something like the static functions discussed in this thread, though. Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0xF0FBF51F Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From simonpj at microsoft.com Mon Feb 9 13:20:56 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 9 Feb 2015 13:20:56 +0000 Subject: Question about implementing `Typeable` (with kinds) In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C2FF7@DB3PRD3001MB020.064d.mgd.msft.net> I think just add a new constructor to EvTerm. Yes, it?s special-purpose, but the *solver* is special-purpose too. And it does mean that we know exactly what forms of evidence we can generate! Simon From: Iavor Diatchki [mailto:iavor.diatchki at gmail.com] Sent: 07 February 2015 20:11 To: Simon Peyton Jones; ghc-devs at haskell.org Subject: Question about implementing `Typeable` (with kinds) Hello, I started adding custom solving for `Typeable` constraints, to work around the problem where kind parameters were missing from the representation of types. The idea is as follows: 1. Add a new filed to `TypeRep` that remembers _kind_ parameters: TypeRep Fingerprint TyCon [TypeRep]{-kinds-} [TypeRep]{-types-} 2. Modify the constraint solver, to solve constraints like this: - Kind-polymorphic type constructors don't get `Typeable` instances on their own - GHC can solve `Typeable` constraints on _concrete uses_ of polymorphic type constructors. More precisely, GHC can solve constraints of the form `Typeable k (TC @ ks)`, as long as: (1) `k` is not a forall kind, (2) the `ks` are all concrete kinds (i.e., they have no free kind variables). This all seems fairly straight-forward, but I got stuck on the actual implementation, in particular: what `EvTerm` should I use when discharging a `Typeable` constraint? I can create a an `HsSyn` value for the required method (i.e., a function of type `Proxy# t -> TypeRep`). I can also cast this into a `Typeable` dictionary value. The issue is that I am left with an `HsSyn` expression, and not an `EvTerm`. So is there a way to treat an arbitrary expression as an `EvTerm`? In the implementation of the type-lits, I just added custom evidence, but this does not scale well (also, in that case the evidence is just a simple value, while here it is a bit more complex). Suggestions would be most appreciated! -Iavor -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at well-typed.com Mon Feb 9 13:41:43 2015 From: adam at well-typed.com (Adam Gundry) Date: Mon, 09 Feb 2015 13:41:43 +0000 Subject: Question about implementing `Typeable` (with kinds) In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C2FF7@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C2FF7@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <54D8B917.2000901@well-typed.com> On 09/02/15 13:20, Simon Peyton Jones wrote: > I think just add a new constructor to EvTerm. > > Yes, it?s special-purpose, but the **solver* *is special-purpose too. > And it does mean that we know exactly what forms of evidence we can > generate! Is there any problem in principle with allowing arbitrary HsExprs inside an EvTerm? Hopefully that would subsume the type-lits, Typeable and possible future cases. The grand plan with typechecker plugins is to make it possible to implement such special-purpose constraint solvers outside GHC itself; at the moment we can do that for equality constraints, but not very easily for other sorts of constraints (like Typeable). Adam > > *From:*Iavor Diatchki [mailto:iavor.diatchki at gmail.com] > *Sent:* 07 February 2015 20:11 > *To:* Simon Peyton Jones; ghc-devs at haskell.org > *Subject:* Question about implementing `Typeable` (with kinds) > > > > Hello, > > > > I started adding custom solving for `Typeable` constraints, to work > around the problem where kind parameters were missing from the > representation of types. > > > > The idea is as follows: > > > > 1. Add a new filed to `TypeRep` that remembers _kind_ parameters: > > > > TypeRep Fingerprint TyCon [TypeRep]{-kinds-} [TypeRep]{-types-} > > > > 2. Modify the constraint solver, to solve constraints like this: > > - Kind-polymorphic type constructors don't get `Typeable` instances > on their own > > - GHC can solve `Typeable` constraints on _/concrete uses/_ of > polymorphic type constructors. > > More precisely, GHC can solve constraints of the form `Typeable k > (TC @ ks)`, as long as: > > (1) `k` is not a forall kind, > > (2) the `ks` are all concrete kinds (i.e., they have no free kind > variables). > > > > This all seems fairly straight-forward, but I got stuck on the actual > implementation, in particular: > > > > *what `**EvTerm` should I use when discharging a `**Typeable` constraint?* > > > > I can create a an `HsSyn` value for the required method (i.e., a > function of type `Proxy# t -> TypeRep`). > > I can also cast this into a `Typeable` dictionary value. > > The issue is that I am left with an `HsSyn` expression, and not an `EvTerm`. > > > > So is there a way to treat an arbitrary expression as an `EvTerm`? > > > > In the implementation of the type-lits, I just added custom evidence, > but this does not scale well (also, in that case the evidence is just a > simple value, while here > > it is a bit more complex). > > > > Suggestions would be most appreciated! > > > > -Iavor -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From simonpj at microsoft.com Mon Feb 9 13:45:37 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 9 Feb 2015 13:45:37 +0000 Subject: Question about implementing `Typeable` (with kinds) In-Reply-To: <54D8B917.2000901@well-typed.com> References: <618BE556AADD624C9C918AA5D5911BEF562C2FF7@DB3PRD3001MB020.064d.mgd.msft.net> <54D8B917.2000901@well-typed.com> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C30B6@DB3PRD3001MB020.064d.mgd.msft.net> | Is there any problem in principle with allowing arbitrary HsExprs | inside an EvTerm? Hopefully that would subsume the type-lits, Typeable | and possible future cases. I don't think there is an objection in principle. But maybe it should be Core not HsSyn? And it's a bit tiresome for the type checker to be generating syntax trees ... it is for the desugarer to, well, desugar them. But I suggest that for the #9858 stuff we stick the current story S The grand plan with typechecker plugins is | to make it possible to implement such special-purpose constraint | solvers outside GHC itself; at the moment we can do that for equality | constraints, but not very easily for other sorts of constraints (like | Typeable). | | Adam | | | > | > *From:*Iavor Diatchki [mailto:iavor.diatchki at gmail.com] | > *Sent:* 07 February 2015 20:11 | > *To:* Simon Peyton Jones; ghc-devs at haskell.org | > *Subject:* Question about implementing `Typeable` (with kinds) | > | > | > | > Hello, | > | > | > | > I started adding custom solving for `Typeable` constraints, to work | > around the problem where kind parameters were missing from the | > representation of types. | > | > | > | > The idea is as follows: | > | > | > | > 1. Add a new filed to `TypeRep` that remembers _kind_ parameters: | > | > | > | > TypeRep Fingerprint TyCon [TypeRep]{-kinds-} [TypeRep]{-types- | } | > | > | > | > 2. Modify the constraint solver, to solve constraints like this: | > | > - Kind-polymorphic type constructors don't get `Typeable` | > instances on their own | > | > - GHC can solve `Typeable` constraints on _/concrete uses/_ of | > polymorphic type constructors. | > | > More precisely, GHC can solve constraints of the form | `Typeable | > k (TC @ ks)`, as long as: | > | > (1) `k` is not a forall kind, | > | > (2) the `ks` are all concrete kinds (i.e., they have no free | > kind variables). | > | > | > | > This all seems fairly straight-forward, but I got stuck on the | actual | > implementation, in particular: | > | > | > | > *what `**EvTerm` should I use when discharging a `**Typeable` | > constraint?* | > | > | > | > I can create a an `HsSyn` value for the required method (i.e., a | > function of type `Proxy# t -> TypeRep`). | > | > I can also cast this into a `Typeable` dictionary value. | > | > The issue is that I am left with an `HsSyn` expression, and not an | `EvTerm`. | > | > | > | > So is there a way to treat an arbitrary expression as an `EvTerm`? | > | > | > | > In the implementation of the type-lits, I just added custom | evidence, | > but this does not scale well (also, in that case the evidence is | just | > a simple value, while here | > | > it is a bit more complex). | > | > | > | > Suggestions would be most appreciated! | > | > | > | > -Iavor | | | -- | Adam Gundry, Haskell Consultant | Well-Typed LLP, http://www.well-typed.com/ From adam at well-typed.com Mon Feb 9 16:44:49 2015 From: adam at well-typed.com (Adam Gundry) Date: Mon, 09 Feb 2015 16:44:49 +0000 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> <75993583-3304-4CBF-B58D-FE58A2DA6233@inconsistent.nl> <54D524AA.5070608@well-typed.com> Message-ID: <54D8E401.3060606@well-typed.com> Hi Merijn, Thanks for persevering with explaining things to me. :-) On 09/02/15 09:47, Merijn Verstraaten wrote: >> On 6 Feb 2015, at 21:31, Adam Gundry wrote: >> What does "all monomorphic cases" mean? Is the idea what GHC would >> typecheck an expression involving a literal integer, determine that >> the occurrence had type Even, then evaluate the TH splice *after* >> typechecking? Whereas if the occurrence had a non-ground type, it >> would do something else? > > Yes, Typed TH already runs *after* type checking, which is what > allows you to do validation based on the resulting type. The main > reason why I was only proposing to do this for monomorphic values is, > because, how could you possible validate a polymorphic literal? Which > validation function would you use? > > You could ban polymorphic literals, but that'd involve eliminating > most uses of polymorphic Num functions (as I mentioned as another > email), which would break so much code it would render the extension > unusable in "real" code. I'm open to better ideas on how to tackle > this, the main reason I started this discussion is because I don't > really like this "polymorphic literals fail at compile time" thing > either. I just don't see how to solve it without going all dependent > types on the problem. In the absence of a coherent story for polymorphism, I think the right thing to do is to be able to specify a particular validator, rather than try to have type inference determine a monomorphic type and otherwise get stuck... >> None of this is particularly persuasive, I'm afraid. Is it >> worthwhile introducing something new just to avoid having to write >> a quasi quote? > > Actually, I would be mildly ok with quasi quoters, BUT there > currently is no Typed TH quasi quoter (as mentioned on the wiki > page), additionally, such a quoter does not have access to Lift > instances for all but a handful of datatypes until we have a more > comprehensive way to generate Lift instances. I think both of these > points are also highly relevant for this dicussion. ...so is the right solution to introduce Typed TH quasiquoters for expressions? Sorry, I presumed such a thing existed, as Typed TH is rather regrettably underdocumented. Is there any particular difficulty with them, or is it just a Small Matter of Programming? I think the lack of Lift instances is a separate problem; while it looks like 7.10 will be better in this respect and dataToExpQ goes a fair way, I agree that making them easier to generate would be nice. Perhaps a generics-based default method combined with DeriveAnyClass would make "deriving Lift" possible? Adam -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From iavor.diatchki at gmail.com Mon Feb 9 17:23:03 2015 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Mon, 9 Feb 2015 09:23:03 -0800 Subject: Question about implementing `Typeable` (with kinds) In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C30B6@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C2FF7@DB3PRD3001MB020.064d.mgd.msft.net> <54D8B917.2000901@well-typed.com> <618BE556AADD624C9C918AA5D5911BEF562C30B6@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Hello, Like Adam, I think it'd be nice to allow for general HsSyn (or, perhaps, Core) in EvTerm. In the meantime, I'll add another constructor specific for `Typeable`, and deal with it in the desugarer. -Iavor On Mon, Feb 9, 2015 at 5:45 AM, Simon Peyton Jones wrote: > | Is there any problem in principle with allowing arbitrary HsExprs > | inside an EvTerm? Hopefully that would subsume the type-lits, Typeable > | and possible future cases. > > I don't think there is an objection in principle. But maybe it should be > Core not HsSyn? And it's a bit tiresome for the type checker to be > generating syntax trees ... it is for the desugarer to, well, desugar them. > > But I suggest that for the #9858 stuff we stick the current story > > S > > The grand plan with typechecker plugins is > | to make it possible to implement such special-purpose constraint > | solvers outside GHC itself; at the moment we can do that for equality > | constraints, but not very easily for other sorts of constraints (like > | Typeable). > | > | Adam > | > | > | > > | > *From:*Iavor Diatchki [mailto:iavor.diatchki at gmail.com] > | > *Sent:* 07 February 2015 20:11 > | > *To:* Simon Peyton Jones; ghc-devs at haskell.org > | > *Subject:* Question about implementing `Typeable` (with kinds) > | > > | > > | > > | > Hello, > | > > | > > | > > | > I started adding custom solving for `Typeable` constraints, to work > | > around the problem where kind parameters were missing from the > | > representation of types. > | > > | > > | > > | > The idea is as follows: > | > > | > > | > > | > 1. Add a new filed to `TypeRep` that remembers _kind_ parameters: > | > > | > > | > > | > TypeRep Fingerprint TyCon [TypeRep]{-kinds-} [TypeRep]{-types- > | } > | > > | > > | > > | > 2. Modify the constraint solver, to solve constraints like this: > | > > | > - Kind-polymorphic type constructors don't get `Typeable` > | > instances on their own > | > > | > - GHC can solve `Typeable` constraints on _/concrete uses/_ of > | > polymorphic type constructors. > | > > | > More precisely, GHC can solve constraints of the form > | `Typeable > | > k (TC @ ks)`, as long as: > | > > | > (1) `k` is not a forall kind, > | > > | > (2) the `ks` are all concrete kinds (i.e., they have no free > | > kind variables). > | > > | > > | > > | > This all seems fairly straight-forward, but I got stuck on the > | actual > | > implementation, in particular: > | > > | > > | > > | > *what `**EvTerm` should I use when discharging a `**Typeable` > | > constraint?* > | > > | > > | > > | > I can create a an `HsSyn` value for the required method (i.e., a > | > function of type `Proxy# t -> TypeRep`). > | > > | > I can also cast this into a `Typeable` dictionary value. > | > > | > The issue is that I am left with an `HsSyn` expression, and not an > | `EvTerm`. > | > > | > > | > > | > So is there a way to treat an arbitrary expression as an `EvTerm`? > | > > | > > | > > | > In the implementation of the type-lits, I just added custom > | evidence, > | > but this does not scale well (also, in that case the evidence is > | just > | > a simple value, while here > | > > | > it is a bit more complex). > | > > | > > | > > | > Suggestions would be most appreciated! > | > > | > > | > > | > -Iavor > | > | > | -- > | Adam Gundry, Haskell Consultant > | Well-Typed LLP, http://www.well-typed.com/ > -------------- next part -------------- An HTML attachment was scrubbed... URL: From petersen at fedoraproject.org Mon Feb 9 21:49:15 2015 From: petersen at fedoraproject.org (Jens Petersen) Date: Mon, 9 Feb 2015 22:49:15 +0100 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: References: Message-ID: On 27 January 2015 at 01:13, Austin Seipp wrote: > We are pleased to announce the second release candidate for GHC 7.10.1: > Thanks, I updated my Fedora ghc-7.10 Copr repo to RC2: https://copr.fedoraproject.org/coprs/petersen/ghc-7.10/ (The build is currently only for Rawhide but I think it should work on Fedora 21 too.) Jens -------------- next part -------------- An HTML attachment was scrubbed... URL: From iavor.diatchki at gmail.com Tue Feb 10 01:20:39 2015 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Mon, 9 Feb 2015 17:20:39 -0800 Subject: Trouble pushing changes? Message-ID: Hello, Today I made some more progress with the implementation of `Typebable with kinds`. In the process, I had to update one line in the `deepseq` package, because it has code to `rnf` `TypeReps`, which now have an extra field. I made a separate branch in `deep-seq` where I was going to push the change, but when I try to do so I get the following error: git push -u origin typeable-with-kinds:typeable-with-kinds Counting objects: 30, done. Delta compression using up to 8 threads. Compressing objects: 100% (3/3), done. Writing objects: 100% (4/4), 377 bytes | 0 bytes/s, done. Total 4 (delta 2), reused 0 (delta 0) remote: W refs/heads/typeable-with-kinds packages/deepseq diatchki DENIED by refs/.* remote: error: hook declined to update refs/heads/typeable-with-kinds To ssh://git at git.haskell.org/packages/deepseq.git ! [remote rejected] typeable-with-kinds -> typeable-with-kinds (hook declined) error: failed to push some refs to 'ssh:// git at git.haskell.org/packages/deepseq.git' Any ideas what that's about? Perhaps, it is simply that I don't have permission to push to `deep-seq`? -Iavor -------------- next part -------------- An HTML attachment was scrubbed... URL: From mark.lentczner at gmail.com Tue Feb 10 04:30:59 2015 From: mark.lentczner at gmail.com (Mark Lentczner) Date: Mon, 9 Feb 2015 20:30:59 -0800 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: <87h9v4vhcp.fsf@gnu.org> References: <87h9v4vhcp.fsf@gnu.org> Message-ID: I will have 7.10 RC2 and 7.8.4 mac bindist up tonight - but I need help testing them on various configurations before we declare them "good". I'll post again when they are up. - Mark ? -------------- next part -------------- An HTML attachment was scrubbed... URL: From merijn at inconsistent.nl Tue Feb 10 08:41:22 2015 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Tue, 10 Feb 2015 09:41:22 +0100 Subject: Proposal: ValidateMonoLiterals - Initial bikeshed discussion In-Reply-To: <54D8E401.3060606@well-typed.com> References: <5F203379-8242-4137-AFA2-91289F2119B6@inconsistent.nl> <618BE556AADD624C9C918AA5D5911BEF562C0405@DB3PRD3001MB020.064d.mgd.msft.net> <7BFEA344-05CB-4663-A594-9C4CF25E1D04@inconsistent.nl> <54D4BF98.3020104@well-typed.com> <75993583-3304-4CBF-B58D-FE58A2DA6233@inconsistent.nl> <54D524AA.5070608@well-typed.com> <54D8E401.3060606@well-typed.com> Message-ID: <44E08944-D81C-4196-B919-5ED217AA18FB@inconsistent.nl> Hi Adam, > On 9 Feb 2015, at 17:44, Adam Gundry wrote: > In the absence of a coherent story for polymorphism, I think the right > thing to do is to be able to specify a particular validator, rather than > try to have type inference determine a monomorphic type and otherwise > get stuck... I was planning to write a TH library for this sort of thing anyway, I was just curious if people had better solutions for the polymorphic story/solutions to take away this annoyance. But maybe a better solution in this direction is Gershom's solution to allow proper compile time functions. > ...so is the right solution to introduce Typed TH quasiquoters for > expressions? Sorry, I presumed such a thing existed, as Typed TH is > rather regrettably underdocumented. Is there any particular difficulty > with them, or is it just a Small Matter of Programming? I don't actually know the answer to this, it was one of the questions I was hoping to answer in this discussion :) > I think the lack of Lift instances is a separate problem; while it looks > like 7.10 will be better in this respect and dataToExpQ goes a fair way, > I agree that making them easier to generate would be nice. Perhaps a > generics-based default method combined with DeriveAnyClass would make > "deriving Lift" possible? It's not directly related to whatever solution we pick, but I do think it's an important issue. There's currently a TH library for deriving them, but from what I've seen about writing them by hand I don't understand how GHC couldn't trivially generate them for most (all?) ADTs. Cheers, Merijn -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From hvriedel at gmail.com Tue Feb 10 08:47:27 2015 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Tue, 10 Feb 2015 09:47:27 +0100 Subject: Trouble pushing changes? In-Reply-To: (Iavor Diatchki's message of "Mon, 9 Feb 2015 17:20:39 -0800") References: Message-ID: <87386e17c0.fsf@gmail.com> On 2015-02-10 at 02:20:39 +0100, Iavor Diatchki wrote: [...] > Any ideas what that's about? Perhaps, it is simply that I don't have > permission to push to `deep-seq`? You have to push to GitHub's upstream of deepseq: $ awk '/^libraries\/deepseq/ { print $4 }' packages ssh://git at github.com/haskell/deepseq.git you can do that ad-hoc by git push ssh://git at github.com/haskell/deepseq.git HEAD:master from inside libraries/deepseq it's also mentioned as a comment in the ./packages (as well as on the GHC Wiki, I think) file that some subrepos have to be pushed somewhere else Cheers, hvr From simonpj at microsoft.com Tue Feb 10 14:52:22 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 10 Feb 2015 14:52:22 +0000 Subject: LLVM Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C4797@DB3PRD3001MB020.064d.mgd.msft.net> I'm getting this on Linux (Ubuntu). How do I get a newer version of llvm? Simon : You are using an old version of LLVM that isn't supported anymore! We will try though... /usr/bin/opt: /tmp/ghc451_0/ghc451_1.ll:7:6: error: expected type !0 = !{!"top", i8* null} ^ -------------- next part -------------- An HTML attachment was scrubbed... URL: From austin at well-typed.com Tue Feb 10 14:54:49 2015 From: austin at well-typed.com (Austin Seipp) Date: Tue, 10 Feb 2015 08:54:49 -0600 Subject: LLVM In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C4797@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C4797@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Hurgh. My fault. I was testing ben's new patch with a newer LLVM and got it working, but didn't test the case of not having it installed. :) Will try to fix shortly. Was this just from running validate? On Tuesday, February 10, 2015, Simon Peyton Jones wrote: > I?m getting this on Linux (Ubuntu). How do I get a newer version of > llvm? > > Simon > > > > : > > You are using an old version of LLVM that isn't supported anymore! > > We will try though... > > /usr/bin/opt: /tmp/ghc451_0/ghc451_1.ll:7:6: error: expected type > > !0 = !{!"top", i8* null} > > ^ > -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From mark.lentczner at gmail.com Tue Feb 10 15:01:08 2015 From: mark.lentczner at gmail.com (Mark Lentczner) Date: Tue, 10 Feb 2015 07:01:08 -0800 Subject: MAC builds of 7.8.4 and 7.10.1 RC2 Message-ID: I have built "in the official manner" both GHC 7.8.4 and GHC 7.10.1 rc2 from sources. You can find them here: http://www.ozonehouse.com/mark/platform/ They need some "doesn't crash out of the box" testing on a few OS X systems before I think we should declare them good and put them on the download page. Can you help out? Basic instructions to install a bindist in a local, isolated area (so you don't clobber your system GHC installation): mkdir test-ghc cd test-ghc tar xf $binddist_tar_file cd ghc* configure --prefix=`cd ..; pwd` make install cd .. Let me know if that works - and what version of OS X you used. - Mark -------------- next part -------------- An HTML attachment was scrubbed... URL: From george.colpitts at gmail.com Tue Feb 10 15:40:42 2015 From: george.colpitts at gmail.com (George Colpitts) Date: Tue, 10 Feb 2015 11:40:42 -0400 Subject: MAC builds of 7.8.4 and 7.10.1 RC2 In-Reply-To: References: Message-ID: I am on 10.10.2 and so far it works. I will do more testing this evening. Issues - With this version I still see bug https://ghc.haskell.org/trac/ghc/ticket/10053. Do you see this on your machine? - As I've noted in https://ghc.haskell.org/trac/ghc/ticket/9586 I don't think this ticket (BPP/FTP proposal) should be closed as it says "We are currently constructing a poll and summaries of two possible plans of action that will go out in the next day or so. Based on the results of that poll, which will likely run until the 28th or so, to give folks a couple of weeks to respond, Simon Peyton Jones and Simon Marlow will come to a decision on how we are going to proceed for 7.10." But this issue doesn't show on ?https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.1and since the issue still appears to be open the referenced Status page doesn't give an indication of the true status of the release. Changing the status of this ticket to open would make the 7.10.1 Status page more accurate wrt where we are on 7.10.1 - Is there a preferred compiler to be used, i.e. Apple gcc or gnu gcc? If the former perhaps the installation instructions should suggest something like "export PATH=/usr/bin:$PATH" ? - It might be good to document how to remove previous versions of RC2. I did the following: - rm -fr /usr/local/lib/ghc-7.10.0.20150123/package.conf.d - bash-3.2$ rm -fr /Users/gcolpitts/.ghc/x86_64-darwin-7.10.0.20150123/package.conf.d - bash-3.2$ rm -fr /usr/local/lib/ghc* - bash-3.2$ rm -fr /usr/local/bin/ghc* - I wanted to install in /usr/local/bin and didn't follow your instructions exactly. After unzipping and changing into the directory I did the following - export PATH=/usr/bin:$PATH - ./configure - make install On Tue, Feb 10, 2015 at 11:01 AM, Mark Lentczner wrote: > I have built "in the official manner" both GHC 7.8.4 and GHC 7.10.1 rc2 > from sources. You can find them here: > > http://www.ozonehouse.com/mark/platform/ > > They need some "doesn't crash out of the box" testing on a few OS X > systems before I think we should declare them good and put them on the > download page. > > Can you help out? > > Basic instructions to install a bindist in a local, isolated area (so you > don't clobber your system GHC installation): > > mkdir test-ghc > cd test-ghc > tar xf $binddist_tar_file > cd ghc* > configure --prefix=`cd ..; pwd` > make install > cd .. > > Let me know if that works - and what version of OS X you used. > > - Mark > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Feb 10 15:50:02 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 10 Feb 2015 15:50:02 +0000 Subject: GHC 7.10 Prelude: we need your opinion Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C4A1C@DB3PRD3001MB020.064d.mgd.msft.net> Haskell Friends This email asks for your help in deciding how to proceed with some Prelude changes in GHC 7.10. Please read on, but all the info is also at the survey link, here: http://goo.gl/forms/XP1W2JdfpX. Deadline is 21 Feb. The ?Core Libraries Committee (CLC) is responsible for developing the core libraries that ship with GHC. This is an important but painstaking task, and we owe the CLC a big vote of thanks for taking it on. For over a year the CLC has been working on integrating the Foldable and Traversable classes (shipped in base in GHC 7.8) into the core libraries, and into the Prelude in particular. Detailed planning for GHC 7.10 started in the autumn of 2014, and the CLC went ahead with this integration. Then we had a failure of communication. As these changes affect the Prelude, which is in scope for all users of Haskell, these changes should be held to a higher bar than the regular libraries@ review process. However, the Foldable/Traversable changes were not particularly well signposted. Many people have only recently woken up to them, and some have objected (both in principle and detail). This is an extremely unfortunate situation. On the one hand we are at RC2 for GHC 7.10, so library authors have invested effort in updating their libraries to the new Prelude. On the other, altering the Prelude is in effect altering the language, something we take pretty seriously. We should have had this debate back in 2014, but here we are, and it is unproductive to argue about whose fault it is. We all share responsibility. We need to decide what to do now. A small group of us met by Skype and we've decided to do this: ? Push back GHC 7.10's release by at least a month, to late March. This delay also gives us breathing space to address an unrelated show-stopping bug, Trac #9858. ? Invite input from the Haskell community on which of two approaches to adopt (this survey). The main questions revolve around impact on the Haskell ecosystem (commercial applications, teaching, libraries, etc etc), so we want to ask your opinion rather than guess it. ? Ask Simon Marlow and Simon Peyton Jones to decide which approach to follow for GHC 7.10. Wiki pages have been created summarizing these two primary alternatives, including many more points and counter-points and technical details: ? Overall summary: https://ghc.haskell.org/trac/ghc/wiki/Prelude710 ? Details of Plan List: https://ghc.haskell.org/trac/ghc/wiki/Prelude710/List ? Details of Plan FTP: https://ghc.haskell.org/trac/ghc/wiki/Prelude710/FTP This survey invites your input on which plan we should follow. Would you please ? Read the details of the alternative plans on the three wiki pages above ? Add your response to the survey Please do read the background. Well-informed responses will help. Thank you! DEADLINE: 21 February 2015 Simon PJ -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Feb 10 16:05:21 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 10 Feb 2015 16:05:21 +0000 Subject: [Haskell-cafe] GHC 7.10 Prelude: we need your opinion In-Reply-To: <4445561423583958@web8j.yandex.ru> References: <618BE556AADD624C9C918AA5D5911BEF562C4A1C@DB3PRD3001MB020.064d.mgd.msft.net> <4445561423583958@web8j.yandex.ru> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C4AE6@DB3PRD3001MB020.064d.mgd.msft.net> | What were the objections? Especially the principle ones? Please read the info pages, which set out the arguments quite carefully. Also, I spammed several email lists to ensure broad coverage, but it'd be best to debate on the libraries at haskell.org, rather than reply-to-all; that's what it's for. (Which I failed to send the announcement to! I'll fix that.) Simon | -----Original Message----- | From: Miguel Mitrofanov [mailto:miguelimo38 at yandex.ru] | Sent: 10 February 2015 15:59 | To: Simon Peyton Jones; haskell at haskell.org; Haskell Cafe (haskell- | cafe at haskell.org); GHC users; ghc-devs at haskell.org | Subject: Re: [Haskell-cafe] GHC 7.10 Prelude: we need your opinion | | What were the objections? Especially the principle ones? | | 10.02.2015, 18:51, "Simon Peyton Jones" : | > Haskell Friends | > | > This email asks for your help in deciding how to proceed with some | Prelude changes in GHC 7.10.? Please read on, but all the info is also | at the survey link, here: http://goo.gl/forms/XP1W2JdfpX.?? Deadline | is 21 Feb. | > | > The ?Core Libraries Committee (CLC) is responsible for developing the | core libraries that ship with GHC. This is an important but | painstaking task, and we owe the CLC a big vote of thanks for taking | it on. | > | > For over a year the CLC has been working on integrating the Foldable | and Traversable classes (shipped in base in GHC 7.8) into the core | libraries, and into the Prelude in particular. Detailed planning for | GHC 7.10 started in the autumn of 2014, and the CLC went ahead with | this integration. | > | > Then we had a failure of communication.? As these changes affect the | Prelude, which is in scope for all users of Haskell, these changes | should be held to a higher bar than the regular libraries@ review | process.? However, the Foldable/Traversable changes were not | particularly well signposted. Many people have only recently woken up | to them, and some have objected (both in principle and detail). | > | > This is an extremely unfortunate situation. On the one hand we are | at RC2 for GHC 7.10, so library authors have invested effort in | updating their libraries to the new Prelude. On the other, altering | the Prelude is in effect altering the language, something we take | pretty seriously. We should have had this debate back in 2014, but | here we are, and it is unproductive to argue about whose fault it is. | We all share responsibility. | > | > We need to decide what to do now. A small group of us met by Skype | and we've decided to do this: | > | > ????????? Push back GHC 7.10's release by at least a month, to late | March.? This delay also gives us breathing space to address an | unrelated show-stopping bug, Trac #9858. | > | > ????????? Invite input from the Haskell community on which of two | approaches to adopt (this survey).? The main questions revolve around | impact on the Haskell ecosystem (commercial applications, teaching, | libraries, etc etc), so we want to ask your opinion rather than guess | it. | > | > ????????? Ask Simon Marlow and Simon Peyton Jones to decide which | approach to follow for GHC 7.10. | > | > Wiki pages have been created summarizing these two primary | alternatives, including many more points and counter-points and | technical details: | > | > ????????? Overall summary: | https://ghc.haskell.org/trac/ghc/wiki/Prelude710 | > | > ????????? Details of Plan List: | https://ghc.haskell.org/trac/ghc/wiki/Prelude710/List | > | > ????????? Details of Plan FTP: | https://ghc.haskell.org/trac/ghc/wiki/Prelude710/FTP | > | > This survey invites your input on which plan we should follow. Would | you please | > | > ????????? Read the details of the alternative plans on the three | wiki pages above | > | > ????????? Add your response to the survey | > | > Please do read the background.? Well-informed responses will | help.? Thank you! | > | > DEADLINE: 21 February 2015 | > | > Simon PJ | > | > , | > | > _______________________________________________ | > Haskell-Cafe mailing list | > Haskell-Cafe at haskell.org | > http://www.haskell.org/mailman/listinfo/haskell-cafe From tuncer.ayaz at gmail.com Tue Feb 10 17:50:38 2015 From: tuncer.ayaz at gmail.com (Tuncer Ayaz) Date: Tue, 10 Feb 2015 18:50:38 +0100 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: References: Message-ID: On Sat, Feb 7, 2015 at 2:01 PM, Tuncer Ayaz wrote: > On Wed, Jan 28, 2015 at 11:45 AM, Tuncer Ayaz wrote: > > With all three listed build.mk settings, I'm unable to make install: [...] > > Makefile:71: recipe for target 'install' failed > > make: *** [install] Error 2 > > So, am I alone in encountering this issue with RC2 but not RC1? Didn't figure out the failure's cause, but the next clean build was successful. From mietek at bak.io Tue Feb 10 17:54:52 2015 From: mietek at bak.io (=?iso-8859-1?Q?Mi=EBtek_Bak?=) Date: Tue, 10 Feb 2015 17:54:52 +0000 Subject: MAC builds of 7.8.4 and 7.10.1 RC2 In-Reply-To: References: Message-ID: <214AC80A-A714-4201-96DD-D6E0B988F224@bak.io> Thanks, Mark. I?ve successfully installed both version on OS X 10.9.5. I?ve also made both versions available in Halcyon. https://halcyon.sh/ -- Mi?tek On 2015-02-10, at 15:01, Mark Lentczner wrote: > I have built "in the official manner" both GHC 7.8.4 and GHC 7.10.1 rc2 from sources. You can find them here: > > http://www.ozonehouse.com/mark/platform/ > > They need some "doesn't crash out of the box" testing on a few OS X systems before I think we should declare them good and put them on the download page. > > Can you help out? > > Basic instructions to install a bindist in a local, isolated area (so you don't clobber your system GHC installation): > > mkdir test-ghc > cd test-ghc > tar xf $binddist_tar_file > cd ghc* > configure --prefix=`cd ..; pwd` > make install > cd .. > > Let me know if that works - and what version of OS X you used. > > - Mark > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 4203 bytes Desc: not available URL: From iavor.diatchki at gmail.com Tue Feb 10 18:01:39 2015 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Tue, 10 Feb 2015 10:01:39 -0800 Subject: Trouble pushing changes? In-Reply-To: <87386e17c0.fsf@gmail.com> References: <87386e17c0.fsf@gmail.com> Message-ID: Aha, that makes sense, thanks! -Iavor On Tue, Feb 10, 2015 at 12:47 AM, Herbert Valerio Riedel wrote: > On 2015-02-10 at 02:20:39 +0100, Iavor Diatchki wrote: > > [...] > > > Any ideas what that's about? Perhaps, it is simply that I don't have > > permission to push to `deep-seq`? > > You have to push to GitHub's upstream of deepseq: > > $ awk '/^libraries\/deepseq/ { print $4 }' packages > ssh://git at github.com/haskell/deepseq.git > > you can do that ad-hoc by > > git push ssh://git at github.com/haskell/deepseq.git HEAD:master > > from inside libraries/deepseq > > it's also mentioned as a comment in the ./packages (as well as on the > GHC Wiki, I think) file that some subrepos have to be pushed somewhere > else > > > Cheers, > hvr > -------------- next part -------------- An HTML attachment was scrubbed... URL: From iavor.diatchki at gmail.com Tue Feb 10 18:14:12 2015 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Tue, 10 Feb 2015 10:14:12 -0800 Subject: Trouble pushing changes? In-Reply-To: References: <87386e17c0.fsf@gmail.com> Message-ID: On further thought, would it be hard to update whatever hook is checking for this, to give a bit more detail? If it is easy, we could update the message to say something like ("You should not push here, please push to URL instead"). It is nice to have documentation on the wiki, but it is even better if the system is self-documenting, so one does not have to go searching on the Internet. On Tue, Feb 10, 2015 at 10:01 AM, Iavor Diatchki wrote: > Aha, that makes sense, thanks! > -Iavor > > On Tue, Feb 10, 2015 at 12:47 AM, Herbert Valerio Riedel < > hvriedel at gmail.com> wrote: > >> On 2015-02-10 at 02:20:39 +0100, Iavor Diatchki wrote: >> >> [...] >> >> > Any ideas what that's about? Perhaps, it is simply that I don't have >> > permission to push to `deep-seq`? >> >> You have to push to GitHub's upstream of deepseq: >> >> $ awk '/^libraries\/deepseq/ { print $4 }' packages >> ssh://git at github.com/haskell/deepseq.git >> >> you can do that ad-hoc by >> >> git push ssh://git at github.com/haskell/deepseq.git HEAD:master >> >> from inside libraries/deepseq >> >> it's also mentioned as a comment in the ./packages (as well as on the >> GHC Wiki, I think) file that some subrepos have to be pushed somewhere >> else >> >> >> Cheers, >> hvr >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hvriedel at gmail.com Tue Feb 10 18:53:02 2015 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Tue, 10 Feb 2015 19:53:02 +0100 Subject: Trouble pushing changes? In-Reply-To: (Iavor Diatchki's message of "Tue, 10 Feb 2015 10:14:12 -0800") References: <87386e17c0.fsf@gmail.com> Message-ID: <87386dzjht.fsf@gmail.com> On 2015-02-10 at 19:14:12 +0100, Iavor Diatchki wrote: > On further thought, would it be hard to update whatever hook is checking > for this, to give a bit more detail? If it is easy, we could update the > message to say something like ("You should not push here, please push to > URL instead"). Tbh, I don't know how easy it is; we use Gitolite (v2) for handling access control, and I'd have to investigate if there's a way to customize the access-denied message in useful way (as a function of git-repo and maybe ref-name)... I'd have to investigate, or have somebody with more experience tell me... :) Cheers, hvr From carter.schonwald at gmail.com Tue Feb 10 21:02:48 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 10 Feb 2015 16:02:48 -0500 Subject: MAC builds of 7.8.4 and 7.10.1 RC2 In-Reply-To: References: Message-ID: hey Mark, what configure flags etc did you do for the 7.8.4 build? I'd like to know so i can compare my build vs yours! thanks! -Carter On Tue, Feb 10, 2015 at 10:01 AM, Mark Lentczner wrote: > I have built "in the official manner" both GHC 7.8.4 and GHC 7.10.1 rc2 > from sources. You can find them here: > > http://www.ozonehouse.com/mark/platform/ > > They need some "doesn't crash out of the box" testing on a few OS X > systems before I think we should declare them good and put them on the > download page. > > Can you help out? > > Basic instructions to install a bindist in a local, isolated area (so you > don't clobber your system GHC installation): > > mkdir test-ghc > cd test-ghc > tar xf $binddist_tar_file > cd ghc* > configure --prefix=`cd ..; pwd` > make install > cd .. > > Let me know if that works - and what version of OS X you used. > > - Mark > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From austin at well-typed.com Tue Feb 10 23:17:36 2015 From: austin at well-typed.com (Austin Seipp) Date: Tue, 10 Feb 2015 17:17:36 -0600 Subject: GHC Weekly News - 2015/02/10 Message-ID: Hi *, Welcome! This is the first GHC Weekly news of February 2015. You might be wondering what happened to the last one. Well, your author was just in New York for the past week attending [http://www.composeconference.org Compose Conference], making friends and talking a lot about Haskell (luckily we missed a snow storm that may have messed it up quite badly!) The conference was great. I got to have some interesting discussions about GHC and Haskell with many friendly faces from all around at an incredibly well run conference with a stellar set of people. Many thanks to NY Haskell (organizing), Spotify (hosting space), and to all the speakers for a wonderful time. (And of course, your editor would like to thank his employer Well-Typed for sending him!) But now, since your author has returned, GHC HQ met back up this week for some discussion, with some regularly scheduled topics. For the most part it was a short meeting this week - our goals are pretty well identified: - GHC HQ and the Core Libraries Committee have posted a survey on the future of the 7.10 prelude and the FTP/BBP discussion. The deadline is February 20th, so please vote if the discussion is of interest to you. Simon Peyton-Jones and Simon Marlow will be making the final decision. https://www.haskell.org/pipermail/haskell-cafe/2015-February/118095.html - It's likely GHC HQ will do a third 7.10.1 Release Candidate at the very end of February after the votes are included. We missed some patches in RC2 (such as Phab:D347) and incorporated even more bugfixes, so this is worth a test drive by users. - For the most part, things for 7.10 have been going very smoothly other than the debates and a few bugs trickling in - there has not been much ticket activity the past two weeks, so things feel pretty good right now. Austin will mostly be focused on shipping 7.10 and keeping the normal review/patch/triaging cycles going until it's done. We're on track to fix all the major bugs we've assigned (see milestone:7.10.1). Since my last post, we've also had other random assorted chatter on the mailing lists by the dev team: - In light of a recent large bug in GHC which can be used to derive `unsafeCoerce`, GHC HQ '''has decided to push back the 7.10 release a bit longer to about March''', in order to fix this bug and ferret out the little fallout afterwords. It turns out this isn't a simple bug to fix, but luckily a fix is being worked on already. https://www.haskell.org/pipermail/ghc-devs/2015-January/008189.html - Luckily, Iavor has started work on fixing this nasty bug, and had a few questions for the list: https://www.haskell.org/pipermail/ghc-devs/2015-February/008269.html - Iavor Diatchki has raised a new topic about a simpler OverloadedRecordsField proposal. Adam swooped in to address some points about the design. https://www.haskell.org/pipermail/ghc-devs/2015-January/008183.html - Herbert Valerio Riedel posted about a huge (76x) regression between GHC 7.11 and GHC 7.10, but strangely nobody has picked up as to why this is the case yet! https://www.haskell.org/pipermail/ghc-devs/2015-January/008207.html - David Feuer has a question: why is `undefined` so special? In particular, it seems as if `undefined` can be specially used as a value with a type of kind `#` as well as `*`. It turns out GHC has a special notion of subkinding, and `undefined` has a type more special than meets the eye which allows this, as Adam Gundry replied. https://www.haskell.org/pipermail/ghc-devs/2015-February/008222.html - Merijn Verstraaten has started up a discussion about a new proposal of his, ValidateMonoLiterals. The proposal revolves around the idea of using GHC to enforce compile-time constraints on monomorphic literals, whose type may have invariants enforced on them. While this is doable with Template Haskell, Merijn would like to see something inside GHC instead. https://www.haskell.org/pipermail/ghc-devs/2015-February/008239.html - David Feuer asked: can we merge `FlexibleContexts` with `FlexibleInstances`? The proposal seems to be relatively undiscussed at the moment with a neutral future, but perhaps someone would like to chime in on this minor issue. https://www.haskell.org/pipermail/ghc-devs/2015-February/008245.html - Greg Weber opened up a discussion about 'Restricted Template Haskell', which would hopefully make it easier for users to see what a TH computation is actually doing. It turns out - as noted by Simon - that Typed Template Haskell is perhaps closer to what Greg wants. The proposal and discussion then resulted in us realising that the typed TH documentation is rather poor! Hopefully Greg or someone can swing in to improve things. https://www.haskell.org/pipermail/ghc-devs/2015-February/008232.html Closed tickets the past two weeks include: #10028, #10040, #10031, #9935, #9928, #2615, #10048, #10057, #10054, #10060, #10017, #10038, #9937, #8796, #10030, #9988, #10066, #7425, #7424, #7434, #10041, #2917, #4834, #10004, #10050, #10020, #10036, #9213, and #10047. -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From mark.lentczner at gmail.com Wed Feb 11 06:16:23 2015 From: mark.lentczner at gmail.com (Mark Lentczner) Date: Tue, 10 Feb 2015 22:16:23 -0800 Subject: MAC builds of 7.8.4 and 7.10.1 RC2 In-Reply-To: References: Message-ID: My build procedure is very minimal: export MACOSX_DEPLOYMENT_TARGET=10.6 ./configure 2>&1 | tee ../conf.log cat > mk/build.mk <&1 | tee ../make.log time make binary-dist 2>&1 | tee ../bd.log That is all! ? -------------- next part -------------- An HTML attachment was scrubbed... URL: From f at mazzo.li Wed Feb 11 10:26:17 2015 From: f at mazzo.li (Francesco Mazzoli) Date: Wed, 11 Feb 2015 11:26:17 +0100 Subject: Anonymous FFI calls Message-ID: Hi, I am in a situation where it would be very useful to call C functions without an explicit FFI import. For example, I'd like to be able to do (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 instead of declaring the foreign import explicitely at the top level. Is there a way to do this or to achieve similar results in some other way? If not, I imagine it would be easy to implement such a facility in GHC, given that the code implementing calling to C functions must already be present to implement "proper" FFI imports. I think such an addition would be useful in many cases. Thanks, Francesco From simonpj at microsoft.com Wed Feb 11 10:40:19 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 11 Feb 2015 10:40:19 +0000 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> This may be relevant. http://www.cse.unsw.edu.au/~chak/papers/CMCK14.html Manuel gave a talk about something like this at the Haskell Symposium. Simon | -----Original Message----- | From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf | Of Francesco Mazzoli | Sent: 11 February 2015 10:26 | To: haskell; ghc-devs at haskell.org | Subject: [Haskell-cafe] Anonymous FFI calls | | Hi, | | I am in a situation where it would be very useful to call C functions | without an explicit FFI import. For example, I'd like to be able to | do | | (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 | | instead of declaring the foreign import explicitely at the top level. | | Is there a way to do this or to achieve similar results in some other | way? | | If not, I imagine it would be easy to implement such a facility in | GHC, given that the code implementing calling to C functions must | already be present to implement "proper" FFI imports. I think such an | addition would be useful in many cases. | | Thanks, | Francesco | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe at haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe From f at mazzo.li Wed Feb 11 15:18:43 2015 From: f at mazzo.li (Francesco Mazzoli) Date: Wed, 11 Feb 2015 16:18:43 +0100 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Hi Simon, Thanks for the reply. The work on accelerated is indeed relevant: in accelerate-cuda, CUDA kernels (which are composed of C code) get compiled to a binary file invoking an external compiler, and then (this is the relevant part) the compiled binary is executed used the CUDA library. The problem is that while CUDA kernels are executable through a libraries, compiled functions using the C calling convention aren't. So I can't really call compiled C functions like accelerate-cuda invokes CUDA kernels. Relatedly, if I have some function pointer known at runtime that addresses a C function that takes some arguments, I have no way to invoke it from Haskell, since all FFI imports must be declared at compile-time, and I don't know the address of the symbol I want to execute at compile time. I am exploring the possibility of adding such capabilities to GHC, since as I mentioned I don't see any particular roadblock. Francesco On 11 February 2015 at 11:40, Simon Peyton Jones wrote: > This may be relevant. http://www.cse.unsw.edu.au/~chak/papers/CMCK14.html > Manuel gave a talk about something like this at the Haskell Symposium. > > Simon > > | -----Original Message----- > | From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf > | Of Francesco Mazzoli > | Sent: 11 February 2015 10:26 > | To: haskell; ghc-devs at haskell.org > | Subject: [Haskell-cafe] Anonymous FFI calls > | > | Hi, > | > | I am in a situation where it would be very useful to call C functions > | without an explicit FFI import. For example, I'd like to be able to > | do > | > | (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 > | > | instead of declaring the foreign import explicitely at the top level. > | > | Is there a way to do this or to achieve similar results in some other > | way? > | > | If not, I imagine it would be easy to implement such a facility in > | GHC, given that the code implementing calling to C functions must > | already be present to implement "proper" FFI imports. I think such an > | addition would be useful in many cases. > | > | Thanks, > | Francesco > | _______________________________________________ > | Haskell-Cafe mailing list > | Haskell-Cafe at haskell.org > | http://www.haskell.org/mailman/listinfo/haskell-cafe From hsyl20 at gmail.com Wed Feb 11 17:26:10 2015 From: hsyl20 at gmail.com (Sylvain Henry) Date: Wed, 11 Feb 2015 18:26:10 +0100 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: 2015-02-11 16:18 GMT+01:00 Francesco Mazzoli : > > Relatedly, if I have some function pointer known at runtime that > addresses a C function that takes some arguments, I have no way to > invoke it from Haskell, since all FFI imports must be declared at > compile-time, and I don't know the address of the symbol I want to > execute at compile time. > You can use FunPtr and wrapper imports to convert a FunPtr into a Haskell function. https://hackage.haskell.org/package/base-4.7.0.2/docs/Foreign-Ptr.html#g:2 You may be interested in my dynamic-linker-template package [1] to avoid having to write boilerplate wrappers. For now it only works with dynamic linking from System.Posix.DynamicLinker, but it could be easily extended to support other platforms. It automatically generates wrappers for all the functions in a record as well as the code to load symbol addresses and to convert them into Haskell functions (examples [2,3]). Sylvain [1] https://hackage.haskell.org/package/dynamic-linker-template [2] https://github.com/hsyl20/dynamic-linker-template/blob/master/Tests/Test.hs [3] https://github.com/hsyl20/ViperVM/blob/master/src/lib/ViperVM/Arch/OpenCL/Library.hs -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Wed Feb 11 19:32:03 2015 From: vogt.adam at gmail.com (adam vogt) Date: Wed, 11 Feb 2015 14:32:03 -0500 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: On Wed, Feb 11, 2015 at 12:26 PM, Sylvain Henry wrote: > 2015-02-11 16:18 GMT+01:00 Francesco Mazzoli : >> >> >> Relatedly, if I have some function pointer known at runtime that >> addresses a C function that takes some arguments, I have no way to >> invoke it from Haskell, since all FFI imports must be declared at >> compile-time, and I don't know the address of the symbol I want to >> execute at compile time. > > > You can use FunPtr and wrapper imports to convert a FunPtr into a Haskell > function. > https://hackage.haskell.org/package/base-4.7.0.2/docs/Foreign-Ptr.html#g:2 > > You may be interested in my dynamic-linker-template package [1] to avoid > having to write boilerplate wrappers. Code using http://hackage.haskell.org/package/libffi looks pretty similar, though the specification needs terms (such as argCInt) instead of a mandatory type signature. GHC itself includes libffi so maybe the foreign import "dynamic" calls end up doing exactly the same thing as the hackage libffi does. From f at mazzo.li Wed Feb 11 20:01:41 2015 From: f at mazzo.li (Francesco Mazzoli) Date: Wed, 11 Feb 2015 21:01:41 +0100 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: On 11 February 2015 at 18:26, Sylvain Henry wrote: > You can use FunPtr and wrapper imports to convert a FunPtr into a Haskell > function. > https://hackage.haskell.org/package/base-4.7.0.2/docs/Foreign-Ptr.html#g:2 The problem with that scheme is that you have to define a FFI import per type. TH solutions are not viable (and cumbersome) for our use case -- the biggest problem being related to the TH staging restriction. > Code using http://hackage.haskell.org/package/libffi looks pretty > similar, though the specification needs terms (such as argCInt) > instead of a mandatory type signature. GHC itself includes libffi so > maybe the foreign import "dynamic" calls end up doing exactly the same > thing as the hackage libffi does. Thanks! That seems like a good workaround for the time being -- we had actually considered for a split second re-implementing the C calling convention, I should have suspected that such a library existed already. However, while that library works for pointers, it does not (and can't) have the facilities to refer to symbols. In any case, there still is the need for such a facility built-in GHC, since such solutions are always going to incur in some overhead, compared to calling C functions directly. For example in the linked bindings to `libffi' the arguments are passed as a list, which is certainly a big difference from storing them into registers. And again, it seems like 95% of the work is already done, since `foreign import's are already desugared to Haskell functions with a primitive call to the C function. Francesco From simonpj at microsoft.com Wed Feb 11 23:09:48 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 11 Feb 2015 23:09:48 +0000 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C738A@DB3PRD3001MB020.064d.mgd.msft.net> There's a bunch of useful info on this thread. Does anyone feel able to distill it to our main FFI wiki page: https://wiki.haskell.org/GHC/Using_the_FFI That way, future generations will benefit. (These user-oriented wiki pages are all linked from GHC's documentation page https://wiki.haskell.org/GHC.) Thanks! Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of adam | vogt | Sent: 11 February 2015 19:32 | To: Sylvain Henry | Cc: ghc-devs at haskell.org; haskell | Subject: Re: [Haskell-cafe] Anonymous FFI calls | | On Wed, Feb 11, 2015 at 12:26 PM, Sylvain Henry wrote: | > 2015-02-11 16:18 GMT+01:00 Francesco Mazzoli : | >> | >> | >> Relatedly, if I have some function pointer known at runtime that | >> addresses a C function that takes some arguments, I have no way to | >> invoke it from Haskell, since all FFI imports must be declared at | >> compile-time, and I don't know the address of the symbol I want to | >> execute at compile time. | > | > | > You can use FunPtr and wrapper imports to convert a FunPtr into a | Haskell | > function. | > https://hackage.haskell.org/package/base-4.7.0.2/docs/Foreign- | Ptr.html#g:2 | > | > You may be interested in my dynamic-linker-template package [1] to | avoid | > having to write boilerplate wrappers. | | Code using http://hackage.haskell.org/package/libffi looks pretty | similar, though the specification needs terms (such as argCInt) | instead of a mandatory type signature. GHC itself includes libffi so | maybe the foreign import "dynamic" calls end up doing exactly the same | thing as the hackage libffi does. | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs From mgsloan at gmail.com Wed Feb 11 23:18:31 2015 From: mgsloan at gmail.com (Michael Sloan) Date: Wed, 11 Feb 2015 15:18:31 -0800 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: Message-ID: It seems like addTopDecls[1] will able to help here. Unfortunately, the function is not well documented and not very discoverable because it's only exported by Language.Haskell.TH. The documentation doesn't mention that it can only be used to create new top level functions and FFI imports[2]. I think that adding FFI imports was the main motivation for implementing it. In the past I've wanted to generate instances via this function, but unfortunately it's not implemented.. Hope that helps! -Michael [1] http://hackage.haskell.org/package/template-haskell-2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls [2] https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33f78a/compiler/typecheck/TcSplice.hs#L818 On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli wrote: > Hi, > > I am in a situation where it would be very useful to call C functions > without an explicit FFI import. For example, I'd like to be able to do > > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 > > instead of declaring the foreign import explicitely at the top level. > > Is there a way to do this or to achieve similar results in some other > way? > > If not, I imagine it would be easy to implement such a facility in GHC, > given that the code implementing calling to C functions must already be > present to implement "proper" FFI imports. I think such an addition > would be useful in many cases. > > Thanks, > Francesco > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From simonpj at microsoft.com Wed Feb 11 23:25:49 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 11 Feb 2015 23:25:49 +0000 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> I would LOVE someone to improve the documentation for addTopDecls. Manuel Chakravarty and Geoff Mainland were responsible for the implementation. Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Michael | Sloan | Sent: 11 February 2015 23:19 | To: Francesco Mazzoli | Cc: ghc-devs at haskell.org; haskell | Subject: Re: [Haskell-cafe] Anonymous FFI calls | | It seems like addTopDecls[1] will able to help here. Unfortunately, | the function is not well documented and not very discoverable because | it's only exported by Language.Haskell.TH. | | The documentation doesn't mention that it can only be used to create | new top level functions and FFI imports[2]. I think that adding FFI | imports was the main motivation for implementing it. In the past | I've wanted to generate instances via this function, but unfortunately | it's not implemented.. | | Hope that helps! | -Michael | | [1] http://hackage.haskell.org/package/template-haskell- | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls | | [2] | https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33f78a/ | compiler/typecheck/TcSplice.hs#L818 | | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli wrote: | > Hi, | > | > I am in a situation where it would be very useful to call C functions | > without an explicit FFI import. For example, I'd like to be able to do | > | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 | > | > instead of declaring the foreign import explicitely at the top level. | > | > Is there a way to do this or to achieve similar results in some other | > way? | > | > If not, I imagine it would be easy to implement such a facility in GHC, | > given that the code implementing calling to C functions must already be | > present to implement "proper" FFI imports. I think such an addition | > would be useful in many cases. | > | > Thanks, | > Francesco | > _______________________________________________ | > Haskell-Cafe mailing list | > Haskell-Cafe at haskell.org | > http://www.haskell.org/mailman/listinfo/haskell-cafe | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs From mgsloan at gmail.com Wed Feb 11 23:32:35 2015 From: mgsloan at gmail.com (Michael Sloan) Date: Wed, 11 Feb 2015 15:32:35 -0800 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: I'd love for the implementation to be as powerful as the documentation suggests it is :D However, yes, in the meantime, fixing the documentation would be great! Also, I meant to say that addTopDecls is only exported by "Language.Haskell.TH.Syntax". While this is a digression, there are a few other handy functions that are oddly left out of "Language.Haskell.TH": addDependentFile, addModFinalizer, and possibly more. -Michael On Wed, Feb 11, 2015 at 3:25 PM, Simon Peyton Jones wrote: > I would LOVE someone to improve the documentation for addTopDecls. Manuel Chakravarty and Geoff Mainland were responsible for the implementation. > > Simon > > | -----Original Message----- > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Michael > | Sloan > | Sent: 11 February 2015 23:19 > | To: Francesco Mazzoli > | Cc: ghc-devs at haskell.org; haskell > | Subject: Re: [Haskell-cafe] Anonymous FFI calls > | > | It seems like addTopDecls[1] will able to help here. Unfortunately, > | the function is not well documented and not very discoverable because > | it's only exported by Language.Haskell.TH. > | > | The documentation doesn't mention that it can only be used to create > | new top level functions and FFI imports[2]. I think that adding FFI > | imports was the main motivation for implementing it. In the past > | I've wanted to generate instances via this function, but unfortunately > | it's not implemented.. > | > | Hope that helps! > | -Michael > | > | [1] http://hackage.haskell.org/package/template-haskell- > | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls > | > | [2] > | https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33f78a/ > | compiler/typecheck/TcSplice.hs#L818 > | > | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli wrote: > | > Hi, > | > > | > I am in a situation where it would be very useful to call C functions > | > without an explicit FFI import. For example, I'd like to be able to do > | > > | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 > | > > | > instead of declaring the foreign import explicitely at the top level. > | > > | > Is there a way to do this or to achieve similar results in some other > | > way? > | > > | > If not, I imagine it would be easy to implement such a facility in GHC, > | > given that the code implementing calling to C functions must already be > | > present to implement "proper" FFI imports. I think such an addition > | > would be useful in many cases. > | > > | > Thanks, > | > Francesco > | > _______________________________________________ > | > Haskell-Cafe mailing list > | > Haskell-Cafe at haskell.org > | > http://www.haskell.org/mailman/listinfo/haskell-cafe > | _______________________________________________ > | ghc-devs mailing list > | ghc-devs at haskell.org > | http://www.haskell.org/mailman/listinfo/ghc-devs From mgsloan at gmail.com Thu Feb 12 00:41:28 2015 From: mgsloan at gmail.com (Michael Sloan) Date: Wed, 11 Feb 2015 16:41:28 -0800 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: <54DBEAF8.2060501@cs.drexel.edu> References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> <54DBEAF8.2060501@cs.drexel.edu> Message-ID: Hi! I don't mean to be accusatory with the whole documentation thing - I totally understand that most folks have a lot going on! In this particular case, I got very excited when I initially saw addTopDecls, because it says it allows you to "Add additional top-level declarations". After implementing something to use it, I got rather disappointed as it couldn't add instances. So, when I say "not implemented", it's just that the docs say it allows you to add additional top-level decls, when you can really only add functions, variable bindings, and foreign import decls. I didn't realize that not re-exporting these functions is due to their experimental status. That makes sense! I'm glad it was a conscious decision. I just tried writing a demo of addTopDecls, but unfortunately using it to add a function and referencing this function causes a GHC internal error: https://gist.github.com/mgsloan/53d7fa50338c696e5c80 . I haven't tried it with a foreign import yet. -Michael On Wed, Feb 11, 2015 at 3:51 PM, Geoffrey Mainland wrote: > Typed Template Haskell happened at the end of my tenure at MSR, and > there was a mad rush to get it in to the compiler in time for 7.8.3 at > the same time I was starting a new job. I'm afraid the documentation is > indeed wanting, but the alternative was no typed Template Haskell. > > One side-effect was that the functions you note as present only in > Language.Haskell.TH.Syntax were not thoroughly vetted, so we didn't > re-export them from Language.Haskell.TH. > > I am willing to help with documentation if people want to use this > functionality. Has anyone attempted to use addTopDecls? Michael, when > you say "it's not implemented," what do you mean? What, exactly, is not > implemented? > > Cheers, > Geoff > > On 2/11/15 6:32 PM, Michael Sloan wrote: >> I'd love for the implementation to be as powerful as the documentation >> suggests it is :D >> >> However, yes, in the meantime, fixing the documentation would be great! >> >> Also, I meant to say that addTopDecls is only exported by >> "Language.Haskell.TH.Syntax". While this is a digression, there are a >> few other handy functions that are oddly left out of >> "Language.Haskell.TH": addDependentFile, addModFinalizer, and possibly >> more. >> >> -Michael >> >> On Wed, Feb 11, 2015 at 3:25 PM, Simon Peyton Jones >> wrote: >>> I would LOVE someone to improve the documentation for addTopDecls. Manuel Chakravarty and Geoff Mainland were responsible for the implementation. >>> >>> Simon >>> >>> | -----Original Message----- >>> | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Michael >>> | Sloan >>> | Sent: 11 February 2015 23:19 >>> | To: Francesco Mazzoli >>> | Cc: ghc-devs at haskell.org; haskell >>> | Subject: Re: [Haskell-cafe] Anonymous FFI calls >>> | >>> | It seems like addTopDecls[1] will able to help here. Unfortunately, >>> | the function is not well documented and not very discoverable because >>> | it's only exported by Language.Haskell.TH. >>> | >>> | The documentation doesn't mention that it can only be used to create >>> | new top level functions and FFI imports[2]. I think that adding FFI >>> | imports was the main motivation for implementing it. In the past >>> | I've wanted to generate instances via this function, but unfortunately >>> | it's not implemented.. >>> | >>> | Hope that helps! >>> | -Michael >>> | >>> | [1] http://hackage.haskell.org/package/template-haskell- >>> | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls >>> | >>> | [2] >>> | https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33f78a/ >>> | compiler/typecheck/TcSplice.hs#L818 >>> | >>> | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli wrote: >>> | > Hi, >>> | > >>> | > I am in a situation where it would be very useful to call C functions >>> | > without an explicit FFI import. For example, I'd like to be able to do >>> | > >>> | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 >>> | > >>> | > instead of declaring the foreign import explicitely at the top level. >>> | > >>> | > Is there a way to do this or to achieve similar results in some other >>> | > way? >>> | > >>> | > If not, I imagine it would be easy to implement such a facility in GHC, >>> | > given that the code implementing calling to C functions must already be >>> | > present to implement "proper" FFI imports. I think such an addition >>> | > would be useful in many cases. >>> | > >>> | > Thanks, >>> | > Francesco >>> | > _______________________________________________ >>> | > Haskell-Cafe mailing list >>> | > Haskell-Cafe at haskell.org >>> | > http://www.haskell.org/mailman/listinfo/haskell-cafe >>> | _______________________________________________ >>> | ghc-devs mailing list >>> | ghc-devs at haskell.org >>> | http://www.haskell.org/mailman/listinfo/ghc-devs > From iavor.diatchki at gmail.com Thu Feb 12 01:19:59 2015 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Wed, 11 Feb 2015 17:19:59 -0800 Subject: Phabricator question Message-ID: Hello, I followed the instruction on the GHC wiki, and published an `arc` revision for my work on the typeable-with-kinds branch. The result was called D652. After I did this, I noticed a bug, and some redundant code; so I fixed my branch. How can I update D652, so that it will diff using the most current version of my branch? -Iavor -------------- next part -------------- An HTML attachment was scrubbed... URL: From stegeman at gmail.com Thu Feb 12 02:22:01 2015 From: stegeman at gmail.com (Luite Stegeman) Date: Thu, 12 Feb 2015 15:22:01 +1300 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C59A4@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Another example, similar to Manuel's work but for GHCJS JavaScriptFFI is ghcjs-ffiqq: https://github.com/ghcjs/ghcjs-ffiqq . There is some automatic marshalling of arguments and results using the ToJSRef / FromJSRef typeclasses. I'm working on integrating the improvements in these typeclasses back into ghcjs-base. The quasiquoter might be moved there too, but I'm not sure yet. The (ugly) implementation is here: https://github.com/ghcjs/ghcjs-ffiqq/blob/master/src/GHCJS/Foreign/QQ.hs Adapting to ccall imports should be straightforward, but implementing the full functionality would require a bit more stub code generation, since this code depends on GHCJS' native support for inline foreign import argument placeholders ($1, $2, $3 etc) placeholders. luite On Wed, Feb 11, 2015 at 11:40 PM, Simon Peyton Jones wrote: > This may be relevant. http://www.cse.unsw.edu.au/~chak/papers/CMCK14.html > Manuel gave a talk about something like this at the Haskell Symposium. > > Simon > > | -----Original Message----- > | From: Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] On Behalf > | Of Francesco Mazzoli > | Sent: 11 February 2015 10:26 > | To: haskell; ghc-devs at haskell.org > | Subject: [Haskell-cafe] Anonymous FFI calls > | > | Hi, > | > | I am in a situation where it would be very useful to call C functions > | without an explicit FFI import. For example, I'd like to be able to > | do > | > | (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 > | > | instead of declaring the foreign import explicitely at the top level. > | > | Is there a way to do this or to achieve similar results in some other > | way? > | > | If not, I imagine it would be easy to implement such a facility in > | GHC, given that the code implementing calling to C functions must > | already be present to implement "proper" FFI imports. I think such an > | addition would be useful in many cases. > | > | Thanks, > | Francesco > | _______________________________________________ > | Haskell-Cafe mailing list > | Haskell-Cafe at haskell.org > | http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs From mgsloan at gmail.com Thu Feb 12 03:13:21 2015 From: mgsloan at gmail.com (Michael Sloan) Date: Wed, 11 Feb 2015 19:13:21 -0800 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: <54DC1518.80609@cs.drexel.edu> References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> <54DBEAF8.2060501@cs.drexel.edu> <54DC1518.80609@cs.drexel.edu> Message-ID: It works, cool! So at least this ought to address Francesco's use-case. Is there anything wrong with my code? It definitely looks like a GHC bug. Yes, I've successfully generated instance declarations from the top-level. I may as well describe the usecase: pretty printing a value of any type in GHCI. While this feature list isn't the main point here, it'd be very cool to do things like: * Look up the value of mutable references such as IORefs * Print out functions as just their type * Be able to evaluate particular subtrees of the pretty print output (like present [1]) * Select a subportion of the output and get a variable out of it Usage would look like "$(pretty 'x)". This would reify the type of x and transitively generate `Pretty` instances for things, by using my th-reify-many package [2]. It then generates an expression which invokes `pretty` on `x`, using these new instances. This instance generation can do clever things like check if a type has a "Data" instance, and use it if available. In this way, we can construct a pretty printer for ghci which will work for any type. Certainly, this is still possible without instance generation, but it'd be quite clever to not need to re-generate the pretty printing code for every invocation. -Michael [1] https://github.com/chrisdone/present [2] https://github.com/mgsloan/th-reify-many On Wed, Feb 11, 2015 at 6:51 PM, Geoffrey Mainland wrote: > Hi Michael, > > Try this out: > > https://gist.github.com/mainland/f18cf3827c4b0b64b835 > > Have you had success generating instance declarations from top-level > splices? > > Geoff > > On 02/11/2015 07:41 PM, Michael Sloan wrote: >> Hi! >> >> I don't mean to be accusatory with the whole documentation thing - I >> totally understand that most folks have a lot going on! In this >> particular case, I got very excited when I initially saw addTopDecls, >> because it says it allows you to "Add additional top-level >> declarations". After implementing something to use it, I got rather >> disappointed as it couldn't add instances. >> >> So, when I say "not implemented", it's just that the docs say it >> allows you to add additional top-level decls, when you can really only >> add functions, variable bindings, and foreign import decls. >> >> I didn't realize that not re-exporting these functions is due to their >> experimental status. That makes sense! I'm glad it was a conscious >> decision. I just tried writing a demo of addTopDecls, but >> unfortunately using it to add a function and referencing this function >> causes a GHC internal error: >> https://gist.github.com/mgsloan/53d7fa50338c696e5c80 . I haven't >> tried it with a foreign import yet. >> >> -Michael >> >> On Wed, Feb 11, 2015 at 3:51 PM, Geoffrey Mainland >> wrote: >>> Typed Template Haskell happened at the end of my tenure at MSR, and >>> there was a mad rush to get it in to the compiler in time for 7.8.3 at >>> the same time I was starting a new job. I'm afraid the documentation is >>> indeed wanting, but the alternative was no typed Template Haskell. >>> >>> One side-effect was that the functions you note as present only in >>> Language.Haskell.TH.Syntax were not thoroughly vetted, so we didn't >>> re-export them from Language.Haskell.TH. >>> >>> I am willing to help with documentation if people want to use this >>> functionality. Has anyone attempted to use addTopDecls? Michael, when >>> you say "it's not implemented," what do you mean? What, exactly, is not >>> implemented? >>> >>> Cheers, >>> Geoff >>> >>> On 2/11/15 6:32 PM, Michael Sloan wrote: >>>> I'd love for the implementation to be as powerful as the documentation >>>> suggests it is :D >>>> >>>> However, yes, in the meantime, fixing the documentation would be great! >>>> >>>> Also, I meant to say that addTopDecls is only exported by >>>> "Language.Haskell.TH.Syntax". While this is a digression, there are a >>>> few other handy functions that are oddly left out of >>>> "Language.Haskell.TH": addDependentFile, addModFinalizer, and possibly >>>> more. >>>> >>>> -Michael >>>> >>>> On Wed, Feb 11, 2015 at 3:25 PM, Simon Peyton Jones >>>> wrote: >>>>> I would LOVE someone to improve the documentation for addTopDecls. Manuel Chakravarty and Geoff Mainland were responsible for the implementation. >>>>> >>>>> Simon >>>>> >>>>> | -----Original Message----- >>>>> | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Michael >>>>> | Sloan >>>>> | Sent: 11 February 2015 23:19 >>>>> | To: Francesco Mazzoli >>>>> | Cc: ghc-devs at haskell.org; haskell >>>>> | Subject: Re: [Haskell-cafe] Anonymous FFI calls >>>>> | >>>>> | It seems like addTopDecls[1] will able to help here. Unfortunately, >>>>> | the function is not well documented and not very discoverable because >>>>> | it's only exported by Language.Haskell.TH. >>>>> | >>>>> | The documentation doesn't mention that it can only be used to create >>>>> | new top level functions and FFI imports[2]. I think that adding FFI >>>>> | imports was the main motivation for implementing it. In the past >>>>> | I've wanted to generate instances via this function, but unfortunately >>>>> | it's not implemented.. >>>>> | >>>>> | Hope that helps! >>>>> | -Michael >>>>> | >>>>> | [1] http://hackage.haskell.org/package/template-haskell- >>>>> | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls >>>>> | >>>>> | [2] >>>>> | https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33f78a/ >>>>> | compiler/typecheck/TcSplice.hs#L818 >>>>> | >>>>> | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli wrote: >>>>> | > Hi, >>>>> | > >>>>> | > I am in a situation where it would be very useful to call C functions >>>>> | > without an explicit FFI import. For example, I'd like to be able to do >>>>> | > >>>>> | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 >>>>> | > >>>>> | > instead of declaring the foreign import explicitely at the top level. >>>>> | > >>>>> | > Is there a way to do this or to achieve similar results in some other >>>>> | > way? >>>>> | > >>>>> | > If not, I imagine it would be easy to implement such a facility in GHC, >>>>> | > given that the code implementing calling to C functions must already be >>>>> | > present to implement "proper" FFI imports. I think such an addition >>>>> | > would be useful in many cases. >>>>> | > >>>>> | > Thanks, >>>>> | > Francesco >>>>> | > _______________________________________________ >>>>> | > Haskell-Cafe mailing list >>>>> | > Haskell-Cafe at haskell.org >>>>> | > http://www.haskell.org/mailman/listinfo/haskell-cafe >>>>> | _______________________________________________ >>>>> | ghc-devs mailing list >>>>> | ghc-devs at haskell.org >>>>> | http://www.haskell.org/mailman/listinfo/ghc-devs > From eric at seidel.io Thu Feb 12 04:18:18 2015 From: eric at seidel.io (Eric Seidel) Date: Wed, 11 Feb 2015 20:18:18 -0800 Subject: Phabricator question In-Reply-To: References: Message-ID: <1423714698.373460.226479029.5A62E0AF@webmail.messagingengine.com> You'll want to run $ arc diff --update D652 where base is the ref you want to diff against (presumably master). Specifying the base is important, as arc will *replace* the current diff with the new one, so you want to make sure the base is consistent across updates. Eric On Wed, Feb 11, 2015, at 17:19, Iavor Diatchki wrote: > Hello, > > I followed the instruction on the GHC wiki, and published an `arc` > revision > for my work on the typeable-with-kinds branch. The result was called > D652. > > After I did this, I noticed a bug, and some redundant code; so I fixed > my > branch. How can I update D652, so that it will diff using the most > current > version of my branch? > > -Iavor > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs From simonpj at microsoft.com Thu Feb 12 08:29:29 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 12 Feb 2015 08:29:29 +0000 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C75BE@DB3PRD3001MB020.064d.mgd.msft.net> | Also, I meant to say that addTopDecls is only exported by | "Language.Haskell.TH.Syntax". While this is a digression, there are a | few other handy functions that are oddly left out of | "Language.Haskell.TH": addDependentFile, addModFinalizer, and possibly | more. That does seem wrong. Do make a patch! SIMon | | -Michael | | On Wed, Feb 11, 2015 at 3:25 PM, Simon Peyton Jones | wrote: | > I would LOVE someone to improve the documentation for addTopDecls. | Manuel Chakravarty and Geoff Mainland were responsible for the | implementation. | > | > Simon | > | > | -----Original Message----- | > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of | > | Michael Sloan | > | Sent: 11 February 2015 23:19 | > | To: Francesco Mazzoli | > | Cc: ghc-devs at haskell.org; haskell | > | Subject: Re: [Haskell-cafe] Anonymous FFI calls | > | | > | It seems like addTopDecls[1] will able to help here. | Unfortunately, | > | the function is not well documented and not very discoverable | > | because it's only exported by Language.Haskell.TH. | > | | > | The documentation doesn't mention that it can only be used to | create | > | new top level functions and FFI imports[2]. I think that adding | FFI | > | imports was the main motivation for implementing it. In the past | > | I've wanted to generate instances via this function, but | > | unfortunately it's not implemented.. | > | | > | Hope that helps! | > | -Michael | > | | > | [1] http://hackage.haskell.org/package/template-haskell- | > | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls | > | | > | [2] | > | | https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33 | > | f78a/ | > | compiler/typecheck/TcSplice.hs#L818 | > | | > | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli | wrote: | > | > Hi, | > | > | > | > I am in a situation where it would be very useful to call C | > | > functions without an explicit FFI import. For example, I'd like | > | > to be able to do | > | > | > | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 | > | > | > | > instead of declaring the foreign import explicitely at the top | level. | > | > | > | > Is there a way to do this or to achieve similar results in some | > | > other way? | > | > | > | > If not, I imagine it would be easy to implement such a facility | in | > | > GHC, given that the code implementing calling to C functions | must | > | > already be present to implement "proper" FFI imports. I think | > | > such an addition would be useful in many cases. | > | > | > | > Thanks, | > | > Francesco | > | > _______________________________________________ | > | > Haskell-Cafe mailing list | > | > Haskell-Cafe at haskell.org | > | > http://www.haskell.org/mailman/listinfo/haskell-cafe | > | _______________________________________________ | > | ghc-devs mailing list | > | ghc-devs at haskell.org | > | http://www.haskell.org/mailman/listinfo/ghc-devs From simonpj at microsoft.com Thu Feb 12 08:39:35 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 12 Feb 2015 08:39:35 +0000 Subject: Phabricator question In-Reply-To: <1423714698.373460.226479029.5A62E0AF@webmail.messagingengine.com> References: <1423714698.373460.226479029.5A62E0AF@webmail.messagingengine.com> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C763D@DB3PRD3001MB020.064d.mgd.msft.net> Would someone like to add this info to https://ghc.haskell.org/trac/ghc/wiki/Phabricator? Actually that page could so with some re-organisation, to bring out key workflows. Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Eric | Seidel | Sent: 12 February 2015 04:18 | To: ghc-devs at haskell.org | Subject: Re: Phabricator question | | You'll want to run | | $ arc diff --update D652 | | where base is the ref you want to diff against (presumably master). | Specifying the base is important, as arc will *replace* the current | diff with the new one, so you want to make sure the base is consistent | across updates. | | Eric | | On Wed, Feb 11, 2015, at 17:19, Iavor Diatchki wrote: | > Hello, | > | > I followed the instruction on the GHC wiki, and published an `arc` | > revision for my work on the typeable-with-kinds branch. The result | was | > called D652. | > | > After I did this, I noticed a bug, and some redundant code; so I | > fixed my branch. How can I update D652, so that it will diff using | > the most current version of my branch? | > | > -Iavor | > _______________________________________________ | > ghc-devs mailing list | > ghc-devs at haskell.org | > http://www.haskell.org/mailman/listinfo/ghc-devs | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs From f at mazzo.li Thu Feb 12 08:59:53 2015 From: f at mazzo.li (Francesco Mazzoli) Date: Thu, 12 Feb 2015 09:59:53 +0100 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C75BE@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C75BE@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Thanks to everyone who replied! It seems like that through a combination of facilities like `libffi' and `addTopDecls' I can do everything that I wanted to do. I still want to take a shot at implementing anonymous FFI calls, since IMHO I think they are a very small but useful addition to the language. Francesco On 12 February 2015 at 09:29, Simon Peyton Jones wrote: > | Also, I meant to say that addTopDecls is only exported by > | "Language.Haskell.TH.Syntax". While this is a digression, there are a > | few other handy functions that are oddly left out of > | "Language.Haskell.TH": addDependentFile, addModFinalizer, and possibly > | more. > > That does seem wrong. Do make a patch! > > SIMon > > | > | -Michael > | > | On Wed, Feb 11, 2015 at 3:25 PM, Simon Peyton Jones > | wrote: > | > I would LOVE someone to improve the documentation for addTopDecls. > | Manuel Chakravarty and Geoff Mainland were responsible for the > | implementation. > | > > | > Simon > | > > | > | -----Original Message----- > | > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of > | > | Michael Sloan > | > | Sent: 11 February 2015 23:19 > | > | To: Francesco Mazzoli > | > | Cc: ghc-devs at haskell.org; haskell > | > | Subject: Re: [Haskell-cafe] Anonymous FFI calls > | > | > | > | It seems like addTopDecls[1] will able to help here. > | Unfortunately, > | > | the function is not well documented and not very discoverable > | > | because it's only exported by Language.Haskell.TH. > | > | > | > | The documentation doesn't mention that it can only be used to > | create > | > | new top level functions and FFI imports[2]. I think that adding > | FFI > | > | imports was the main motivation for implementing it. In the past > | > | I've wanted to generate instances via this function, but > | > | unfortunately it's not implemented.. > | > | > | > | Hope that helps! > | > | -Michael > | > | > | > | [1] http://hackage.haskell.org/package/template-haskell- > | > | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls > | > | > | > | [2] > | > | > | https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33 > | > | f78a/ > | > | compiler/typecheck/TcSplice.hs#L818 > | > | > | > | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli > | wrote: > | > | > Hi, > | > | > > | > | > I am in a situation where it would be very useful to call C > | > | > functions without an explicit FFI import. For example, I'd like > | > | > to be able to do > | > | > > | > | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 > | > | > > | > | > instead of declaring the foreign import explicitely at the top > | level. > | > | > > | > | > Is there a way to do this or to achieve similar results in some > | > | > other way? > | > | > > | > | > If not, I imagine it would be easy to implement such a facility > | in > | > | > GHC, given that the code implementing calling to C functions > | must > | > | > already be present to implement "proper" FFI imports. I think > | > | > such an addition would be useful in many cases. > | > | > > | > | > Thanks, > | > | > Francesco > | > | > _______________________________________________ > | > | > Haskell-Cafe mailing list > | > | > Haskell-Cafe at haskell.org > | > | > http://www.haskell.org/mailman/listinfo/haskell-cafe > | > | _______________________________________________ > | > | ghc-devs mailing list > | > | ghc-devs at haskell.org > | > | http://www.haskell.org/mailman/listinfo/ghc-devs From simonpj at microsoft.com Thu Feb 12 09:02:33 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 12 Feb 2015 09:02:33 +0000 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C75BE@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C7741@DB3PRD3001MB020.064d.mgd.msft.net> | Thanks to everyone who replied! | | It seems like that through a combination of facilities like `libffi' | and `addTopDecls' I can do everything that I wanted to do. Great. But please, please, do write up what you learned on the FFI wiki page https://wiki.haskell.org/GHC/Using_the_FFI Simon | -----Original Message----- | From: Francesco Mazzoli [mailto:f at mazzo.li] | Sent: 12 February 2015 09:00 | To: Simon Peyton Jones | Cc: Michael Sloan; Manuel Chakravarty; Geoffrey Mainland | (mainland at cs.drexel.edu); ghc-devs at haskell.org; haskell | Subject: Re: [Haskell-cafe] Anonymous FFI calls | | Thanks to everyone who replied! | | It seems like that through a combination of facilities like `libffi' | and `addTopDecls' I can do everything that I wanted to do. | | I still want to take a shot at implementing anonymous FFI calls, since | IMHO I think they are a very small but useful addition to the | language. | | Francesco | | On 12 February 2015 at 09:29, Simon Peyton Jones | wrote: | > | Also, I meant to say that addTopDecls is only exported by | > | "Language.Haskell.TH.Syntax". While this is a digression, there are | a | > | few other handy functions that are oddly left out of | > | "Language.Haskell.TH": addDependentFile, addModFinalizer, and | possibly | > | more. | > | > That does seem wrong. Do make a patch! | > | > SIMon | > | > | | > | -Michael | > | | > | On Wed, Feb 11, 2015 at 3:25 PM, Simon Peyton Jones | > | wrote: | > | > I would LOVE someone to improve the documentation for addTopDecls. | > | Manuel Chakravarty and Geoff Mainland were responsible for the | > | implementation. | > | > | > | > Simon | > | > | > | > | -----Original Message----- | > | > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf | Of | > | > | Michael Sloan | > | > | Sent: 11 February 2015 23:19 | > | > | To: Francesco Mazzoli | > | > | Cc: ghc-devs at haskell.org; haskell | > | > | Subject: Re: [Haskell-cafe] Anonymous FFI calls | > | > | | > | > | It seems like addTopDecls[1] will able to help here. | > | Unfortunately, | > | > | the function is not well documented and not very discoverable | > | > | because it's only exported by Language.Haskell.TH. | > | > | | > | > | The documentation doesn't mention that it can only be used to | > | create | > | > | new top level functions and FFI imports[2]. I think that adding | > | FFI | > | > | imports was the main motivation for implementing it. In the | past | > | > | I've wanted to generate instances via this function, but | > | > | unfortunately it's not implemented.. | > | > | | > | > | Hope that helps! | > | > | -Michael | > | > | | > | > | [1] http://hackage.haskell.org/package/template-haskell- | > | > | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls | > | > | | > | > | [2] | > | > | | > | https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33 | > | > | f78a/ | > | > | compiler/typecheck/TcSplice.hs#L818 | > | > | | > | > | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli | > | wrote: | > | > | > Hi, | > | > | > | > | > | > I am in a situation where it would be very useful to call C | > | > | > functions without an explicit FFI import. For example, I'd | like | > | > | > to be able to do | > | > | > | > | > | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 | > | > | > | > | > | > instead of declaring the foreign import explicitely at the top | > | level. | > | > | > | > | > | > Is there a way to do this or to achieve similar results in | some | > | > | > other way? | > | > | > | > | > | > If not, I imagine it would be easy to implement such a | facility | > | in | > | > | > GHC, given that the code implementing calling to C functions | > | must | > | > | > already be present to implement "proper" FFI imports. I think | > | > | > such an addition would be useful in many cases. | > | > | > | > | > | > Thanks, | > | > | > Francesco | > | > | > _______________________________________________ | > | > | > Haskell-Cafe mailing list | > | > | > Haskell-Cafe at haskell.org | > | > | > http://www.haskell.org/mailman/listinfo/haskell-cafe | > | > | _______________________________________________ | > | > | ghc-devs mailing list | > | > | ghc-devs at haskell.org | > | > | http://www.haskell.org/mailman/listinfo/ghc-devs From f at mazzo.li Thu Feb 12 09:50:04 2015 From: f at mazzo.li (Francesco Mazzoli) Date: Thu, 12 Feb 2015 10:50:04 +0100 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C7741@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C75BE@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C7741@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: On 12 February 2015 at 10:02, Simon Peyton Jones wrote: > | Thanks to everyone who replied! > | > | It seems like that through a combination of facilities like `libffi' > | and `addTopDecls' I can do everything that I wanted to do. > > Great. But please, please, do write up what you learned on the FFI wiki page > https://wiki.haskell.org/GHC/Using_the_FFI I'll try to find the time to do that. I'll definitely have the time to simply write "you should check out X and Y". Francesco From ozgurakgun at gmail.com Thu Feb 12 14:20:53 2015 From: ozgurakgun at gmail.com (Ozgur Akgun) Date: Thu, 12 Feb 2015 14:20:53 +0000 Subject: MAC builds of 7.8.4 and 7.10.1 RC2 In-Reply-To: References: Message-ID: This is great. What would one have to do to get this added to https://www.haskell.org/ghc/download_ghc_7_8_4 ? Ozgur On 11 February 2015 at 06:16, Mark Lentczner wrote: > My build procedure is very minimal: > > export MACOSX_DEPLOYMENT_TARGET=10.6 > ./configure 2>&1 | tee ../conf.log > cat > mk/build.mk < V=1 > SplitObjs=YES > SupportsSplitObjs=YES > HADDOCK_DOCS=YES > LATEX_DOCS=NO > HSCOLOUR_SRCS=YES > BUILD_DOCBOOK_HTML=YES > BUILD_DOCBOOK_PDF=NO > BUILD_DOCBOOK_PS=NO > BeConservative=YES > END > time make -j4 2>&1 | tee ../make.log > time make binary-dist 2>&1 | tee ../bd.log > > That is all! > ? > -------------- next part -------------- An HTML attachment was scrubbed... URL: From austin at well-typed.com Thu Feb 12 15:02:39 2015 From: austin at well-typed.com (Austin Seipp) Date: Thu, 12 Feb 2015 09:02:39 -0600 Subject: MAC builds of 7.8.4 and 7.10.1 RC2 In-Reply-To: References: Message-ID: I'll get them online with signed hashes today. On Thu, Feb 12, 2015 at 8:20 AM, Ozgur Akgun wrote: > This is great. > > What would one have to do to get this added to > https://www.haskell.org/ghc/download_ghc_7_8_4 ? > > Ozgur > > On 11 February 2015 at 06:16, Mark Lentczner > wrote: >> >> My build procedure is very minimal: >> >> export MACOSX_DEPLOYMENT_TARGET=10.6 >> ./configure 2>&1 | tee ../conf.log >> cat > mk/build.mk <> V=1 >> SplitObjs=YES >> SupportsSplitObjs=YES >> HADDOCK_DOCS=YES >> LATEX_DOCS=NO >> HSCOLOUR_SRCS=YES >> BUILD_DOCBOOK_HTML=YES >> BUILD_DOCBOOK_PDF=NO >> BUILD_DOCBOOK_PS=NO >> BeConservative=YES >> END >> time make -j4 2>&1 | tee ../make.log >> time make binary-dist 2>&1 | tee ../bd.log >> >> That is all! > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From afarmer at ittc.ku.edu Thu Feb 12 16:06:29 2015 From: afarmer at ittc.ku.edu (Andrew Farmer) Date: Thu, 12 Feb 2015 10:06:29 -0600 Subject: GHC Haddock URL Message-ID: Can someone with The Power please symlink (or otherwise redirect) this: https://downloads.haskell.org/~ghc/latest/docs/html/libraries/ghc to https://downloads.haskell.org/~ghc/latest/docs/html/libraries/ghc-7.8.4 ... so I can Hoogle with greater ease? Thanks much! Andrew From austin at well-typed.com Thu Feb 12 16:08:19 2015 From: austin at well-typed.com (Austin Seipp) Date: Thu, 12 Feb 2015 10:08:19 -0600 Subject: GHC Haddock URL In-Reply-To: References: Message-ID: Done, this URL seems to fit the bill: https://downloads.haskell.org/~ghc/latest/docs/html/libraries/ghc/ On Thu, Feb 12, 2015 at 10:06 AM, Andrew Farmer wrote: > Can someone with The Power please symlink (or otherwise redirect) this: > > https://downloads.haskell.org/~ghc/latest/docs/html/libraries/ghc > > to > > https://downloads.haskell.org/~ghc/latest/docs/html/libraries/ghc-7.8.4 > > ... so I can Hoogle with greater ease? > > Thanks much! > Andrew > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From hengchu.zhang+ghcdev at gmail.com Thu Feb 12 18:52:22 2015 From: hengchu.zhang+ghcdev at gmail.com (Hengchu Zhang) Date: Thu, 12 Feb 2015 13:52:22 -0500 Subject: Newcomer question Message-ID: Hi GHC Devs, I just joined the community and wanted to start contributing/hacking on GHC. I was going through Newcomer's Info tab, and this https://ghc.haskell.org/trac/ghc/ticket/8811 seemed like a good first thing for me to try. A few questions related to git: from the ticket it looks like this bug happens in 7.6.3. From the repo I checked out, there is a tag ghc-7.6.3-release. But I guess I'm not really supposed to checkout the tag and modify the code from there? But running git branch only shows the master branch. So should I run ./sync-all checkout ghc-7.6 and modify the code from that branch? Thank you very much! Best, Hengchu -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Thu Feb 12 19:01:38 2015 From: mail at joachim-breitner.de (Joachim Breitner) Date: Thu, 12 Feb 2015 20:01:38 +0100 Subject: Newcomer question In-Reply-To: References: Message-ID: <1423767698.699.1.camel@joachim-breitner.de> Dear Hengcu, Am Donnerstag, den 12.02.2015, 13:52 -0500 schrieb Hengchu Zhang: > I just joined the community and wanted to start contributing/hacking > on GHC. Great, Welcome! > I was going through Newcomer's Info tab, and this > https://ghc.haskell.org/trac/ghc/ticket/8811 seemed like a good first > thing for me to try. > > A few questions related to git: from the ticket it looks like this bug > happens in 7.6.3. It just means that it was reported by someone with this version, but likely it is still present in the latest version, and that?s where you should fix it. So simply get the current git master, reproduce the bug there and then create a fix. Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0xF0FBF51F Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From takenobu.hs at gmail.com Fri Feb 13 10:35:36 2015 From: takenobu.hs at gmail.com (Takenobu Tani) Date: Fri, 13 Feb 2015 19:35:36 +0900 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: References: Message-ID: Hi, Does ghc7.10rc2 support for windows 32bit OS (Windows 7) ? I tried to build ghc7.10rc2 [1],[2] on my old 32bit windows to check FTP. Then, the following error has occurred: "C:/MinGW/msys/1.0/home/my/devel/haskell.build.mingw/work8.ghc.7.10.rc2/ghc-7.10.0.20150123/inplace/mingw/bin/ld.exe" -r -o libraries/directory/dist-install/build/HSdirec_3OAebvWY9YTGrbhfMGQ0ml.o libraries/directory/dist-install/build/System/Directory.o libraries/directory/dist-install/build/cbits/directory.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -H64m -O0 -fasm -this-package-key proce_9HgSaudU0TAKauLzQHuwnO -hide-all-packages -i -ilibraries/process/. -ilibraries/process/dist-install/build -ilibraries/process/dist-install/build/autogen -Ilibraries/process/dist-install/build -Ilibraries/process/dist-install/build/autogen -Ilibraries/process/include -optP-include -optPlibraries/process/dist-install/build/autogen/cabal_macros.h -package-key Win32_Cjc5QN7bEuvL7SrTr96E5g -package-key base_469rOtLAqwTGFEOGWxSUiQ -package-key deeps_FT5iVCELxOr62eHY0nbvnU -package-key direc_3OAebvWY9YTGrbhfMGQ0ml -package-key filep_1vDJvPDP7mkAk0dVCj6gws -Wall -XHaskell2010 -O -fasm -no-user-package-db -rtsopts -odir libraries/process/dist-install/build -hidir libraries/process/dist-install/build -stubdir libraries/process/dist-install/build -c libraries/process/./System/Process/Internals.hs -o libraries/process/dist-install/build/System/Process/Internals.o libraries\process\System\Process\Internals.hs:36:5: Not in scope: <81>estopDelegateControlC<81>f Perhaps you meant one of these: <81>estartDelegateControlC<81>f (line 467), <81>eendDelegateControlC<81>f (line 470) make[1]: *** [libraries/process/dist-install/build/System/Process/Internals.o] Error 1 make: *** [all] Error 2 I looks like 'stopDelegateControl' is not defined in System\Process\Internals.hs for mingw32_HOST_OS. [1]: https://downloads.haskell.org/~ghc/7.10.1-rc2/ghc-7.10.0.20150123-src.tar.bz2 [2]: https://downloads.haskell.org/~ghc/7.10.1-rc2/ghc-7.10.0.20150123-windows-extra-src.tar.bz2 Regards, Takenobu 2015-01-27 9:13 GMT+09:00 Austin Seipp : > We are pleased to announce the second release candidate for GHC 7.10.1: > > https://downloads.haskell.org/~ghc/7.10.1-rc2/ > > This includes the source tarball and bindists for 64bit/32bit Linux > and Windows. Binary builds for other platforms will be available > shortly. (CentOS 6.5 binaries are not available at this time like they > were for 7.8.x). These binaries and tarballs have an accompanying > SHA256SUMS file signed by my GPG key id (0x3B58D86F). > > We plan to make the 7.10.1 release sometime in February of 2015. > > Please test as much as possible; bugs are much cheaper if we find them > before the release! > > -- > Regards, > > Austin Seipp, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From f at mazzo.li Fri Feb 13 12:53:40 2015 From: f at mazzo.li (Francesco Mazzoli) Date: Fri, 13 Feb 2015 13:53:40 +0100 Subject: What `reify` sees in Template Haskell Message-ID: Hi, I recently stumbled upon the issue of `reify` not being able to give information about local variables, as of GHC 7.8. For example, this won't work: foo x = $(do {xInfo <- reify 'x; ...}) The motivation for this change is described here: . While I agree that getting the type of local variables is going to be brittle, I also think that offering that functionality is extremely useful in certain cases, such as in the case of the language-c-inline library, that used this facility to avoid having to type verbose type annotations -- see . My two part question is: 1. would it be possible to revert to the old behavior easily, or is doing that difficult or impossible now given the overall changes to the Template Haskell code? 2. if 1, wouldn't it make more sense to allow reifying all names if the user really wants, maybe with a specific `unsafeReify` function or similar? It should be made clear in the docs that by using `unsafeReify` the user is relying on GHC internals (specifically the internals of type checking). Also, I think that post should at least be referenced in the manual, for lack of better documentation. This behavior is not mentioned anywhere else. Thanks, Francesco From simonpj at microsoft.com Fri Feb 13 17:12:47 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 13 Feb 2015 17:12:47 +0000 Subject: What `reify` sees in Template Haskell In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C990D@DB3PRD3001MB020.064d.mgd.msft.net> | 1. would it be possible to revert to the old behavior easily, or is | doing that difficult or impossible now given the overall changes to | the Template Haskell code? I don?t think it would be difficult to recover the old behaviour, but it's not clear to me that it would be a Good Thing. A program that works today, and then does not work tomorrow because of some incidental change to the way type inference works, would not be a happy state of affairs. Perhaps if 'x' had a type annotation that would be ok. Or maybe there is something else about your intended application that makes it solidly predictable. By all means start a wiki page to sketch a design for what you think should happen, and why it should be predicable. Meanwhile, if you would care to draft the bit of user-manual material that you wish had been there, I could review it and put it in. Thanks! Simon | -----Original Message----- | From: Francesco Mazzoli [mailto:f at mazzo.li] | Sent: 13 February 2015 12:54 | To: ghc-devs at haskell.org | Cc: Simon Peyton Jones | Subject: What `reify` sees in Template Haskell | | Hi, | | I recently stumbled upon the issue of `reify` not being able to give | information about local variables, as of GHC 7.8. For example, this | won't work: | | foo x = $(do {xInfo <- reify 'x; ...}) | | The motivation for this change is described here: | . | | While I agree that getting the type of local variables is going to be | brittle, I also think that offering that functionality is extremely | useful in certain cases, such as in the case of the language-c-inline | library, that used this facility to avoid having to type verbose type | annotations -- see . | | My two part question is: | | 1. would it be possible to revert to the old behavior easily, or is | doing that difficult or impossible now given the overall changes to | the Template Haskell code? | 2. if 1, wouldn't it make more sense to allow reifying all names if | the user really wants, maybe with a specific `unsafeReify` function or | similar? | | It should be made clear in the docs that by using `unsafeReify` the | user is relying on GHC internals (specifically the internals of type | checking). | | Also, I think that post should at least be referenced in the manual, | for lack of better documentation. This behavior is not mentioned | anywhere else. | | Thanks, | Francesco From f at mazzo.li Fri Feb 13 17:43:16 2015 From: f at mazzo.li (Francesco Mazzoli) Date: Fri, 13 Feb 2015 18:43:16 +0100 Subject: What `reify` sees in Template Haskell In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C990D@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C990D@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Hi Simon, On 13 February 2015 at 18:12, Simon Peyton Jones wrote: > I don?t think it would be difficult to recover the old behaviour, but it's not clear to me that it would be a Good Thing. A program that works today, and then does not work tomorrow because of some incidental change to the way type inference works, would not be a happy state of affairs. In much the same way, programs that rely on the memory representation that GHC uses for objects can be written with the provided unsafe functions. In my view, if you make this danger clear, having those functions is much better than not having them. And it seems like the Haskell environment generally agree with this view. In any case, if I think of some reasonable but more permissive restriction, I'll write it up. > Meanwhile, if you would care to draft the bit of user-manual material that you wish had been there, I could review it and put it in. I'll try to get some writing done regarding this and the FFI wiki page next week. Francesco From hsyl20 at gmail.com Fri Feb 13 18:28:25 2015 From: hsyl20 at gmail.com (Sylvain Henry) Date: Fri, 13 Feb 2015 19:28:25 +0100 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562C7741@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C75BE@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C7741@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Hi, The FFI pages on the wiki are not really in a good shape in my opinion (especially for newcomers). I have started a fresh one here: https://wiki.haskell.org/Foreign_Function_Interface_(FFI) This is just the first draft. I will improve it, probably split it in several pages and merge information from other pages, especially pages linked on https://wiki.haskell.org/FFI Sylvain 2015-02-12 10:02 GMT+01:00 Simon Peyton Jones : > | Thanks to everyone who replied! > | > | It seems like that through a combination of facilities like `libffi' > | and `addTopDecls' I can do everything that I wanted to do. > > Great. But please, please, do write up what you learned on the FFI wiki > page > https://wiki.haskell.org/GHC/Using_the_FFI > > Simon > > | -----Original Message----- > | From: Francesco Mazzoli [mailto:f at mazzo.li] > | Sent: 12 February 2015 09:00 > | To: Simon Peyton Jones > | Cc: Michael Sloan; Manuel Chakravarty; Geoffrey Mainland > | (mainland at cs.drexel.edu); ghc-devs at haskell.org; haskell > | Subject: Re: [Haskell-cafe] Anonymous FFI calls > | > | Thanks to everyone who replied! > | > | It seems like that through a combination of facilities like `libffi' > | and `addTopDecls' I can do everything that I wanted to do. > | > | I still want to take a shot at implementing anonymous FFI calls, since > | IMHO I think they are a very small but useful addition to the > | language. > | > | Francesco > | > | On 12 February 2015 at 09:29, Simon Peyton Jones > | wrote: > | > | Also, I meant to say that addTopDecls is only exported by > | > | "Language.Haskell.TH.Syntax". While this is a digression, there are > | a > | > | few other handy functions that are oddly left out of > | > | "Language.Haskell.TH": addDependentFile, addModFinalizer, and > | possibly > | > | more. > | > > | > That does seem wrong. Do make a patch! > | > > | > SIMon > | > > | > | > | > | -Michael > | > | > | > | On Wed, Feb 11, 2015 at 3:25 PM, Simon Peyton Jones > | > | wrote: > | > | > I would LOVE someone to improve the documentation for addTopDecls. > | > | Manuel Chakravarty and Geoff Mainland were responsible for the > | > | implementation. > | > | > > | > | > Simon > | > | > > | > | > | -----Original Message----- > | > | > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf > | Of > | > | > | Michael Sloan > | > | > | Sent: 11 February 2015 23:19 > | > | > | To: Francesco Mazzoli > | > | > | Cc: ghc-devs at haskell.org; haskell > | > | > | Subject: Re: [Haskell-cafe] Anonymous FFI calls > | > | > | > | > | > | It seems like addTopDecls[1] will able to help here. > | > | Unfortunately, > | > | > | the function is not well documented and not very discoverable > | > | > | because it's only exported by Language.Haskell.TH. > | > | > | > | > | > | The documentation doesn't mention that it can only be used to > | > | create > | > | > | new top level functions and FFI imports[2]. I think that adding > | > | FFI > | > | > | imports was the main motivation for implementing it. In the > | past > | > | > | I've wanted to generate instances via this function, but > | > | > | unfortunately it's not implemented.. > | > | > | > | > | > | Hope that helps! > | > | > | -Michael > | > | > | > | > | > | [1] http://hackage.haskell.org/package/template-haskell- > | > | > | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls > | > | > | > | > | > | [2] > | > | > | > | > | > https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33 > | > | > | f78a/ > | > | > | compiler/typecheck/TcSplice.hs#L818 > | > | > | > | > | > | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli > | > | wrote: > | > | > | > Hi, > | > | > | > > | > | > | > I am in a situation where it would be very useful to call C > | > | > | > functions without an explicit FFI import. For example, I'd > | like > | > | > | > to be able to do > | > | > | > > | > | > | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 > | > | > | > > | > | > | > instead of declaring the foreign import explicitely at the top > | > | level. > | > | > | > > | > | > | > Is there a way to do this or to achieve similar results in > | some > | > | > | > other way? > | > | > | > > | > | > | > If not, I imagine it would be easy to implement such a > | facility > | > | in > | > | > | > GHC, given that the code implementing calling to C functions > | > | must > | > | > | > already be present to implement "proper" FFI imports. I think > | > | > | > such an addition would be useful in many cases. > | > | > | > > | > | > | > Thanks, > | > | > | > Francesco > | > | > | > _______________________________________________ > | > | > | > Haskell-Cafe mailing list > | > | > | > Haskell-Cafe at haskell.org > | > | > | > http://www.haskell.org/mailman/listinfo/haskell-cafe > | > | > | _______________________________________________ > | > | > | ghc-devs mailing list > | > | > | ghc-devs at haskell.org > | > | > | http://www.haskell.org/mailman/listinfo/ghc-devs > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rwbarton at gmail.com Fri Feb 13 20:32:53 2015 From: rwbarton at gmail.com (Reid Barton) Date: Fri, 13 Feb 2015 15:32:53 -0500 Subject: What `reify` sees in Template Haskell In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562C990D@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: On Fri, Feb 13, 2015 at 12:43 PM, Francesco Mazzoli wrote: > Hi Simon, > > On 13 February 2015 at 18:12, Simon Peyton Jones > wrote: > > I don?t think it would be difficult to recover the old behaviour, but > it's not clear to me that it would be a Good Thing. A program that works > today, and then does not work tomorrow because of some incidental change to > the way type inference works, would not be a happy state of affairs. > > In much the same way, programs that rely on the memory representation > that GHC uses for objects can be written with the provided unsafe > functions. In my view, if you make this danger clear, having those > functions is much better than not having them. And it seems like the > Haskell environment generally agree with this view. > Right, but the users of such features understand that their programs may break under future versions of GHC, and don't expect to have any particular recourse if this happens. And this is essentially what happened here. It doesn't make sense to ask about the type of a variable in a TH splice when the result of that splice might affect what type the variable has! Admittedly it was not documented that the behavior of reify was undefined in this case, but I imagine that's because nobody had considered this scenario (if they had, we'd have had the 7.8 design from the start). I don't like it more than anyone else when GHC breaks user programs, but when those programs were dependent on undefined behavior, I think it's incumbent on the user to find a way to rewrite their program so as to not depend on undefined behavior. This might include requesting a new GHC feature with well-defined semantics. Adding the old undefined behavior should be a last resort, and then in the future the undefined behavior might stop giving you the answer you want anyways. > In any case, if I think of some reasonable but more permissive > restriction, I'll write it up. > Have you tried using Typed TH splices? Those interact differently with the type checker, because the type of the expression resulting from a splice is determined by the type of the splice action, and cannot depend upon its value. So, it seems to me that it would be fine to allow reify to ask about the type of a local variable from within a typed splice, and it may work that way already (I haven't tried it). Regards, Reid Barton -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Fri Feb 13 22:45:56 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 13 Feb 2015 22:45:56 +0000 Subject: [Haskell-cafe] Anonymous FFI calls In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562C740B@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C75BE@DB3PRD3001MB020.064d.mgd.msft.net> <618BE556AADD624C9C918AA5D5911BEF562C7741@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562C9B4E@DB3PRD3001MB020.064d.mgd.msft.net> I have started a fresh one here: https://wiki.haskell.org/Foreign_Function_Interface_(FFI) Very helpful thank you. We NEED people to invest effort in good user guides. Do also include info from https://wiki.haskell.org/GHC/Using_the_FFI as well as https://wiki.haskell.org/FFI Once you?ve absorbed them both, kill them off and replace with forwarding pointers. Or better still overwrite one or the other with your new page (people may have bookmarked the old links). What we don?t want is lots of alternative pages, that don?t refer to each other, with contradictory info. Simon From: Sylvain Henry [mailto:hsyl20 at gmail.com] Sent: 13 February 2015 18:28 To: Simon Peyton Jones Cc: Francesco Mazzoli; Manuel Chakravarty; ghc-devs at haskell.org; Geoffrey Mainland (mainland at cs.drexel.edu) Subject: Re: [Haskell-cafe] Anonymous FFI calls Hi, The FFI pages on the wiki are not really in a good shape in my opinion (especially for newcomers). I have started a fresh one here: https://wiki.haskell.org/Foreign_Function_Interface_(FFI) This is just the first draft. I will improve it, probably split it in several pages and merge information from other pages, especially pages linked on https://wiki.haskell.org/FFI Sylvain 2015-02-12 10:02 GMT+01:00 Simon Peyton Jones >: | Thanks to everyone who replied! | | It seems like that through a combination of facilities like `libffi' | and `addTopDecls' I can do everything that I wanted to do. Great. But please, please, do write up what you learned on the FFI wiki page https://wiki.haskell.org/GHC/Using_the_FFI Simon | -----Original Message----- | From: Francesco Mazzoli [mailto:f at mazzo.li] | Sent: 12 February 2015 09:00 | To: Simon Peyton Jones | Cc: Michael Sloan; Manuel Chakravarty; Geoffrey Mainland | (mainland at cs.drexel.edu); ghc-devs at haskell.org; haskell | Subject: Re: [Haskell-cafe] Anonymous FFI calls | | Thanks to everyone who replied! | | It seems like that through a combination of facilities like `libffi' | and `addTopDecls' I can do everything that I wanted to do. | | I still want to take a shot at implementing anonymous FFI calls, since | IMHO I think they are a very small but useful addition to the | language. | | Francesco | | On 12 February 2015 at 09:29, Simon Peyton Jones > | wrote: | > | Also, I meant to say that addTopDecls is only exported by | > | "Language.Haskell.TH.Syntax". While this is a digression, there are | a | > | few other handy functions that are oddly left out of | > | "Language.Haskell.TH": addDependentFile, addModFinalizer, and | possibly | > | more. | > | > That does seem wrong. Do make a patch! | > | > SIMon | > | > | | > | -Michael | > | | > | On Wed, Feb 11, 2015 at 3:25 PM, Simon Peyton Jones | > | > wrote: | > | > I would LOVE someone to improve the documentation for addTopDecls. | > | Manuel Chakravarty and Geoff Mainland were responsible for the | > | implementation. | > | > | > | > Simon | > | > | > | > | -----Original Message----- | > | > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf | Of | > | > | Michael Sloan | > | > | Sent: 11 February 2015 23:19 | > | > | To: Francesco Mazzoli | > | > | Cc: ghc-devs at haskell.org; haskell | > | > | Subject: Re: [Haskell-cafe] Anonymous FFI calls | > | > | | > | > | It seems like addTopDecls[1] will able to help here. | > | Unfortunately, | > | > | the function is not well documented and not very discoverable | > | > | because it's only exported by Language.Haskell.TH. | > | > | | > | > | The documentation doesn't mention that it can only be used to | > | create | > | > | new top level functions and FFI imports[2]. I think that adding | > | FFI | > | > | imports was the main motivation for implementing it. In the | past | > | > | I've wanted to generate instances via this function, but | > | > | unfortunately it's not implemented.. | > | > | | > | > | Hope that helps! | > | > | -Michael | > | > | | > | > | [1] http://hackage.haskell.org/package/template-haskell- | > | > | 2.9.0.0/docs/Language-Haskell-TH-Syntax.html#v:addTopDecls | > | > | | > | > | [2] | > | > | | > | https://github.com/ghc/ghc/blob/1d982ba10f590828b78eba992e73315dee33 | > | > | f78a/ | > | > | compiler/typecheck/TcSplice.hs#L818 | > | > | | > | > | On Wed, Feb 11, 2015 at 2:26 AM, Francesco Mazzoli > | > | wrote: | > | > | > Hi, | > | > | > | > | > | > I am in a situation where it would be very useful to call C | > | > | > functions without an explicit FFI import. For example, I'd | like | > | > | > to be able to do | > | > | > | > | > | > (foreign import ccall "cadd" :: CInt -> CInt -> CInt) 1 2 | > | > | > | > | > | > instead of declaring the foreign import explicitely at the top | > | level. | > | > | > | > | > | > Is there a way to do this or to achieve similar results in | some | > | > | > other way? | > | > | > | > | > | > If not, I imagine it would be easy to implement such a | facility | > | in | > | > | > GHC, given that the code implementing calling to C functions | > | must | > | > | > already be present to implement "proper" FFI imports. I think | > | > | > such an addition would be useful in many cases. | > | > | > | > | > | > Thanks, | > | > | > Francesco | > | > | > _______________________________________________ | > | > | > Haskell-Cafe mailing list | > | > | > Haskell-Cafe at haskell.org | > | > | > http://www.haskell.org/mailman/listinfo/haskell-cafe | > | > | _______________________________________________ | > | > | ghc-devs mailing list | > | > | ghc-devs at haskell.org | > | > | http://www.haskell.org/mailman/listinfo/ghc-devs _______________________________________________ ghc-devs mailing list ghc-devs at haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From dedgrant at gmail.com Sun Feb 15 07:35:55 2015 From: dedgrant at gmail.com (Darren Grant) Date: Sat, 14 Feb 2015 23:35:55 -0800 Subject: Resolving Windows 64-bit linker issues Message-ID: Hi all, I notice there are a series of related long-standing issues subject to particular cygwin64 quirks, and I'd like to offer time to help resolve these if possible At this point I've had some exposure to the GHC build process (7.8.3), and have poked around the GHC linker to gain some low level insight. Would anyone be available to fill me in on the current state of affairs with mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a preferred direction but no available developer bandwidth to proceed? Thank you. Cheers, Darren -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Sun Feb 15 22:11:01 2015 From: bob at redivi.com (Bob Ippolito) Date: Sun, 15 Feb 2015 14:11:01 -0800 Subject: MAC builds of 7.8.4 and 7.10.1 RC2 In-Reply-To: References: Message-ID: Thanks Mark! This build seems to work well. I'm in the process of publishing a new http://ghcformacosx.github.io/ with it. Austin - do you still plan to get these binaries online? I think haskell.org has more bandwidth than ozonehouse.com :) On Thu, Feb 12, 2015 at 7:02 AM, Austin Seipp wrote: > I'll get them online with signed hashes today. > > On Thu, Feb 12, 2015 at 8:20 AM, Ozgur Akgun wrote: > > This is great. > > > > What would one have to do to get this added to > > https://www.haskell.org/ghc/download_ghc_7_8_4 ? > > > > Ozgur > > > > On 11 February 2015 at 06:16, Mark Lentczner > > wrote: > >> > >> My build procedure is very minimal: > >> > >> export MACOSX_DEPLOYMENT_TARGET=10.6 > >> ./configure 2>&1 | tee ../conf.log > >> cat > mk/build.mk < >> V=1 > >> SplitObjs=YES > >> SupportsSplitObjs=YES > >> HADDOCK_DOCS=YES > >> LATEX_DOCS=NO > >> HSCOLOUR_SRCS=YES > >> BUILD_DOCBOOK_HTML=YES > >> BUILD_DOCBOOK_PDF=NO > >> BUILD_DOCBOOK_PS=NO > >> BeConservative=YES > >> END > >> time make -j4 2>&1 | tee ../make.log > >> time make binary-dist 2>&1 | tee ../bd.log > >> > >> That is all! > > > > > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://www.haskell.org/mailman/listinfo/ghc-devs > > > > > > -- > Regards, > > Austin Seipp, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Feb 16 14:43:01 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 16 Feb 2015 14:43:01 +0000 Subject: Resolving Windows 64-bit linker issues In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF562CB5F6@DB3PRD3001MB020.064d.mgd.msft.net> Darren Excellent! We have a Windows Task Force, consisting roughly of the folk in cc. So they would be the first group to ask. (I think it would be very helpful to have a Windows Task Force home page, so that it?s easier to find the group.) thanks for helping with Windows. Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren Grant Sent: 15 February 2015 07:36 To: ghc-devs at haskell.org Subject: Resolving Windows 64-bit linker issues Hi all, I notice there are a series of related long-standing issues subject to particular cygwin64 quirks, and I'd like to offer time to help resolve these if possible At this point I've had some exposure to the GHC build process (7.8.3), and have poked around the GHC linker to gain some low level insight. Would anyone be available to fill me in on the current state of affairs with mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a preferred direction but no available developer bandwidth to proceed? Thank you. Cheers, Darren -------------- next part -------------- An HTML attachment was scrubbed... URL: From kuznero at gmail.com Mon Feb 16 15:23:32 2015 From: kuznero at gmail.com (Roman Kuznetsov) Date: Mon, 16 Feb 2015 16:23:32 +0100 Subject: Resolving Windows 64-bit linker issues In-Reply-To: References: Message-ID: Hello Darren, I am officially on the Windows Task Force group, though didn't have a chance to contribute yet. Primarily due to the lack of time lately and lack of knowledge. Thus, I would suggest myself as not the one who could effectively fill you in on the matter, but rather join you with an attempt to fix some of these issues you mentioned. Please let me know if you are interested in this kind of cooperation. But keep in mind that I am in the process of getting things up and running with regards to GHC build process. /Roman K. On Sun, Feb 15, 2015 at 8:35 AM, Darren Grant wrote: > Hi all, > > I notice there are a series of related long-standing issues subject to > particular cygwin64 quirks, and I'd like to offer time to help resolve > these if possible > > At this point I've had some exposure to the GHC build process (7.8.3), and > have poked around the GHC linker to gain some low level insight. > > Would anyone be available to fill me in on the current state of affairs > with mingw64 GHCi linking? For instance, is there ongoing work, or perhaps > a preferred direction but no available developer bandwidth to proceed? > > Thank you. > > Cheers, > Darren > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -- Sincerely yours, Roman Kuznetsov -------------- next part -------------- An HTML attachment was scrubbed... URL: From mikolaj at well-typed.com Mon Feb 16 15:47:20 2015 From: mikolaj at well-typed.com (Mikolaj Konarski) Date: Mon, 16 Feb 2015 16:47:20 +0100 Subject: Resolving Windows 64-bit linker issues In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562CB5F6@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF562CB5F6@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Resending, since Roman's and Kyril's email addresses were mangled/missing. On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones wrote: > Darren > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk in > cc. So they would be the first group to ask. > > > > (I think it would be very helpful to have a Windows Task Force home page, so > that it?s easier to find the group.) > > > > thanks for helping with Windows. > > > > Simon > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > Grant > Sent: 15 February 2015 07:36 > To: ghc-devs at haskell.org > Subject: Resolving Windows 64-bit linker issues > > > > Hi all, > > > > I notice there are a series of related long-standing issues subject to > particular cygwin64 quirks, and I'd like to offer time to help resolve these > if possible > > At this point I've had some exposure to the GHC build process (7.8.3), and > have poked around the GHC linker to gain some low level insight. > > > > Would anyone be available to fill me in on the current state of affairs with > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > preferred direction but no available developer bandwidth to proceed? > > > > Thank you. > > > > Cheers, > > Darren > > From dedgrant at gmail.com Tue Feb 17 04:48:12 2015 From: dedgrant at gmail.com (Darren Grant) Date: Mon, 16 Feb 2015 20:48:12 -0800 Subject: Resolving Windows 64-bit linker issues In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562CB5F6@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Thank you kindly for the great introduction. I hope I can be helpful here. On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" wrote: > Resending, since Roman's and Kyril's email addresses were mangled/missing. > > On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones > wrote: > > Darren > > > > > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk > in > > cc. So they would be the first group to ask. > > > > > > > > (I think it would be very helpful to have a Windows Task Force home > page, so > > that it?s easier to find the group.) > > > > > > > > thanks for helping with Windows. > > > > > > > > Simon > > > > > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > > Grant > > Sent: 15 February 2015 07:36 > > To: ghc-devs at haskell.org > > Subject: Resolving Windows 64-bit linker issues > > > > > > > > Hi all, > > > > > > > > I notice there are a series of related long-standing issues subject to > > particular cygwin64 quirks, and I'd like to offer time to help resolve > these > > if possible > > > > At this point I've had some exposure to the GHC build process (7.8.3), > and > > have poked around the GHC linker to gain some low level insight. > > > > > > > > Would anyone be available to fill me in on the current state of affairs > with > > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > > preferred direction but no available developer bandwidth to proceed? > > > > > > > > Thank you. > > > > > > > > Cheers, > > > > Darren > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dedgrant at gmail.com Tue Feb 17 05:02:30 2015 From: dedgrant at gmail.com (Darren Grant) Date: Mon, 16 Feb 2015 21:02:30 -0800 Subject: Resolving Windows 64-bit linker issues In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562CB5F6@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: To expand on that (let's see if I can do this without accidentally sending again, oops!): Roman, I will get in touch with you on a separate email thread to see if we can find an optimal way to coordinate, something that satisfies our schedules and needs. Others please feel free to bug me any time by email ( dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. In the meantime I'll be auditing some of the related backlogged tickets on trac. If there's something I can do to help further the goal of a Windows Task Force page, please let me know. Pleased to meet everyone! Cheers, Darren On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: > Thank you kindly for the great introduction. I hope I can be helpful here. > > > On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" > wrote: > >> Resending, since Roman's and Kyril's email addresses were mangled/missing. >> >> On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones >> wrote: >> > Darren >> > >> > >> > >> > Excellent! We have a Windows Task Force, consisting roughly of the >> folk in >> > cc. So they would be the first group to ask. >> > >> > >> > >> > (I think it would be very helpful to have a Windows Task Force home >> page, so >> > that it?s easier to find the group.) >> > >> > >> > >> > thanks for helping with Windows. >> > >> > >> > >> > Simon >> > >> > >> > >> > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of >> Darren >> > Grant >> > Sent: 15 February 2015 07:36 >> > To: ghc-devs at haskell.org >> > Subject: Resolving Windows 64-bit linker issues >> > >> > >> > >> > Hi all, >> > >> > >> > >> > I notice there are a series of related long-standing issues subject to >> > particular cygwin64 quirks, and I'd like to offer time to help resolve >> these >> > if possible >> > >> > At this point I've had some exposure to the GHC build process (7.8.3), >> and >> > have poked around the GHC linker to gain some low level insight. >> > >> > >> > >> > Would anyone be available to fill me in on the current state of affairs >> with >> > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a >> > preferred direction but no available developer bandwidth to proceed? >> > >> > >> > >> > Thank you. >> > >> > >> > >> > Cheers, >> > >> > Darren >> > >> > >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Tue Feb 17 05:10:42 2015 From: lonetiger at gmail.com (=?utf-8?Q?Tamar_Christina?=) Date: Tue, 17 Feb 2015 05:10:42 +0000 Subject: =?utf-8?Q?Re:_Resolving_Windows_64-bit_linker_issues?= In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562CB5F6@DB3PRD3001MB020.064d.mgd.msft.net> , Message-ID: <54e2ce5e.e24cb40a.60a6.1d1c@mx.google.com> Hi Darren, I don?t actually know what the status of these issues are. I think one of the tasks we had set out to do was actually checking on these tickets and their progress. Gintautas was doing most of the mingw64 build stuff. I don?t know if the cygwin64 link stuff has been looked at by anyone since I think we?re all mostly using mingw64. I have two issues I?m working on atm, both related to the RTS. But if there?s anything I can do to help then just let me know. Cheers, Tamar From: Darren Grant Sent: ?Tuesday?, ?February? ?17?, ?2015 ?06?:?02 To: Mikolaj Konarski Cc: Phyx, Roman Kuznetsov, ghc-devs at haskell.org, Simon Peyton Jones, David Macek, kyra, Gintautas Miliauskas, Martin Foster To expand on that (let's see if I can do this without accidentally sending again, oops!): Roman, I will get in touch with you on a separate email thread to see if we can find an optimal way to coordinate, something that satisfies our schedules and needs. Others please feel free to bug me any time by email (dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. In the meantime I'll be auditing some of the related backlogged tickets on trac. If there's something I can do to help further the goal of a Windows Task Force page, please let me know. Pleased to meet everyone! Cheers, Darren On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: Thank you kindly for the great introduction. I hope I can be helpful here. On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" wrote: Resending, since Roman's and Kyril's email addresses were mangled/missing. On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones wrote: > Darren > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk in > cc. So they would be the first group to ask. > > > > (I think it would be very helpful to have a Windows Task Force home page, so > that it?s easier to find the group.) > > > > thanks for helping with Windows. > > > > Simon > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > Grant > Sent: 15 February 2015 07:36 > To: ghc-devs at haskell.org > Subject: Resolving Windows 64-bit linker issues > > > > Hi all, > > > > I notice there are a series of related long-standing issues subject to > particular cygwin64 quirks, and I'd like to offer time to help resolve these > if possible > > At this point I've had some exposure to the GHC build process (7.8.3), and > have poked around the GHC linker to gain some low level insight. > > > > Would anyone be available to fill me in on the current state of affairs with > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > preferred direction but no available developer bandwidth to proceed? > > > > Thank you. > > > > Cheers, > > Darren > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dedgrant at gmail.com Tue Feb 17 05:57:47 2015 From: dedgrant at gmail.com (Darren Grant) Date: Mon, 16 Feb 2015 21:57:47 -0800 Subject: Resolving Windows 64-bit linker issues In-Reply-To: <54e2ce5e.e24cb40a.60a6.1d1c@mx.google.com> References: <618BE556AADD624C9C918AA5D5911BEF562CB5F6@DB3PRD3001MB020.064d.mgd.msft.net> <54e2ce5e.e24cb40a.60a6.1d1c@mx.google.com> Message-ID: Hi Tamar, Thank you for the offer. Do you have any thoughts or advice on approaching changes to the existing PE code in Linker.c? I'm wondering if this was destined to be extended into support for PE+ given the absence of .refptr and $. Cheers, Darren On Mon, Feb 16, 2015 at 9:10 PM, Tamar Christina wrote: > Hi Darren, > > I don?t actually know what the status of these issues are. I think one of > the tasks we had set out to do was actually checking on these tickets and > their progress. > > Gintautas was doing most of the mingw64 build stuff. I don?t know if the > cygwin64 link stuff has been looked at by anyone since I think we?re all > mostly using mingw64. > > I have two issues I?m working on atm, both related to the RTS. But if > there?s anything I can do to help then just let me know. > > Cheers, > Tamar > > *From:* Darren Grant > *Sent:* ?Tuesday?, ?February? ?17?, ?2015 ?06?:?02 > *To:* Mikolaj Konarski > *Cc:* Phyx , Roman Kuznetsov , > ghc-devs at haskell.org, Simon Peyton Jones , David > Macek , kyra , Gintautas > Miliauskas , Martin Foster > > > To expand on that (let's see if I can do this without accidentally sending > again, oops!): > > Roman, I will get in touch with you on a separate email thread to see if > we can find an optimal way to coordinate, something that satisfies our > schedules and needs. Others please feel free to bug me any time by email ( > dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. > > In the meantime I'll be auditing some of the related backlogged tickets on > trac. If there's something I can do to help further the goal of a Windows > Task Force page, please let me know. > > > Pleased to meet everyone! > > Cheers, > Darren > > > On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: > >> Thank you kindly for the great introduction. I hope I can be helpful here. >> >> >> On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" >> wrote: >> >>> Resending, since Roman's and Kyril's email addresses were >>> mangled/missing. >>> >>> On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones >>> wrote: >>> > Darren >>> > >>> > >>> > >>> > Excellent! We have a Windows Task Force, consisting roughly of the >>> folk in >>> > cc. So they would be the first group to ask. >>> > >>> > >>> > >>> > (I think it would be very helpful to have a Windows Task Force home >>> page, so >>> > that it?s easier to find the group.) >>> > >>> > >>> > >>> > thanks for helping with Windows. >>> > >>> > >>> > >>> > Simon >>> > >>> > >>> > >>> > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of >>> Darren >>> > Grant >>> > Sent: 15 February 2015 07:36 >>> > To: ghc-devs at haskell.org >>> > Subject: Resolving Windows 64-bit linker issues >>> > >>> > >>> > >>> > Hi all, >>> > >>> > >>> > >>> > I notice there are a series of related long-standing issues subject to >>> > particular cygwin64 quirks, and I'd like to offer time to help resolve >>> these >>> > if possible >>> > >>> > At this point I've had some exposure to the GHC build process (7.8.3), >>> and >>> > have poked around the GHC linker to gain some low level insight. >>> > >>> > >>> > >>> > Would anyone be available to fill me in on the current state of >>> affairs with >>> > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a >>> > preferred direction but no available developer bandwidth to proceed? >>> > >>> > >>> > >>> > Thank you. >>> > >>> > >>> > >>> > Cheers, >>> > >>> > Darren >>> > >>> > >>> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Tue Feb 17 07:41:57 2015 From: lonetiger at gmail.com (Tamar Christina) Date: Mon, 16 Feb 2015 23:41:57 -0800 Subject: Resolving Windows 64-bit linker issues Message-ID: <-2654225973446051887@unknownmsgid> Hi Darren, I'm afraid I don't off the top of my head. I've never had to look at that file yet. On my way to work this morning I was reading up on what mingw64 uses .refptr for. So now I understand at least that part. But I'm afraid I can't offer any advice on how to tackle it in GHC at the moment. Regards, Tamar Sent from my Windows Phone ------------------------------ From: Darren Grant Sent: ?17/?02/?2015 06:57 To: Tamar Christina Cc: Mikolaj Konarski ; Roman Kuznetsov ; ghc-devs at haskell.org; Simon Peyton Jones ; David Macek ; kyra ; Gintautas Miliauskas ; Martin Foster Subject: Re: Resolving Windows 64-bit linker issues Hi Tamar, Thank you for the offer. Do you have any thoughts or advice on approaching changes to the existing PE code in Linker.c? I'm wondering if this was destined to be extended into support for PE+ given the absence of .refptr and $. Cheers, Darren On Mon, Feb 16, 2015 at 9:10 PM, Tamar Christina wrote: > Hi Darren, > > I don?t actually know what the status of these issues are. I think one of > the tasks we had set out to do was actually checking on these tickets and > their progress. > > Gintautas was doing most of the mingw64 build stuff. I don?t know if the > cygwin64 link stuff has been looked at by anyone since I think we?re all > mostly using mingw64. > > I have two issues I?m working on atm, both related to the RTS. But if > there?s anything I can do to help then just let me know. > > Cheers, > Tamar > > *From:* Darren Grant > *Sent:* ?Tuesday?, ?February? ?17?, ?2015 ?06?:?02 > *To:* Mikolaj Konarski > *Cc:* Phyx , Roman Kuznetsov , > ghc-devs at haskell.org, Simon Peyton Jones , David > Macek , kyra , Gintautas > Miliauskas , Martin Foster > > > To expand on that (let's see if I can do this without accidentally sending > again, oops!): > > Roman, I will get in touch with you on a separate email thread to see if > we can find an optimal way to coordinate, something that satisfies our > schedules and needs. Others please feel free to bug me any time by email ( > dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. > > In the meantime I'll be auditing some of the related backlogged tickets on > trac. If there's something I can do to help further the goal of a Windows > Task Force page, please let me know. > > > Pleased to meet everyone! > > Cheers, > Darren > > > On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: > >> Thank you kindly for the great introduction. I hope I can be helpful here. >> >> >> On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" >> wrote: >> >>> Resending, since Roman's and Kyril's email addresses were >>> mangled/missing. >>> >>> On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones >>> wrote: >>> > Darren >>> > >>> > >>> > >>> > Excellent! We have a Windows Task Force, consisting roughly of the >>> folk in >>> > cc. So they would be the first group to ask. >>> > >>> > >>> > >>> > (I think it would be very helpful to have a Windows Task Force home >>> page, so >>> > that it?s easier to find the group.) >>> > >>> > >>> > >>> > thanks for helping with Windows. >>> > >>> > >>> > >>> > Simon >>> > >>> > >>> > >>> > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of >>> Darren >>> > Grant >>> > Sent: 15 February 2015 07:36 >>> > To: ghc-devs at haskell.org >>> > Subject: Resolving Windows 64-bit linker issues >>> > >>> > >>> > >>> > Hi all, >>> > >>> > >>> > >>> > I notice there are a series of related long-standing issues subject to >>> > particular cygwin64 quirks, and I'd like to offer time to help resolve >>> these >>> > if possible >>> > >>> > At this point I've had some exposure to the GHC build process (7.8.3), >>> and >>> > have poked around the GHC linker to gain some low level insight. >>> > >>> > >>> > >>> > Would anyone be available to fill me in on the current state of >>> affairs with >>> > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a >>> > preferred direction but no available developer bandwidth to proceed? >>> > >>> > >>> > >>> > Thank you. >>> > >>> > >>> > >>> > Cheers, >>> > >>> > Darren >>> > >>> > >>> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Feb 17 09:16:36 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 17 Feb 2015 09:16:36 +0000 Subject: Resolving Windows 64-bit linker issues In-Reply-To: References: <618BE556AADD624C9C918AA5D5911BEF562CB5F6@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562CC39C@DB3PRD3001MB020.064d.mgd.msft.net> One really helpful thing would be to ? make a wiki home page for the Windows Task Force ? list who is on it ? list the main tasks ?in flight? and what their status is ? any other plans Anything to broaden visibility of the WTF, and encourage others to join in. Communication is all in an open-source context! Thanks for working on Windows? it?s a very popular platform, and needs your love! Simon From: Darren Grant [mailto:dedgrant at gmail.com] Sent: 17 February 2015 05:03 To: Mikolaj Konarski Cc: Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; David Macek; kyrab; Gintautas Miliauskas; Martin Foster Subject: Re: Resolving Windows 64-bit linker issues To expand on that (let's see if I can do this without accidentally sending again, oops!): Roman, I will get in touch with you on a separate email thread to see if we can find an optimal way to coordinate, something that satisfies our schedules and needs. Others please feel free to bug me any time by email (dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. In the meantime I'll be auditing some of the related backlogged tickets on trac. If there's something I can do to help further the goal of a Windows Task Force page, please let me know. Pleased to meet everyone! Cheers, Darren On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant > wrote: Thank you kindly for the great introduction. I hope I can be helpful here. On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" > wrote: Resending, since Roman's and Kyril's email addresses were mangled/missing. On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones > wrote: > Darren > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk in > cc. So they would be the first group to ask. > > > > (I think it would be very helpful to have a Windows Task Force home page, so > that it?s easier to find the group.) > > > > thanks for helping with Windows. > > > > Simon > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > Grant > Sent: 15 February 2015 07:36 > To: ghc-devs at haskell.org > Subject: Resolving Windows 64-bit linker issues > > > > Hi all, > > > > I notice there are a series of related long-standing issues subject to > particular cygwin64 quirks, and I'd like to offer time to help resolve these > if possible > > At this point I've had some exposure to the GHC build process (7.8.3), and > have poked around the GHC linker to gain some low level insight. > > > > Would anyone be available to fill me in on the current state of affairs with > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > preferred direction but no available developer bandwidth to proceed? > > > > Thank you. > > > > Cheers, > > Darren > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Tue Feb 17 10:14:58 2015 From: lonetiger at gmail.com (Tamar Christina) Date: Tue, 17 Feb 2015 02:14:58 -0800 Subject: Resolving Windows 64-bit linker issues Message-ID: <2350464511293266495@unknownmsgid> Hi Simon, We do have a page on Trac with the members: https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce We could add the extra information there. Regards, Tamar ------------------------------ From: Simon Peyton Jones Sent: ?17/?02/?2015 10:18 To: Darren Grant ; Mikolaj Konarski Cc: Phyx ; Roman Kuznetsov ; ghc-devs at haskell.org; David Macek ; kyrab ; Gintautas Miliauskas ; Martin Foster Subject: RE: Resolving Windows 64-bit linker issues One really helpful thing would be to ? make a wiki home page for the Windows Task Force ? list who is on it ? list the main tasks ?in flight? and what their status is ? any other plans Anything to broaden visibility of the WTF, and encourage others to join in. Communication is all in an open-source context! Thanks for working on Windows? it?s a very popular platform, and needs your love! Simon *From:* Darren Grant [mailto:dedgrant at gmail.com] *Sent:* 17 February 2015 05:03 *To:* Mikolaj Konarski *Cc:* Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; David Macek; kyrab; Gintautas Miliauskas; Martin Foster *Subject:* Re: Resolving Windows 64-bit linker issues To expand on that (let's see if I can do this without accidentally sending again, oops!): Roman, I will get in touch with you on a separate email thread to see if we can find an optimal way to coordinate, something that satisfies our schedules and needs. Others please feel free to bug me any time by email ( dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. In the meantime I'll be auditing some of the related backlogged tickets on trac. If there's something I can do to help further the goal of a Windows Task Force page, please let me know. Pleased to meet everyone! Cheers, Darren On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: Thank you kindly for the great introduction. I hope I can be helpful here. On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" wrote: Resending, since Roman's and Kyril's email addresses were mangled/missing. On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones wrote: > Darren > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk in > cc. So they would be the first group to ask. > > > > (I think it would be very helpful to have a Windows Task Force home page, so > that it?s easier to find the group.) > > > > thanks for helping with Windows. > > > > Simon > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > Grant > Sent: 15 February 2015 07:36 > To: ghc-devs at haskell.org > Subject: Resolving Windows 64-bit linker issues > > > > Hi all, > > > > I notice there are a series of related long-standing issues subject to > particular cygwin64 quirks, and I'd like to offer time to help resolve these > if possible > > At this point I've had some exposure to the GHC build process (7.8.3), and > have poked around the GHC linker to gain some low level insight. > > > > Would anyone be available to fill me in on the current state of affairs with > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > preferred direction but no available developer bandwidth to proceed? > > > > Thank you. > > > > Cheers, > > Darren > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Feb 17 11:21:49 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 17 Feb 2015 11:21:49 +0000 Subject: Resolving Windows 64-bit linker issues In-Reply-To: <2350464511293266495@unknownmsgid> References: <2350464511293266495@unknownmsgid> Message-ID: <618BE556AADD624C9C918AA5D5911BEF562CC8BE@DB3PRD3001MB020.064d.mgd.msft.net> Ah yes, so we do! Excellent. Maybe add Darren ? Also should Martin Foster, David Macek be there? I?m sure there is a ?how to build GHC on Windows? page (indeed there were too many at one stage). But none of them is listed under ?Platform-specific building notes? on https://ghc.haskell.org/trac/ghc/wiki/Building. Would that be worth fixing? Simon From: Tamar Christina [mailto:lonetiger at gmail.com] Sent: 17 February 2015 10:15 To: Simon Peyton Jones; Darren Grant; Mikolaj Konarski Cc: Roman Kuznetsov; ghc-devs at haskell.org; David Macek; kyrab; Gintautas Miliauskas; Martin Foster Subject: RE: Resolving Windows 64-bit linker issues Hi Simon, We do have a page on Trac with the members: https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce We could add the extra information there. Regards, Tamar ________________________________ From: Simon Peyton Jones Sent: ?17/?02/?2015 10:18 To: Darren Grant; Mikolaj Konarski Cc: Phyx; Roman Kuznetsov; ghc-devs at haskell.org; David Macek; kyrab; Gintautas Miliauskas; Martin Foster Subject: RE: Resolving Windows 64-bit linker issues One really helpful thing would be to ? make a wiki home page for the Windows Task Force ? list who is on it ? list the main tasks ?in flight? and what their status is ? any other plans Anything to broaden visibility of the WTF, and encourage others to join in. Communication is all in an open-source context! Thanks for working on Windows? it?s a very popular platform, and needs your love! Simon From: Darren Grant [mailto:dedgrant at gmail.com] Sent: 17 February 2015 05:03 To: Mikolaj Konarski Cc: Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; David Macek; kyrab; Gintautas Miliauskas; Martin Foster Subject: Re: Resolving Windows 64-bit linker issues To expand on that (let's see if I can do this without accidentally sending again, oops!): Roman, I will get in touch with you on a separate email thread to see if we can find an optimal way to coordinate, something that satisfies our schedules and needs. Others please feel free to bug me any time by email (dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. In the meantime I'll be auditing some of the related backlogged tickets on trac. If there's something I can do to help further the goal of a Windows Task Force page, please let me know. Pleased to meet everyone! Cheers, Darren On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant > wrote: Thank you kindly for the great introduction. I hope I can be helpful here. On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" > wrote: Resending, since Roman's and Kyril's email addresses were mangled/missing. On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones > wrote: > Darren > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk in > cc. So they would be the first group to ask. > > > > (I think it would be very helpful to have a Windows Task Force home page, so > that it?s easier to find the group.) > > > > thanks for helping with Windows. > > > > Simon > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > Grant > Sent: 15 February 2015 07:36 > To: ghc-devs at haskell.org > Subject: Resolving Windows 64-bit linker issues > > > > Hi all, > > > > I notice there are a series of related long-standing issues subject to > particular cygwin64 quirks, and I'd like to offer time to help resolve these > if possible > > At this point I've had some exposure to the GHC build process (7.8.3), and > have poked around the GHC linker to gain some low level insight. > > > > Would anyone be available to fill me in on the current state of affairs with > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > preferred direction but no available developer bandwidth to proceed? > > > > Thank you. > > > > Cheers, > > Darren > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gintautas at miliauskas.lt Tue Feb 17 11:56:16 2015 From: gintautas at miliauskas.lt (Gintautas Miliauskas) Date: Tue, 17 Feb 2015 11:56:16 +0000 Subject: Resolving Windows 64-bit linker issues In-Reply-To: <2350464511293266495@unknownmsgid> References: <2350464511293266495@unknownmsgid> Message-ID: Hi, would someone be willing to be a coordinator for the team? Feel free to just edit the wiki. I am completely swamped by my new job and my move to London at the moment, and the situation is unlikely to change soon. Sorry :( On Tue, Feb 17, 2015 at 10:14 AM, Tamar Christina wrote: > Hi Simon, > > We do have a page on Trac with the members: > https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce > > We could add the extra information there. > > Regards, > Tamar > ------------------------------ > From: Simon Peyton Jones > Sent: ?17/?02/?2015 10:18 > To: Darren Grant ; Mikolaj Konarski > > Cc: Phyx ; Roman Kuznetsov ; > ghc-devs at haskell.org; David Macek ; kyrab > ; Gintautas Miliauskas ; Martin > Foster > Subject: RE: Resolving Windows 64-bit linker issues > > One really helpful thing would be to > > ? make a wiki home page for the Windows Task Force > > ? list who is on it > > ? list the main tasks ?in flight? and what their status is > > ? any other plans > > Anything to broaden visibility of the WTF, and encourage others to join > in. Communication is all in an open-source context! > > > > Thanks for working on Windows? it?s a very popular platform, and needs > your love! > > > > Simon > > > > *From:* Darren Grant [mailto:dedgrant at gmail.com] > *Sent:* 17 February 2015 05:03 > *To:* Mikolaj Konarski > *Cc:* Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; > David Macek; kyrab; Gintautas Miliauskas; Martin Foster > *Subject:* Re: Resolving Windows 64-bit linker issues > > > > To expand on that (let's see if I can do this without accidentally sending > again, oops!): > > Roman, I will get in touch with you on a separate email thread to see if > we can find an optimal way to coordinate, something that satisfies our > schedules and needs. Others please feel free to bug me any time by email ( > dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. > > In the meantime I'll be auditing some of the related backlogged tickets on > trac. If there's something I can do to help further the goal of a Windows > Task Force page, please let me know. > > > Pleased to meet everyone! > > Cheers, > > Darren > > > > > > On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: > > Thank you kindly for the great introduction. I hope I can be helpful > here. > > On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" > wrote: > > Resending, since Roman's and Kyril's email addresses were mangled/missing. > > On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones > wrote: > > Darren > > > > > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk > in > > cc. So they would be the first group to ask. > > > > > > > > (I think it would be very helpful to have a Windows Task Force home > page, so > > that it?s easier to find the group.) > > > > > > > > thanks for helping with Windows. > > > > > > > > Simon > > > > > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > > Grant > > Sent: 15 February 2015 07:36 > > To: ghc-devs at haskell.org > > Subject: Resolving Windows 64-bit linker issues > > > > > > > > Hi all, > > > > > > > > I notice there are a series of related long-standing issues subject to > > particular cygwin64 quirks, and I'd like to offer time to help resolve > these > > if possible > > > > At this point I've had some exposure to the GHC build process (7.8.3), > and > > have poked around the GHC linker to gain some low level insight. > > > > > > > > Would anyone be available to fill me in on the current state of affairs > with > > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > > preferred direction but no available developer bandwidth to proceed? > > > > > > > > Thank you. > > > > > > > > Cheers, > > > > Darren > > > > > > > -- Gintautas Miliauskas -------------- next part -------------- An HTML attachment was scrubbed... URL: From takenobu.hs at gmail.com Tue Feb 17 12:47:50 2015 From: takenobu.hs at gmail.com (Takenobu Tani) Date: Tue, 17 Feb 2015 21:47:50 +0900 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: References: Message-ID: Hi, I modified System/Process/Internals.hs locally and build on MinGW 32bit. Then I was successful to build on 32bit Windows 7. Shall I write a bug report on trac or any? or ghc7.10.1.rc2 will not support 32 bit Windows? Change part is the following: diff -u ghc-7.10.0.20150123/libraries/process/System/Process/ Internals.hs.org ghc-7.10.0.20150123/libraries/process/System/Process/Internals.hs --- ghc-7.10.0.20150123/libraries/process/System/Process/Internals.hs.org 2015-01-19 21:37:52 +0900 +++ ghc-7.10.0.20150123/libraries/process/System/Process/Internals.hs 2015-02-17 13:50:31 +0900 @@ -469,6 +469,9 @@ endDelegateControlC :: ExitCode -> IO () endDelegateControlC _ = return () +stopDelegateControlC :: IO () +stopDelegateControlC = return () + foreign import ccall unsafe "runInteractiveProcess" c_runInteractiveProcess :: CWString Regards, Takenobu 2015-02-13 19:35 GMT+09:00 Takenobu Tani : > Hi, > > Does ghc7.10rc2 support for windows 32bit OS (Windows 7) ? > > I tried to build ghc7.10rc2 [1],[2] on my old 32bit windows to check FTP. > Then, the following error has occurred: > > > "C:/MinGW/msys/1.0/home/my/devel/haskell.build.mingw/work8.ghc.7.10.rc2/ghc-7.10.0.20150123/inplace/mingw/bin/ld.exe" > -r -o > libraries/directory/dist-install/build/HSdirec_3OAebvWY9YTGrbhfMGQ0ml.o > libraries/directory/dist-install/build/System/Directory.o > libraries/directory/dist-install/build/cbits/directory.o > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -H64m > -O0 -fasm -this-package-key proce_9HgSaudU0TAKauLzQHuwnO > -hide-all-packages -i -ilibraries/process/. > -ilibraries/process/dist-install/build > -ilibraries/process/dist-install/build/autogen > -Ilibraries/process/dist-install/build > -Ilibraries/process/dist-install/build/autogen -Ilibraries/process/include > -optP-include > -optPlibraries/process/dist-install/build/autogen/cabal_macros.h > -package-key Win32_Cjc5QN7bEuvL7SrTr96E5g -package-key > base_469rOtLAqwTGFEOGWxSUiQ -package-key deeps_FT5iVCELxOr62eHY0nbvnU > -package-key direc_3OAebvWY9YTGrbhfMGQ0ml -package-key > filep_1vDJvPDP7mkAk0dVCj6gws -Wall -XHaskell2010 -O -fasm > -no-user-package-db -rtsopts -odir > libraries/process/dist-install/build -hidir > libraries/process/dist-install/build -stubdir > libraries/process/dist-install/build -c > libraries/process/./System/Process/Internals.hs -o > libraries/process/dist-install/build/System/Process/Internals.o > > libraries\process\System\Process\Internals.hs:36:5: > Not in scope: <81>estopDelegateControlC<81>f > Perhaps you meant one of these: > <81>estartDelegateControlC<81>f (line 467), > <81>eendDelegateControlC<81>f (line 470) > make[1]: *** > [libraries/process/dist-install/build/System/Process/Internals.o] Error 1 > make: *** [all] Error 2 > > > > I looks like 'stopDelegateControl' is not defined in > System\Process\Internals.hs for mingw32_HOST_OS. > > > [1]: > https://downloads.haskell.org/~ghc/7.10.1-rc2/ghc-7.10.0.20150123-src.tar.bz2 > [2]: > https://downloads.haskell.org/~ghc/7.10.1-rc2/ghc-7.10.0.20150123-windows-extra-src.tar.bz2 > > > Regards, > Takenobu > > > > > > 2015-01-27 9:13 GMT+09:00 Austin Seipp : > >> We are pleased to announce the second release candidate for GHC 7.10.1: >> >> https://downloads.haskell.org/~ghc/7.10.1-rc2/ >> >> This includes the source tarball and bindists for 64bit/32bit Linux >> and Windows. Binary builds for other platforms will be available >> shortly. (CentOS 6.5 binaries are not available at this time like they >> were for 7.8.x). These binaries and tarballs have an accompanying >> SHA256SUMS file signed by my GPG key id (0x3B58D86F). >> >> We plan to make the 7.10.1 release sometime in February of 2015. >> >> Please test as much as possible; bugs are much cheaper if we find them >> before the release! >> >> -- >> Regards, >> >> Austin Seipp, Haskell Consultant >> Well-Typed LLP, http://www.well-typed.com/ >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://www.haskell.org/mailman/listinfo/ghc-devs >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hvriedel at gmail.com Tue Feb 17 13:02:55 2015 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Tue, 17 Feb 2015 14:02:55 +0100 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: (Takenobu Tani's message of "Tue, 17 Feb 2015 21:47:50 +0900") References: Message-ID: <87wq3gitc0.fsf@gmail.com> On 2015-02-17 at 13:47:50 +0100, Takenobu Tani wrote: > I modified System/Process/Internals.hs locally and build on MinGW 32bit. > Then I was successful to build on 32bit Windows 7. > > Shall I write a bug report on trac or any? or ghc7.10.1.rc2 will not > support 32 bit Windows? Please file a pull-request at https://github.com/haskell/process I'm somewhat surprised this wasn't noticed before(?) From jan.stolarek at p.lodz.pl Tue Feb 17 13:19:43 2015 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Tue, 17 Feb 2015 14:19:43 +0100 Subject: Building vector with GHC HEAD Message-ID: <201502171419.44155.jan.stolarek@p.lodz.pl> Devs, I'm not sure if this is the best place to ask this question but I'm almost certain someone here will have the answer. I want to build upstream master branch of vector library using GHC HEAD and cabal 1.22. Alas my attempts have failed: $ git clone git at github.com:haskell/vector.git $ cd vector $ cabal sandbox init $ cabal install -w /dane/projekty/ghc/build/inplace/bin/ghc-stage2 Resolving dependencies... cabal: Could not resolve dependencies: trying: vector-0.11.0.0 (user goal) trying: base-4.8.0.0/installed-inp... (dependency of vector-0.11.0.0) next goal: deepseq (dependency of vector-0.11.0.0) rejecting: deepseq-1.4.0.0/installed-inp..., 1.4.0.0 (conflict: vector => deepseq>=1.1 && <1.4) rejecting: deepseq-1.3.0.2 (conflict: base==4.8.0.0/installed-inp..., deepseq => base>=4.3 && <4.8) trying: deepseq-1.3.0.1 next goal: array (dependency of deepseq-1.3.0.1) rejecting: array-0.5.0.1/installed-inp..., 0.5.0.0 (conflict: deepseq => array>=0.1 && <0.5) rejecting: array-0.4.0.1 (conflict: base==4.8.0.0/installed-inp..., array => base>=4.2 && <4.7) rejecting: array-0.4.0.0 (conflict: base==4.8.0.0/installed-inp..., array => base>=4.2 && <4.6) rejecting: array-0.3.0.3 (conflict: base==4.8.0.0/installed-inp..., array => base>=4.2 && <4.5) rejecting: array-0.3.0.2, 0.3.0.1 (conflict: base==4.8.0.0/installed-inp..., array => base>=4.2 && <4.4) rejecting: array-0.3.0.0 (conflict: base==4.8.0.0/installed-inp..., array => base>=3 && <4.4) rejecting: array-0.2.0.0, 0.1.0.0 (conflict: base==4.8.0.0/installed-inp..., array => base<4.3) Dependency tree exhaustively searched. The problem arises from vector requiring deepseq < 1.4 when intree package db contains deepseq 1.4. Removing the upper bound on deepseq in vector.cabal allows to resolve dependencies but ends with a build error: Data/Vector/Primitive/Mutable.hs:78:10: No instance for (GHC.Generics.Generic (MVector s a)) arising from a use of ?Control.DeepSeq.$gdmrnf? In the expression: Control.DeepSeq.$gdmrnf In an equation for ?rnf?: rnf = Control.DeepSeq.$gdmrnf In the instance declaration for ?NFData (MVector s a)? Fixing this error (importing GHC.Generics & deriving `Generic` instance for `MVector s a`) leads to another one: Data/Vector/Primitive/Mutable.hs:80:10: No instance for (Control.DeepSeq.GNFData (Rep (MVector s a))) arising from a use of ?Control.DeepSeq.$gdmrnf? In the expression: Control.DeepSeq.$gdmrnf In an equation for ?rnf?: rnf = Control.DeepSeq.$gdmrnf In the instance declaration for ?NFData (MVector s a)? This time I have no idea how to fix it since GNFData is an internal class of Control.Deepseq module. Help? Aside: at first I thought vector is one of the boot libraries since it is kept in the source tree. But then I realized it is not being build during bootstrapping. Why do we keep it in the source tree then? Janek --- Politechnika ??dzka Lodz University of Technology Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez pomy?k? prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. This email contains information intended solely for the use of the individual to whom it is addressed. If you are not the intended recipient or if you have received this message in error, please notify the sender and delete it from your system. From roma at ro-che.info Tue Feb 17 13:39:39 2015 From: roma at ro-che.info (Roman Cheplyaka) Date: Tue, 17 Feb 2015 15:39:39 +0200 Subject: Building vector with GHC HEAD In-Reply-To: <201502171419.44155.jan.stolarek@p.lodz.pl> References: <201502171419.44155.jan.stolarek@p.lodz.pl> Message-ID: <54E3449B.7070000@ro-che.info> See http://bit.ly/1CDVOIZ On 17/02/15 15:19, Jan Stolarek wrote: > Devs, > > I'm not sure if this is the best place to ask this question but I'm almost certain someone here > will have the answer. I want to build upstream master branch of vector library using GHC HEAD and > cabal 1.22. Alas my attempts have failed: > > $ git clone git at github.com:haskell/vector.git > $ cd vector > $ cabal sandbox init > $ cabal install -w /dane/projekty/ghc/build/inplace/bin/ghc-stage2 > Resolving dependencies... > cabal: Could not resolve dependencies: > trying: vector-0.11.0.0 (user goal) > trying: base-4.8.0.0/installed-inp... (dependency of vector-0.11.0.0) > next goal: deepseq (dependency of vector-0.11.0.0) > rejecting: deepseq-1.4.0.0/installed-inp..., 1.4.0.0 (conflict: vector => > deepseq>=1.1 && <1.4) > rejecting: deepseq-1.3.0.2 (conflict: base==4.8.0.0/installed-inp..., deepseq > => base>=4.3 && <4.8) > trying: deepseq-1.3.0.1 > next goal: array (dependency of deepseq-1.3.0.1) > rejecting: array-0.5.0.1/installed-inp..., 0.5.0.0 (conflict: deepseq => > array>=0.1 && <0.5) > rejecting: array-0.4.0.1 (conflict: base==4.8.0.0/installed-inp..., array => > base>=4.2 && <4.7) > rejecting: array-0.4.0.0 (conflict: base==4.8.0.0/installed-inp..., array => > base>=4.2 && <4.6) > rejecting: array-0.3.0.3 (conflict: base==4.8.0.0/installed-inp..., array => > base>=4.2 && <4.5) > rejecting: array-0.3.0.2, 0.3.0.1 (conflict: base==4.8.0.0/installed-inp..., > array => base>=4.2 && <4.4) > rejecting: array-0.3.0.0 (conflict: base==4.8.0.0/installed-inp..., array => > base>=3 && <4.4) > rejecting: array-0.2.0.0, 0.1.0.0 (conflict: base==4.8.0.0/installed-inp..., > array => base<4.3) > Dependency tree exhaustively searched. > > The problem arises from vector requiring deepseq < 1.4 when intree package db contains deepseq > 1.4. Removing the upper bound on deepseq in vector.cabal allows to resolve dependencies but ends > with a build error: > > Data/Vector/Primitive/Mutable.hs:78:10: > No instance for (GHC.Generics.Generic (MVector s a)) > arising from a use of ?Control.DeepSeq.$gdmrnf? > In the expression: Control.DeepSeq.$gdmrnf > In an equation for ?rnf?: rnf = Control.DeepSeq.$gdmrnf > In the instance declaration for ?NFData (MVector s a)? > > Fixing this error (importing GHC.Generics & deriving `Generic` instance for `MVector s a`) leads > to another one: > > Data/Vector/Primitive/Mutable.hs:80:10: > No instance for (Control.DeepSeq.GNFData (Rep (MVector s a))) > arising from a use of ?Control.DeepSeq.$gdmrnf? > In the expression: Control.DeepSeq.$gdmrnf > In an equation for ?rnf?: rnf = Control.DeepSeq.$gdmrnf > In the instance declaration for ?NFData (MVector s a)? > > This time I have no idea how to fix it since GNFData is an internal class of Control.Deepseq > module. Help? > > Aside: at first I thought vector is one of the boot libraries since it is kept in the source tree. > But then I realized it is not being build during bootstrapping. Why do we keep it in the source > tree then? > > Janek > > --- > Politechnika ??dzka > Lodz University of Technology > > Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. > Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez pomy?k? > prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. > > This email contains information intended solely for the use of the individual to whom it is addressed. > If you are not the intended recipient or if you have received this message in error, > please notify the sender and delete it from your system. > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From kuznero at gmail.com Tue Feb 17 13:45:21 2015 From: kuznero at gmail.com (Roman Kuznetsov) Date: Tue, 17 Feb 2015 14:45:21 +0100 Subject: Resolving Windows 64-bit linker issues In-Reply-To: References: <2350464511293266495@unknownmsgid> Message-ID: Hi, That would definitely make sense to add more information for Windows in "Platform-specific build notes". I will try taking care of it the coming week. Roman On Tue, Feb 17, 2015 at 12:56 PM, Gintautas Miliauskas < gintautas at miliauskas.lt> wrote: > Hi, > > would someone be willing to be a coordinator for the team? Feel free to > just edit the wiki. I am completely swamped by my new job and my move to > London at the moment, and the situation is unlikely to change soon. Sorry :( > > On Tue, Feb 17, 2015 at 10:14 AM, Tamar Christina > wrote: > >> Hi Simon, >> >> We do have a page on Trac with the members: >> https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce >> >> We could add the extra information there. >> >> Regards, >> Tamar >> ------------------------------ >> From: Simon Peyton Jones >> Sent: ?17/?02/?2015 10:18 >> To: Darren Grant ; Mikolaj Konarski >> >> Cc: Phyx ; Roman Kuznetsov ; >> ghc-devs at haskell.org; David Macek ; kyrab >> ; Gintautas Miliauskas ; Martin >> Foster >> Subject: RE: Resolving Windows 64-bit linker issues >> >> One really helpful thing would be to >> >> ? make a wiki home page for the Windows Task Force >> >> ? list who is on it >> >> ? list the main tasks ?in flight? and what their status is >> >> ? any other plans >> >> Anything to broaden visibility of the WTF, and encourage others to join >> in. Communication is all in an open-source context! >> >> >> >> Thanks for working on Windows? it?s a very popular platform, and needs >> your love! >> >> >> >> Simon >> >> >> >> *From:* Darren Grant [mailto:dedgrant at gmail.com] >> *Sent:* 17 February 2015 05:03 >> *To:* Mikolaj Konarski >> *Cc:* Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; >> David Macek; kyrab; Gintautas Miliauskas; Martin Foster >> *Subject:* Re: Resolving Windows 64-bit linker issues >> >> >> >> To expand on that (let's see if I can do this without accidentally >> sending again, oops!): >> >> Roman, I will get in touch with you on a separate email thread to see if >> we can find an optimal way to coordinate, something that satisfies our >> schedules and needs. Others please feel free to bug me any time by email ( >> dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. >> >> In the meantime I'll be auditing some of the related backlogged tickets >> on trac. If there's something I can do to help further the goal of a >> Windows Task Force page, please let me know. >> >> >> Pleased to meet everyone! >> >> Cheers, >> >> Darren >> >> >> >> >> >> On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: >> >> Thank you kindly for the great introduction. I hope I can be helpful >> here. >> >> On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" >> wrote: >> >> Resending, since Roman's and Kyril's email addresses were mangled/missing. >> >> On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones >> wrote: >> > Darren >> > >> > >> > >> > Excellent! We have a Windows Task Force, consisting roughly of the >> folk in >> > cc. So they would be the first group to ask. >> > >> > >> > >> > (I think it would be very helpful to have a Windows Task Force home >> page, so >> > that it?s easier to find the group.) >> > >> > >> > >> > thanks for helping with Windows. >> > >> > >> > >> > Simon >> > >> > >> > >> > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of >> Darren >> > Grant >> > Sent: 15 February 2015 07:36 >> > To: ghc-devs at haskell.org >> > Subject: Resolving Windows 64-bit linker issues >> > >> > >> > >> > Hi all, >> > >> > >> > >> > I notice there are a series of related long-standing issues subject to >> > particular cygwin64 quirks, and I'd like to offer time to help resolve >> these >> > if possible >> > >> > At this point I've had some exposure to the GHC build process (7.8.3), >> and >> > have poked around the GHC linker to gain some low level insight. >> > >> > >> > >> > Would anyone be available to fill me in on the current state of affairs >> with >> > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a >> > preferred direction but no available developer bandwidth to proceed? >> > >> > >> > >> > Thank you. >> > >> > >> > >> > Cheers, >> > >> > Darren >> > >> > >> >> >> > > > > -- > Gintautas Miliauskas > -- Sincerely yours, Roman Kuznetsov -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Tue Feb 17 13:45:09 2015 From: hesselink at gmail.com (Erik Hesselink) Date: Tue, 17 Feb 2015 14:45:09 +0100 Subject: Building vector with GHC HEAD In-Reply-To: <54E3449B.7070000@ro-che.info> References: <201502171419.44155.jan.stolarek@p.lodz.pl> <54E3449B.7070000@ro-che.info> Message-ID: Or [1]. The tl;dr: add "where rnf x = seq x ()" to the instance to get the old behavior. Erik [1] https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#deepseq-1.4.0.0 On Tue, Feb 17, 2015 at 2:39 PM, Roman Cheplyaka wrote: > See http://bit.ly/1CDVOIZ > > On 17/02/15 15:19, Jan Stolarek wrote: >> Devs, >> >> I'm not sure if this is the best place to ask this question but I'm almost certain someone here >> will have the answer. I want to build upstream master branch of vector library using GHC HEAD and >> cabal 1.22. Alas my attempts have failed: >> >> $ git clone git at github.com:haskell/vector.git >> $ cd vector >> $ cabal sandbox init >> $ cabal install -w /dane/projekty/ghc/build/inplace/bin/ghc-stage2 >> Resolving dependencies... >> cabal: Could not resolve dependencies: >> trying: vector-0.11.0.0 (user goal) >> trying: base-4.8.0.0/installed-inp... (dependency of vector-0.11.0.0) >> next goal: deepseq (dependency of vector-0.11.0.0) >> rejecting: deepseq-1.4.0.0/installed-inp..., 1.4.0.0 (conflict: vector => >> deepseq>=1.1 && <1.4) >> rejecting: deepseq-1.3.0.2 (conflict: base==4.8.0.0/installed-inp..., deepseq >> => base>=4.3 && <4.8) >> trying: deepseq-1.3.0.1 >> next goal: array (dependency of deepseq-1.3.0.1) >> rejecting: array-0.5.0.1/installed-inp..., 0.5.0.0 (conflict: deepseq => >> array>=0.1 && <0.5) >> rejecting: array-0.4.0.1 (conflict: base==4.8.0.0/installed-inp..., array => >> base>=4.2 && <4.7) >> rejecting: array-0.4.0.0 (conflict: base==4.8.0.0/installed-inp..., array => >> base>=4.2 && <4.6) >> rejecting: array-0.3.0.3 (conflict: base==4.8.0.0/installed-inp..., array => >> base>=4.2 && <4.5) >> rejecting: array-0.3.0.2, 0.3.0.1 (conflict: base==4.8.0.0/installed-inp..., >> array => base>=4.2 && <4.4) >> rejecting: array-0.3.0.0 (conflict: base==4.8.0.0/installed-inp..., array => >> base>=3 && <4.4) >> rejecting: array-0.2.0.0, 0.1.0.0 (conflict: base==4.8.0.0/installed-inp..., >> array => base<4.3) >> Dependency tree exhaustively searched. >> >> The problem arises from vector requiring deepseq < 1.4 when intree package db contains deepseq >> 1.4. Removing the upper bound on deepseq in vector.cabal allows to resolve dependencies but ends >> with a build error: >> >> Data/Vector/Primitive/Mutable.hs:78:10: >> No instance for (GHC.Generics.Generic (MVector s a)) >> arising from a use of ?Control.DeepSeq.$gdmrnf? >> In the expression: Control.DeepSeq.$gdmrnf >> In an equation for ?rnf?: rnf = Control.DeepSeq.$gdmrnf >> In the instance declaration for ?NFData (MVector s a)? >> >> Fixing this error (importing GHC.Generics & deriving `Generic` instance for `MVector s a`) leads >> to another one: >> >> Data/Vector/Primitive/Mutable.hs:80:10: >> No instance for (Control.DeepSeq.GNFData (Rep (MVector s a))) >> arising from a use of ?Control.DeepSeq.$gdmrnf? >> In the expression: Control.DeepSeq.$gdmrnf >> In an equation for ?rnf?: rnf = Control.DeepSeq.$gdmrnf >> In the instance declaration for ?NFData (MVector s a)? >> >> This time I have no idea how to fix it since GNFData is an internal class of Control.Deepseq >> module. Help? >> >> Aside: at first I thought vector is one of the boot libraries since it is kept in the source tree. >> But then I realized it is not being build during bootstrapping. Why do we keep it in the source >> tree then? >> >> Janek >> >> --- >> Politechnika ??dzka >> Lodz University of Technology >> >> Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. >> Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez pomy?k? >> prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. >> >> This email contains information intended solely for the use of the individual to whom it is addressed. >> If you are not the intended recipient or if you have received this message in error, >> please notify the sender and delete it from your system. >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From takenobu.hs at gmail.com Tue Feb 17 13:48:04 2015 From: takenobu.hs at gmail.com (Takenobu Tani) Date: Tue, 17 Feb 2015 22:48:04 +0900 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: <87wq3gitc0.fsf@gmail.com> References: <87wq3gitc0.fsf@gmail.com> Message-ID: Hi Herbert, Thank you for your directions. I will send the pull-request after checking the file. Thank you, Takenobu 2015-02-17 22:02 GMT+09:00 Herbert Valerio Riedel : > On 2015-02-17 at 13:47:50 +0100, Takenobu Tani wrote: > > I modified System/Process/Internals.hs locally and build on MinGW 32bit. > > Then I was successful to build on 32bit Windows 7. > > > > Shall I write a bug report on trac or any? or ghc7.10.1.rc2 will not > > support 32 bit Windows? > > Please file a pull-request at https://github.com/haskell/process > > I'm somewhat surprised this wasn't noticed before(?) > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jan.stolarek at p.lodz.pl Tue Feb 17 13:54:58 2015 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Tue, 17 Feb 2015 14:54:58 +0100 Subject: Building vector with GHC HEAD In-Reply-To: References: <201502171419.44155.jan.stolarek@p.lodz.pl> <54E3449B.7070000@ro-che.info> Message-ID: <201502171454.58297.jan.stolarek@p.lodz.pl> That works perfectly. Thank you. Dnia wtorek, 17 lutego 2015, Erik Hesselink napisa?: > Or [1]. The tl;dr: add "where rnf x = seq x ()" to the instance to get > the old behavior. > > Erik > > [1] https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#deepseq-1.4.0.0 > > On Tue, Feb 17, 2015 at 2:39 PM, Roman Cheplyaka wrote: > > See http://bit.ly/1CDVOIZ > > > > On 17/02/15 15:19, Jan Stolarek wrote: > >> Devs, > >> > >> I'm not sure if this is the best place to ask this question but I'm > >> almost certain someone here will have the answer. I want to build > >> upstream master branch of vector library using GHC HEAD and cabal 1.22. > >> Alas my attempts have failed: > >> > >> $ git clone git at github.com:haskell/vector.git > >> $ cd vector > >> $ cabal sandbox init > >> $ cabal install -w /dane/projekty/ghc/build/inplace/bin/ghc-stage2 > >> Resolving dependencies... > >> cabal: Could not resolve dependencies: > >> trying: vector-0.11.0.0 (user goal) > >> trying: base-4.8.0.0/installed-inp... (dependency of vector-0.11.0.0) > >> next goal: deepseq (dependency of vector-0.11.0.0) > >> rejecting: deepseq-1.4.0.0/installed-inp..., 1.4.0.0 (conflict: vector > >> => deepseq>=1.1 && <1.4) > >> rejecting: deepseq-1.3.0.2 (conflict: base==4.8.0.0/installed-inp..., > >> deepseq => base>=4.3 && <4.8) > >> trying: deepseq-1.3.0.1 > >> next goal: array (dependency of deepseq-1.3.0.1) > >> rejecting: array-0.5.0.1/installed-inp..., 0.5.0.0 (conflict: deepseq => > >> array>=0.1 && <0.5) > >> rejecting: array-0.4.0.1 (conflict: base==4.8.0.0/installed-inp..., > >> array => base>=4.2 && <4.7) > >> rejecting: array-0.4.0.0 (conflict: base==4.8.0.0/installed-inp..., > >> array => base>=4.2 && <4.6) > >> rejecting: array-0.3.0.3 (conflict: base==4.8.0.0/installed-inp..., > >> array => base>=4.2 && <4.5) > >> rejecting: array-0.3.0.2, 0.3.0.1 (conflict: > >> base==4.8.0.0/installed-inp..., array => base>=4.2 && <4.4) > >> rejecting: array-0.3.0.0 (conflict: base==4.8.0.0/installed-inp..., > >> array => base>=3 && <4.4) > >> rejecting: array-0.2.0.0, 0.1.0.0 (conflict: > >> base==4.8.0.0/installed-inp..., array => base<4.3) > >> Dependency tree exhaustively searched. > >> > >> The problem arises from vector requiring deepseq < 1.4 when intree > >> package db contains deepseq 1.4. Removing the upper bound on deepseq in > >> vector.cabal allows to resolve dependencies but ends with a build error: > >> > >> Data/Vector/Primitive/Mutable.hs:78:10: > >> No instance for (GHC.Generics.Generic (MVector s a)) > >> arising from a use of ?Control.DeepSeq.$gdmrnf? > >> In the expression: Control.DeepSeq.$gdmrnf > >> In an equation for ?rnf?: rnf = Control.DeepSeq.$gdmrnf > >> In the instance declaration for ?NFData (MVector s a)? > >> > >> Fixing this error (importing GHC.Generics & deriving `Generic` instance > >> for `MVector s a`) leads to another one: > >> > >> Data/Vector/Primitive/Mutable.hs:80:10: > >> No instance for (Control.DeepSeq.GNFData (Rep (MVector s a))) > >> arising from a use of ?Control.DeepSeq.$gdmrnf? > >> In the expression: Control.DeepSeq.$gdmrnf > >> In an equation for ?rnf?: rnf = Control.DeepSeq.$gdmrnf > >> In the instance declaration for ?NFData (MVector s a)? > >> > >> This time I have no idea how to fix it since GNFData is an internal > >> class of Control.Deepseq module. Help? > >> > >> Aside: at first I thought vector is one of the boot libraries since it > >> is kept in the source tree. But then I realized it is not being build > >> during bootstrapping. Why do we keep it in the source tree then? > >> > >> Janek > >> > >> --- > >> Politechnika ??dzka > >> Lodz University of Technology > >> > >> Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. > >> Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez > >> pomy?k? prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. > >> > >> This email contains information intended solely for the use of the > >> individual to whom it is addressed. If you are not the intended > >> recipient or if you have received this message in error, please notify > >> the sender and delete it from your system. > >> _______________________________________________ > >> ghc-devs mailing list > >> ghc-devs at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs --- Politechnika ??dzka Lodz University of Technology Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez pomy?k? prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. This email contains information intended solely for the use of the individual to whom it is addressed. If you are not the intended recipient or if you have received this message in error, please notify the sender and delete it from your system. From hvriedel at gmail.com Tue Feb 17 14:22:07 2015 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Tue, 17 Feb 2015 15:22:07 +0100 Subject: Building vector with GHC HEAD In-Reply-To: <201502171419.44155.jan.stolarek@p.lodz.pl> (Jan Stolarek's message of "Tue, 17 Feb 2015 14:19:43 +0100") References: <201502171419.44155.jan.stolarek@p.lodz.pl> Message-ID: <87sie4ipo0.fsf@gmail.com> On 2015-02-17 at 14:19:43 +0100, Jan Stolarek wrote: > Devs, > > I'm not sure if this is the best place to ask this question but I'm almost certain someone here > will have the answer. I want to build upstream master branch of vector library using GHC HEAD and > cabal 1.22. Alas my attempts have failed: > > $ git clone git at github.com:haskell/vector.git > $ cd vector > $ cabal sandbox init > $ cabal install -w /dane/projekty/ghc/build/inplace/bin/ghc-stage2 ...you need (at least) the following still unmerged PR applied for vector's 'master': https://github.com/haskell/vector/pull/58 Cheers, hvr From lonetiger at gmail.com Tue Feb 17 17:08:32 2015 From: lonetiger at gmail.com (=?utf-8?Q?Tamar_Christina?=) Date: Tue, 17 Feb 2015 17:08:32 +0000 Subject: =?utf-8?Q?Re:_Resolving_Windows_64-bit_linker_issues?= In-Reply-To: References: <2350464511293266495@unknownmsgid> , Message-ID: <54e3760e.4b08b50a.728d.0c76@mx.google.com> Hi Roman & Simon, I agree it makes sense to add it there, however I think https://ghc.haskell.org/trac/ghc/wiki/WindowsGhc that link should be used instead of the WindowsTaskForce link directly. @Darren & Martin, would you also like to be added to the page? Regards, Tamar From: Roman Kuznetsov Sent: ?Tuesday?, ?February? ?17?, ?2015 ?14?:?45 To: Gintautas Miliauskas Cc: Tamar Christina, Simon Peyton Jones, Darren Grant, Mikolaj Konarski, ghc-devs at haskell.org, David Macek, kyra, Martin Foster Hi, That would definitely make sense to add more information for Windows in "Platform-specific build notes". I will try taking care of it the coming week. Roman On Tue, Feb 17, 2015 at 12:56 PM, Gintautas Miliauskas wrote: Hi, would someone be willing to be a coordinator for the team? Feel free to just edit the wiki. I am completely swamped by my new job and my move to London at the moment, and the situation is unlikely to change soon. Sorry :( On Tue, Feb 17, 2015 at 10:14 AM, Tamar Christina wrote: Hi Simon, We do have a page on Trac with the members: https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce We could add the extra information there. Regards, Tamar From: Simon Peyton Jones Sent: ?17/?02/?2015 10:18 To: Darren Grant; Mikolaj Konarski Cc: Phyx; Roman Kuznetsov; ghc-devs at haskell.org; David Macek; kyrab; Gintautas Miliauskas; Martin Foster Subject: RE: Resolving Windows 64-bit linker issues One really helpful thing would be to ? make a wiki home page for the Windows Task Force ? list who is on it ? list the main tasks ?in flight? and what their status is ? any other plans Anything to broaden visibility of the WTF, and encourage others to join in. Communication is all in an open-source context! Thanks for working on Windows? it?s a very popular platform, and needs your love! Simon From: Darren Grant [mailto:dedgrant at gmail.com] Sent: 17 February 2015 05:03 To: Mikolaj Konarski Cc: Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; David Macek; kyrab; Gintautas Miliauskas; Martin Foster Subject: Re: Resolving Windows 64-bit linker issues To expand on that (let's see if I can do this without accidentally sending again, oops!): Roman, I will get in touch with you on a separate email thread to see if we can find an optimal way to coordinate, something that satisfies our schedules and needs. Others please feel free to bug me any time by email (dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. In the meantime I'll be auditing some of the related backlogged tickets on trac. If there's something I can do to help further the goal of a Windows Task Force page, please let me know. Pleased to meet everyone! Cheers, Darren On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: Thank you kindly for the great introduction. I hope I can be helpful here. On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" wrote: Resending, since Roman's and Kyril's email addresses were mangled/missing. On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones wrote: > Darren > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk in > cc. So they would be the first group to ask. > > > > (I think it would be very helpful to have a Windows Task Force home page, so > that it?s easier to find the group.) > > > > thanks for helping with Windows. > > > > Simon > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > Grant > Sent: 15 February 2015 07:36 > To: ghc-devs at haskell.org > Subject: Resolving Windows 64-bit linker issues > > > > Hi all, > > > > I notice there are a series of related long-standing issues subject to > particular cygwin64 quirks, and I'd like to offer time to help resolve these > if possible > > At this point I've had some exposure to the GHC build process (7.8.3), and > have poked around the GHC linker to gain some low level insight. > > > > Would anyone be available to fill me in on the current state of affairs with > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > preferred direction but no available developer bandwidth to proceed? > > > > Thank you. > > > > Cheers, > > Darren > > -- Gintautas Miliauskas -- Sincerely yours, Roman Kuznetsov -------------- next part -------------- An HTML attachment was scrubbed... URL: From dan.doel at gmail.com Tue Feb 17 17:13:09 2015 From: dan.doel at gmail.com (Dan Doel) Date: Tue, 17 Feb 2015 12:13:09 -0500 Subject: Building vector with GHC HEAD In-Reply-To: <87sie4ipo0.fsf@gmail.com> References: <201502171419.44155.jan.stolarek@p.lodz.pl> <87sie4ipo0.fsf@gmail.com> Message-ID: Sorry about that. The pull request is now merged. On Tue, Feb 17, 2015 at 9:22 AM, Herbert Valerio Riedel wrote: > On 2015-02-17 at 14:19:43 +0100, Jan Stolarek wrote: > > Devs, > > > > I'm not sure if this is the best place to ask this question but I'm > almost certain someone here > > will have the answer. I want to build upstream master branch of vector > library using GHC HEAD and > > cabal 1.22. Alas my attempts have failed: > > > > $ git clone git at github.com:haskell/vector.git > > $ cd vector > > $ cabal sandbox init > > $ cabal install -w /dane/projekty/ghc/build/inplace/bin/ghc-stage2 > > ...you need (at least) the following still unmerged PR applied for > vector's 'master': > > https://github.com/haskell/vector/pull/58 > > > Cheers, > hvr > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Tue Feb 17 18:47:19 2015 From: ekmett at gmail.com (Edward Kmett) Date: Tue, 17 Feb 2015 13:47:19 -0500 Subject: Seeking an active maintainer for 'directory' Message-ID: The 'directory' package could use an active maintainer. Currently, the package falls to the Core Libraries Committee for maintenance, but we've had a number of issues accrete for the directory package over the last six months or so, which need some attention to detail and a good understanding of cross-platform issues. Is anybody interested in nominating themselves for this role? -Edward -------------- next part -------------- An HTML attachment was scrubbed... URL: From rf at rufflewind.com Tue Feb 17 19:25:19 2015 From: rf at rufflewind.com (Phil Ruffwind) Date: Tue, 17 Feb 2015 14:25:19 -0500 Subject: Seeking an active maintainer for 'directory' In-Reply-To: References: Message-ID: > Is anybody interested in nominating themselves for this role? I would be interested in this. I'm generally quite meticulous :) and I'm familiar with the APIs of both POSIX and Win32, albeit more so with POSIX. -- Phil From ekmett at gmail.com Tue Feb 17 19:53:43 2015 From: ekmett at gmail.com (Edward Kmett) Date: Tue, 17 Feb 2015 14:53:43 -0500 Subject: Seeking an active maintainer for 'directory' In-Reply-To: References: Message-ID: And we have a winner. Thanks, Phil. If you need any help from the core libraries committee, just ask; we'll support your efforts however we can. -Edward On Tue, Feb 17, 2015 at 2:25 PM, Phil Ruffwind wrote: > > Is anybody interested in nominating themselves for this role? > > I would be interested in this. I'm generally quite meticulous :) and > I'm familiar with the APIs of both POSIX and Win32, albeit more so > with POSIX. > > -- > Phil > -------------- next part -------------- An HTML attachment was scrubbed... URL: From elliot.robinson at argiopetech.com Tue Feb 17 22:12:21 2015 From: elliot.robinson at argiopetech.com (Elliot Robinson) Date: Tue, 17 Feb 2015 17:12:21 -0500 Subject: Seeking an active maintainer for 'directory' In-Reply-To: References: Message-ID: <20150217221221.GB10625@suwako.argiopetech.com> My, that was quick... I'd be happy to throw my hat into the ring as a co-maintainer with Phil (if the involved parties aren't opposed). I'm also somewhat more familiar with the POSIX side of things, though it wouldn't hurt me to brush up on my Win32. -- Elliot Robinson GPG Key: 9FEDE59A On 02/17/15, Edward Kmett wrote: > And we have a winner. > > Thanks, Phil. > > If you need any help from the core libraries committee, just ask; we'll > support your efforts however we can. > > -Edward > > On Tue, Feb 17, 2015 at 2:25 PM, Phil Ruffwind wrote: > > > > Is anybody interested in nominating themselves for this role? > > > > I would be interested in this. I'm generally quite meticulous :) and > > I'm familiar with the APIs of both POSIX and Win32, albeit more so > > with POSIX. > > > > -- > > Phil > > From ekmett at gmail.com Wed Feb 18 00:24:21 2015 From: ekmett at gmail.com (Edward Kmett) Date: Tue, 17 Feb 2015 19:24:21 -0500 Subject: Seeking an active maintainer for 'directory' In-Reply-To: <20150217221221.GB10625@suwako.argiopetech.com> References: <20150217221221.GB10625@suwako.argiopetech.com> Message-ID: I have no particularly strong opinion on the matter. I'm happy to leave that up to Phil. -Edward On Tue, Feb 17, 2015 at 5:12 PM, Elliot Robinson < elliot.robinson at argiopetech.com> wrote: > My, that was quick... > > I'd be happy to throw my hat into the ring as a co-maintainer with Phil > (if the involved parties aren't opposed). I'm also somewhat more familiar > with the POSIX side of things, though it wouldn't hurt me to brush up on my > Win32. > > -- > Elliot Robinson > GPG Key: 9FEDE59A > > On 02/17/15, Edward Kmett wrote: > > And we have a winner. > > > > Thanks, Phil. > > > > If you need any help from the core libraries committee, just ask; we'll > > support your efforts however we can. > > > > -Edward > > > > On Tue, Feb 17, 2015 at 2:25 PM, Phil Ruffwind > wrote: > > > > > > Is anybody interested in nominating themselves for this role? > > > > > > I would be interested in this. I'm generally quite meticulous :) and > > > I'm familiar with the APIs of both POSIX and Win32, albeit more so > > > with POSIX. > > > > > > -- > > > Phil > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rf at rufflewind.com Wed Feb 18 00:54:00 2015 From: rf at rufflewind.com (Phil Ruffwind) Date: Tue, 17 Feb 2015 19:54:00 -0500 Subject: Seeking an active maintainer for 'directory' In-Reply-To: References: <20150217221221.GB10625@suwako.argiopetech.com> Message-ID: >> I'd be happy to throw my hat into the ring as a co-maintainer with Phil > > I have no particularly strong opinion on the matter. Me neither :) We can work on the issues in parallel as long it's clear who is doing what. From elliot.robinson at argiopetech.com Wed Feb 18 03:50:48 2015 From: elliot.robinson at argiopetech.com (Elliot Robinson) Date: Tue, 17 Feb 2015 22:50:48 -0500 Subject: Seeking an active maintainer for 'directory' In-Reply-To: References: <20150217221221.GB10625@suwako.argiopetech.com> Message-ID: <20150218035048.GC10625@suwako.argiopetech.com> Seems reasonable to me. -- Elliot Robinson GPG Key: 9FEDE59A On 02/17/15, Phil Ruffwind wrote: > >> I'd be happy to throw my hat into the ring as a co-maintainer with Phil > > > > I have no particularly strong opinion on the matter. > > Me neither :) We can work on the issues in parallel as long it's > clear who is doing what. From austin at well-typed.com Wed Feb 18 04:09:17 2015 From: austin at well-typed.com (Austin Seipp) Date: Tue, 17 Feb 2015 22:09:17 -0600 Subject: GHC Weekly News - 2015/02/17 Message-ID: Hi *, It's time for the GHC weekly news. It's been particularly quiet the past week still, and the `ghc-7.10` branch has been quite quiet. So the notes are relatively short this week. This week, GHC HQ met up to discuss some new stuff: - Most of the discussion this week was about particular bugs for GHC 7.10, including getting some tickets fixed like #10058, #8276, and #9968. - Since the 7.10 release is getting close, we'll be starting up a new status page about GHC 7.12 (and probably get started writing things for the HCAR report in May) and what our plans are soon. Watch this space! As usual, we've had a healthy amount of random assorted chatter on the mailing lists: - Simon Peyton Jones opened the polls for the GHC 7.10 Prelude changes this week, following the discussions and delay of the 7.10 release, as to what the new Prelude should look like. Simon's email has all the details - and voting ends next week! https://mail.haskell.org/pipermail/ghc-devs/2015-February/008290.html - Hengchu Zhang popped up on the list as an excited new contributor, and wanted to know about the process strategy for fixing a bug. Joachim was quick to respond with help - and welcome Hengchu! https://mail.haskell.org/pipermail/ghc-devs/2015-February/008324.html - Francesco Mazzoli has a question about Template Haskell, specifically the semantics of reification since 7.8. In short, the semantics of `reify` changed in 7.8, and Francesco was wondering if the old behavior should be supported. But while it could be, it discussion seems to indicate that perhaps it shouldn't. https://mail.haskell.org/pipermail/ghc-devs/2015-February/008327.html - Darren Grant popped up on the list and asked: "I notice there are a series of related long-standing issues subject to particular cygwin64 quirks, and I'd like to offer time to help resolve these if possible". Darren wanted some pointers, and they were given! GHC on Windows crucially still needs dedicated developers; the email sparked up a bunch of chatter amongst Windows developers on the list as well, so hopefully life is coming back to it. https://mail.haskell.org/pipermail/ghc-devs/2015-February/008333.html - Jan Stolarek hit a confusing error when trying to install `vector` with HEAD and asked for help. The quick reply: you need support for the new `deepseq` package, which hasn't been merged upstream yet. https://mail.haskell.org/pipermail/ghc-devs/2015-February/008349.html - Francesco Mazzoli had a simple feature request: could we have anonymous FFI calls that don't require a name? https://mail.haskell.org/pipermail/ghc-devs/2015-February/008300.html Some noteworthy commits that went into `ghc.git` in the past week include: - Commit e22282e5d2a370395535df4051bdeb8213106d1c - GHC 7.12 will no longer ship with the `Typeable.h` header file. - Commit 5d5abdca31cdb4db5303999778fa25c4a1371084 - The LLVM backend has been overhauled and updated to use LLVM 3.6 exclusively. Closed tickets the past week include: #10047, #10082, #10019, #10007, #9930, #10085, #10080, #9266, #10095, and #3649. -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From dedgrant at gmail.com Wed Feb 18 05:56:12 2015 From: dedgrant at gmail.com (Darren Grant) Date: Tue, 17 Feb 2015 21:56:12 -0800 Subject: Resolving Windows 64-bit linker issues In-Reply-To: <54e3760e.4b08b50a.728d.0c76@mx.google.com> References: <2350464511293266495@unknownmsgid> <54e3760e.4b08b50a.728d.0c76@mx.google.com> Message-ID: Hi All, Tamar, certainly add me to the Windows Task Force page. Thank you! Gintautas, what are the duties of a coordinator for the task force? I can volunteer contingent on qualifications and balancing obligations with my day job. Cheers, Darren On Tue, Feb 17, 2015 at 9:08 AM, Tamar Christina wrote: > Hi Roman & Simon, > > I agree it makes sense to add it there, however I think > https://ghc.haskell.org/trac/ghc/wiki/WindowsGhc that link should be used > instead of the WindowsTaskForce link directly. > > @Darren & Martin, would you also like to be added to the page? > > Regards, > Tamar > > *From:* Roman Kuznetsov > *Sent:* ?Tuesday?, ?February? ?17?, ?2015 ?14?:?45 > *To:* Gintautas Miliauskas > *Cc:* Tamar Christina , Simon Peyton Jones > , Darren Grant , Mikolaj > Konarski , ghc-devs at haskell.org, David Macek > , kyra , Martin Foster > > > Hi, > > That would definitely make sense to add more information for Windows in > "Platform-specific build notes". I will try taking care of it the coming > week. > > Roman > > On Tue, Feb 17, 2015 at 12:56 PM, Gintautas Miliauskas < > gintautas at miliauskas.lt> wrote: > >> Hi, >> >> would someone be willing to be a coordinator for the team? Feel free to >> just edit the wiki. I am completely swamped by my new job and my move to >> London at the moment, and the situation is unlikely to change soon. Sorry :( >> >> On Tue, Feb 17, 2015 at 10:14 AM, Tamar Christina >> wrote: >> >>> Hi Simon, >>> >>> We do have a page on Trac with the members: >>> https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce >>> >>> We could add the extra information there. >>> >>> Regards, >>> Tamar >>> ------------------------------ >>> From: Simon Peyton Jones >>> Sent: ?17/?02/?2015 10:18 >>> To: Darren Grant ; Mikolaj Konarski >>> >>> Cc: Phyx ; Roman Kuznetsov ; >>> ghc-devs at haskell.org; David Macek ; kyrab >>> ; Gintautas Miliauskas ; Martin >>> Foster >>> Subject: RE: Resolving Windows 64-bit linker issues >>> >>> One really helpful thing would be to >>> >>> ? make a wiki home page for the Windows Task Force >>> >>> ? list who is on it >>> >>> ? list the main tasks ?in flight? and what their status is >>> >>> ? any other plans >>> >>> Anything to broaden visibility of the WTF, and encourage others to join >>> in. Communication is all in an open-source context! >>> >>> >>> >>> Thanks for working on Windows? it?s a very popular platform, and needs >>> your love! >>> >>> >>> >>> Simon >>> >>> >>> >>> *From:* Darren Grant [mailto:dedgrant at gmail.com] >>> *Sent:* 17 February 2015 05:03 >>> *To:* Mikolaj Konarski >>> *Cc:* Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; >>> David Macek; kyrab; Gintautas Miliauskas; Martin Foster >>> *Subject:* Re: Resolving Windows 64-bit linker issues >>> >>> >>> >>> To expand on that (let's see if I can do this without accidentally >>> sending again, oops!): >>> >>> Roman, I will get in touch with you on a separate email thread to see if >>> we can find an optimal way to coordinate, something that satisfies our >>> schedules and needs. Others please feel free to bug me any time by email ( >>> dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. >>> >>> In the meantime I'll be auditing some of the related backlogged tickets >>> on trac. If there's something I can do to help further the goal of a >>> Windows Task Force page, please let me know. >>> >>> >>> Pleased to meet everyone! >>> >>> Cheers, >>> >>> Darren >>> >>> >>> >>> >>> >>> On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant >>> wrote: >>> >>> Thank you kindly for the great introduction. I hope I can be helpful >>> here. >>> >>> On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" >>> wrote: >>> >>> Resending, since Roman's and Kyril's email addresses were >>> mangled/missing. >>> >>> On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones >>> wrote: >>> > Darren >>> > >>> > >>> > >>> > Excellent! We have a Windows Task Force, consisting roughly of the >>> folk in >>> > cc. So they would be the first group to ask. >>> > >>> > >>> > >>> > (I think it would be very helpful to have a Windows Task Force home >>> page, so >>> > that it?s easier to find the group.) >>> > >>> > >>> > >>> > thanks for helping with Windows. >>> > >>> > >>> > >>> > Simon >>> > >>> > >>> > >>> > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of >>> Darren >>> > Grant >>> > Sent: 15 February 2015 07:36 >>> > To: ghc-devs at haskell.org >>> > Subject: Resolving Windows 64-bit linker issues >>> > >>> > >>> > >>> > Hi all, >>> > >>> > >>> > >>> > I notice there are a series of related long-standing issues subject to >>> > particular cygwin64 quirks, and I'd like to offer time to help resolve >>> these >>> > if possible >>> > >>> > At this point I've had some exposure to the GHC build process (7.8.3), >>> and >>> > have poked around the GHC linker to gain some low level insight. >>> > >>> > >>> > >>> > Would anyone be available to fill me in on the current state of >>> affairs with >>> > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a >>> > preferred direction but no available developer bandwidth to proceed? >>> > >>> > >>> > >>> > Thank you. >>> > >>> > >>> > >>> > Cheers, >>> > >>> > Darren >>> > >>> > >>> >>> >>> >> >> >> >> -- >> Gintautas Miliauskas >> > > > > -- > Sincerely yours, > Roman Kuznetsov > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.macek.0 at gmail.com Wed Feb 18 09:13:59 2015 From: david.macek.0 at gmail.com (David Macek) Date: Wed, 18 Feb 2015 10:13:59 +0100 Subject: Resolving Windows 64-bit linker issues In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF562CC8BE@DB3PRD3001MB020.064d.mgd.msft.net> References: <2350464511293266495@unknownmsgid> <618BE556AADD624C9C918AA5D5911BEF562CC8BE@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <54E457D7.5080500@gmail.com> On 17. 2. 2015 12:21, Simon Peyton Jones wrote: > Ah yes, so we do! Excellent. Maybe add Darren J > > Also should Martin Foster, David Macek be there? Depends on the expectations arising from my inclusion. I'm not sure if I can do much work on ghc itself as the code seems pretty complex. I'm always glad to run tests and help with stuff like that. Anyway, at this stage, my top priority is a ghc package for MSYS2. I was waiting for the mingw work by Gintas (is that done?), so I could try making ghc package without the sanctioned mingw toolchain, and instead have it depend on other MSYS2 packages. -- David Macek -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 4234 bytes Desc: S/MIME Cryptographic Signature URL: From gintautas at miliauskas.lt Wed Feb 18 14:48:48 2015 From: gintautas at miliauskas.lt (Gintautas Miliauskas) Date: Wed, 18 Feb 2015 14:48:48 +0000 Subject: Resolving Windows 64-bit linker issues In-Reply-To: References: <2350464511293266495@unknownmsgid> <54e3760e.4b08b50a.728d.0c76@mx.google.com> Message-ID: I don't think there is any formal list of duties, and there's not much precedent either. Monitoring mailing lists, glancing at bugs from time to time, pinging involved people once in a while, following up on tasks and ideas and generally keeping things moving. It's all best effort though. Anything is better than nothing. On Wed, Feb 18, 2015 at 5:56 AM, Darren Grant wrote: > Hi All, > > Tamar, certainly add me to the Windows Task Force page. Thank you! > > Gintautas, what are the duties of a coordinator for the task force? I can > volunteer contingent on qualifications and balancing obligations with my > day job. > > > Cheers, > Darren > > > On Tue, Feb 17, 2015 at 9:08 AM, Tamar Christina > wrote: > >> Hi Roman & Simon, >> >> I agree it makes sense to add it there, however I think >> https://ghc.haskell.org/trac/ghc/wiki/WindowsGhc that link should be >> used instead of the WindowsTaskForce link directly. >> >> @Darren & Martin, would you also like to be added to the page? >> >> Regards, >> Tamar >> >> *From:* Roman Kuznetsov >> *Sent:* ?Tuesday?, ?February? ?17?, ?2015 ?14?:?45 >> *To:* Gintautas Miliauskas >> *Cc:* Tamar Christina , Simon Peyton Jones >> , Darren Grant , Mikolaj >> Konarski , ghc-devs at haskell.org, David Macek >> , kyra , Martin Foster >> >> >> Hi, >> >> That would definitely make sense to add more information for Windows in >> "Platform-specific build notes". I will try taking care of it the coming >> week. >> >> Roman >> >> On Tue, Feb 17, 2015 at 12:56 PM, Gintautas Miliauskas < >> gintautas at miliauskas.lt> wrote: >> >>> Hi, >>> >>> would someone be willing to be a coordinator for the team? Feel free to >>> just edit the wiki. I am completely swamped by my new job and my move to >>> London at the moment, and the situation is unlikely to change soon. Sorry :( >>> >>> On Tue, Feb 17, 2015 at 10:14 AM, Tamar Christina >>> wrote: >>> >>>> Hi Simon, >>>> >>>> We do have a page on Trac with the members: >>>> https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce >>>> >>>> We could add the extra information there. >>>> >>>> Regards, >>>> Tamar >>>> ------------------------------ >>>> From: Simon Peyton Jones >>>> Sent: ?17/?02/?2015 10:18 >>>> To: Darren Grant ; Mikolaj Konarski >>>> >>>> Cc: Phyx ; Roman Kuznetsov ; >>>> ghc-devs at haskell.org; David Macek ; kyrab >>>> ; Gintautas Miliauskas ; Martin >>>> Foster >>>> Subject: RE: Resolving Windows 64-bit linker issues >>>> >>>> One really helpful thing would be to >>>> >>>> ? make a wiki home page for the Windows Task Force >>>> >>>> ? list who is on it >>>> >>>> ? list the main tasks ?in flight? and what their status is >>>> >>>> ? any other plans >>>> >>>> Anything to broaden visibility of the WTF, and encourage others to join >>>> in. Communication is all in an open-source context! >>>> >>>> >>>> >>>> Thanks for working on Windows? it?s a very popular platform, and needs >>>> your love! >>>> >>>> >>>> >>>> Simon >>>> >>>> >>>> >>>> *From:* Darren Grant [mailto:dedgrant at gmail.com] >>>> *Sent:* 17 February 2015 05:03 >>>> *To:* Mikolaj Konarski >>>> *Cc:* Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; >>>> David Macek; kyrab; Gintautas Miliauskas; Martin Foster >>>> *Subject:* Re: Resolving Windows 64-bit linker issues >>>> >>>> >>>> >>>> To expand on that (let's see if I can do this without accidentally >>>> sending again, oops!): >>>> >>>> Roman, I will get in touch with you on a separate email thread to see >>>> if we can find an optimal way to coordinate, something that satisfies our >>>> schedules and needs. Others please feel free to bug me any time by email ( >>>> dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. >>>> >>>> In the meantime I'll be auditing some of the related backlogged tickets >>>> on trac. If there's something I can do to help further the goal of a >>>> Windows Task Force page, please let me know. >>>> >>>> >>>> Pleased to meet everyone! >>>> >>>> Cheers, >>>> >>>> Darren >>>> >>>> >>>> >>>> >>>> >>>> On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant >>>> wrote: >>>> >>>> Thank you kindly for the great introduction. I hope I can be helpful >>>> here. >>>> >>>> On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" >>>> wrote: >>>> >>>> Resending, since Roman's and Kyril's email addresses were >>>> mangled/missing. >>>> >>>> On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones >>>> wrote: >>>> > Darren >>>> > >>>> > >>>> > >>>> > Excellent! We have a Windows Task Force, consisting roughly of the >>>> folk in >>>> > cc. So they would be the first group to ask. >>>> > >>>> > >>>> > >>>> > (I think it would be very helpful to have a Windows Task Force home >>>> page, so >>>> > that it?s easier to find the group.) >>>> > >>>> > >>>> > >>>> > thanks for helping with Windows. >>>> > >>>> > >>>> > >>>> > Simon >>>> > >>>> > >>>> > >>>> > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of >>>> Darren >>>> > Grant >>>> > Sent: 15 February 2015 07:36 >>>> > To: ghc-devs at haskell.org >>>> > Subject: Resolving Windows 64-bit linker issues >>>> > >>>> > >>>> > >>>> > Hi all, >>>> > >>>> > >>>> > >>>> > I notice there are a series of related long-standing issues subject to >>>> > particular cygwin64 quirks, and I'd like to offer time to help >>>> resolve these >>>> > if possible >>>> > >>>> > At this point I've had some exposure to the GHC build process >>>> (7.8.3), and >>>> > have poked around the GHC linker to gain some low level insight. >>>> > >>>> > >>>> > >>>> > Would anyone be available to fill me in on the current state of >>>> affairs with >>>> > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps >>>> a >>>> > preferred direction but no available developer bandwidth to proceed? >>>> > >>>> > >>>> > >>>> > Thank you. >>>> > >>>> > >>>> > >>>> > Cheers, >>>> > >>>> > Darren >>>> > >>>> > >>>> >>>> >>>> >>> >>> >>> >>> -- >>> Gintautas Miliauskas >>> >> >> >> >> -- >> Sincerely yours, >> Roman Kuznetsov >> > > -- Gintautas Miliauskas -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Wed Feb 18 22:31:00 2015 From: lonetiger at gmail.com (=?utf-8?Q?Tamar_Christina?=) Date: Wed, 18 Feb 2015 22:31:00 +0000 Subject: =?utf-8?Q?Re:_Resolving_Windows_64-bit_linker_issues?= In-Reply-To: References: <2350464511293266495@unknownmsgid> <54e3760e.4b08b50a.728d.0c76@mx.google.com>, Message-ID: <54e51363.e24cb40a.60a6.ffffe055@mx.google.com> Hi all, I have added your name to the wiki Darren and I have also added a link to the Windows build instructions under the ?Platform specific build instructions?. @David I don?t think there?s any real formal expectations from adding your name to the wiki, you can always remove it if you want ? Regards, Tamar From: Darren Grant Sent: ?Wednesday?, ?February? ?18?, ?2015 ?06?:?56 To: Tamar Christina Cc: Roman Kuznetsov, Gintautas Miliauskas, Simon Peyton Jones, Mikolaj Konarski, ghc-devs at haskell.org, David Macek, kyra, Martin Foster Hi All, Tamar, certainly add me to the Windows Task Force page. Thank you! Gintautas, what are the duties of a coordinator for the task force? I can volunteer contingent on qualifications and balancing obligations with my day job. Cheers, Darren On Tue, Feb 17, 2015 at 9:08 AM, Tamar Christina wrote: Hi Roman & Simon, I agree it makes sense to add it there, however I think https://ghc.haskell.org/trac/ghc/wiki/WindowsGhc that link should be used instead of the WindowsTaskForce link directly. @Darren & Martin, would you also like to be added to the page? Regards, Tamar From: Roman Kuznetsov Sent: ?Tuesday?, ?February? ?17?, ?2015 ?14?:?45 To: Gintautas Miliauskas Cc: Tamar Christina, Simon Peyton Jones, Darren Grant, Mikolaj Konarski, ghc-devs at haskell.org, David Macek, kyra, Martin Foster Hi, That would definitely make sense to add more information for Windows in "Platform-specific build notes". I will try taking care of it the coming week. Roman On Tue, Feb 17, 2015 at 12:56 PM, Gintautas Miliauskas wrote: Hi, would someone be willing to be a coordinator for the team? Feel free to just edit the wiki. I am completely swamped by my new job and my move to London at the moment, and the situation is unlikely to change soon. Sorry :( On Tue, Feb 17, 2015 at 10:14 AM, Tamar Christina wrote: Hi Simon, We do have a page on Trac with the members: https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce We could add the extra information there. Regards, Tamar From: Simon Peyton Jones Sent: ?17/?02/?2015 10:18 To: Darren Grant; Mikolaj Konarski Cc: Phyx; Roman Kuznetsov; ghc-devs at haskell.org; David Macek; kyrab; Gintautas Miliauskas; Martin Foster Subject: RE: Resolving Windows 64-bit linker issues One really helpful thing would be to ? make a wiki home page for the Windows Task Force ? list who is on it ? list the main tasks ?in flight? and what their status is ? any other plans Anything to broaden visibility of the WTF, and encourage others to join in. Communication is all in an open-source context! Thanks for working on Windows? it?s a very popular platform, and needs your love! Simon From: Darren Grant [mailto:dedgrant at gmail.com] Sent: 17 February 2015 05:03 To: Mikolaj Konarski Cc: Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; David Macek; kyrab; Gintautas Miliauskas; Martin Foster Subject: Re: Resolving Windows 64-bit linker issues To expand on that (let's see if I can do this without accidentally sending again, oops!): Roman, I will get in touch with you on a separate email thread to see if we can find an optimal way to coordinate, something that satisfies our schedules and needs. Others please feel free to bug me any time by email (dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. In the meantime I'll be auditing some of the related backlogged tickets on trac. If there's something I can do to help further the goal of a Windows Task Force page, please let me know. Pleased to meet everyone! Cheers, Darren On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant wrote: Thank you kindly for the great introduction. I hope I can be helpful here. On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" wrote: Resending, since Roman's and Kyril's email addresses were mangled/missing. On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones wrote: > Darren > > > > Excellent! We have a Windows Task Force, consisting roughly of the folk in > cc. So they would be the first group to ask. > > > > (I think it would be very helpful to have a Windows Task Force home page, so > that it?s easier to find the group.) > > > > thanks for helping with Windows. > > > > Simon > > > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Darren > Grant > Sent: 15 February 2015 07:36 > To: ghc-devs at haskell.org > Subject: Resolving Windows 64-bit linker issues > > > > Hi all, > > > > I notice there are a series of related long-standing issues subject to > particular cygwin64 quirks, and I'd like to offer time to help resolve these > if possible > > At this point I've had some exposure to the GHC build process (7.8.3), and > have poked around the GHC linker to gain some low level insight. > > > > Would anyone be available to fill me in on the current state of affairs with > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps a > preferred direction but no available developer bandwidth to proceed? > > > > Thank you. > > > > Cheers, > > Darren > > -- Gintautas Miliauskas -- Sincerely yours, Roman Kuznetsov -------------- next part -------------- An HTML attachment was scrubbed... URL: From dedgrant at gmail.com Wed Feb 18 23:22:52 2015 From: dedgrant at gmail.com (Darren Grant) Date: Wed, 18 Feb 2015 15:22:52 -0800 Subject: Resolving Windows 64-bit linker issues In-Reply-To: <54e51363.e24cb40a.60a6.ffffe055@mx.google.com> References: <2350464511293266495@unknownmsgid> <54e3760e.4b08b50a.728d.0c76@mx.google.com> <54e51363.e24cb40a.60a6.ffffe055@mx.google.com> Message-ID: Excellent thank you Tamar! Cheers, Darren On Feb 18, 2015 2:34 PM, "Tamar Christina" wrote: > Hi all, > > I have added your name to the wiki Darren and I have also added a link to > the Windows build instructions under the ?Platform specific build > instructions?. > > @David I don?t think there?s any real formal expectations from adding your > name to the wiki, you can always remove it if you want ? > > Regards, > Tamar > > *From:* Darren Grant > *Sent:* ?Wednesday?, ?February? ?18?, ?2015 ?06?:?56 > *To:* Tamar Christina > *Cc:* Roman Kuznetsov , Gintautas Miliauskas > , Simon Peyton Jones , Mikolaj > Konarski , ghc-devs at haskell.org, David Macek > , kyra , Martin Foster > > > Hi All, > > Tamar, certainly add me to the Windows Task Force page. Thank you! > > Gintautas, what are the duties of a coordinator for the task force? I can > volunteer contingent on qualifications and balancing obligations with my > day job. > > > Cheers, > Darren > > > On Tue, Feb 17, 2015 at 9:08 AM, Tamar Christina > wrote: > >> Hi Roman & Simon, >> >> I agree it makes sense to add it there, however I think >> https://ghc.haskell.org/trac/ghc/wiki/WindowsGhc that link should be >> used instead of the WindowsTaskForce link directly. >> >> @Darren & Martin, would you also like to be added to the page? >> >> Regards, >> Tamar >> >> *From:* Roman Kuznetsov >> *Sent:* ?Tuesday?, ?February? ?17?, ?2015 ?14?:?45 >> *To:* Gintautas Miliauskas >> *Cc:* Tamar Christina , Simon Peyton Jones >> , Darren Grant , Mikolaj >> Konarski , ghc-devs at haskell.org, David Macek >> , kyra , Martin Foster >> >> >> Hi, >> >> That would definitely make sense to add more information for Windows in >> "Platform-specific build notes". I will try taking care of it the coming >> week. >> >> Roman >> >> On Tue, Feb 17, 2015 at 12:56 PM, Gintautas Miliauskas < >> gintautas at miliauskas.lt> wrote: >> >>> Hi, >>> >>> would someone be willing to be a coordinator for the team? Feel free to >>> just edit the wiki. I am completely swamped by my new job and my move to >>> London at the moment, and the situation is unlikely to change soon. Sorry :( >>> >>> On Tue, Feb 17, 2015 at 10:14 AM, Tamar Christina >>> wrote: >>> >>>> Hi Simon, >>>> >>>> We do have a page on Trac with the members: >>>> https://ghc.haskell.org/trac/ghc/wiki/WindowsTaskForce >>>> >>>> We could add the extra information there. >>>> >>>> Regards, >>>> Tamar >>>> ------------------------------ >>>> From: Simon Peyton Jones >>>> Sent: ?17/?02/?2015 10:18 >>>> To: Darren Grant ; Mikolaj Konarski >>>> >>>> Cc: Phyx ; Roman Kuznetsov ; >>>> ghc-devs at haskell.org; David Macek ; kyrab >>>> ; Gintautas Miliauskas ; Martin >>>> Foster >>>> Subject: RE: Resolving Windows 64-bit linker issues >>>> >>>> One really helpful thing would be to >>>> >>>> ? make a wiki home page for the Windows Task Force >>>> >>>> ? list who is on it >>>> >>>> ? list the main tasks ?in flight? and what their status is >>>> >>>> ? any other plans >>>> >>>> Anything to broaden visibility of the WTF, and encourage others to join >>>> in. Communication is all in an open-source context! >>>> >>>> >>>> >>>> Thanks for working on Windows? it?s a very popular platform, and needs >>>> your love! >>>> >>>> >>>> >>>> Simon >>>> >>>> >>>> >>>> *From:* Darren Grant [mailto:dedgrant at gmail.com] >>>> *Sent:* 17 February 2015 05:03 >>>> *To:* Mikolaj Konarski >>>> *Cc:* Phyx; Roman Kuznetsov; ghc-devs at haskell.org; Simon Peyton Jones; >>>> David Macek; kyrab; Gintautas Miliauskas; Martin Foster >>>> *Subject:* Re: Resolving Windows 64-bit linker issues >>>> >>>> >>>> >>>> To expand on that (let's see if I can do this without accidentally >>>> sending again, oops!): >>>> >>>> Roman, I will get in touch with you on a separate email thread to see >>>> if we can find an optimal way to coordinate, something that satisfies our >>>> schedules and needs. Others please feel free to bug me any time by email ( >>>> dedgrant at gmail.com) or on freenode #ghc as dedgrant, PST hours. >>>> >>>> In the meantime I'll be auditing some of the related backlogged tickets >>>> on trac. If there's something I can do to help further the goal of a >>>> Windows Task Force page, please let me know. >>>> >>>> >>>> Pleased to meet everyone! >>>> >>>> Cheers, >>>> >>>> Darren >>>> >>>> >>>> >>>> >>>> >>>> On Mon, Feb 16, 2015 at 8:48 PM, Darren Grant >>>> wrote: >>>> >>>> Thank you kindly for the great introduction. I hope I can be helpful >>>> here. >>>> >>>> On Feb 16, 2015 7:47 AM, "Mikolaj Konarski" >>>> wrote: >>>> >>>> Resending, since Roman's and Kyril's email addresses were >>>> mangled/missing. >>>> >>>> On Mon, Feb 16, 2015 at 3:43 PM, Simon Peyton Jones >>>> wrote: >>>> > Darren >>>> > >>>> > >>>> > >>>> > Excellent! We have a Windows Task Force, consisting roughly of the >>>> folk in >>>> > cc. So they would be the first group to ask. >>>> > >>>> > >>>> > >>>> > (I think it would be very helpful to have a Windows Task Force home >>>> page, so >>>> > that it?s easier to find the group.) >>>> > >>>> > >>>> > >>>> > thanks for helping with Windows. >>>> > >>>> > >>>> > >>>> > Simon >>>> > >>>> > >>>> > >>>> > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of >>>> Darren >>>> > Grant >>>> > Sent: 15 February 2015 07:36 >>>> > To: ghc-devs at haskell.org >>>> > Subject: Resolving Windows 64-bit linker issues >>>> > >>>> > >>>> > >>>> > Hi all, >>>> > >>>> > >>>> > >>>> > I notice there are a series of related long-standing issues subject to >>>> > particular cygwin64 quirks, and I'd like to offer time to help >>>> resolve these >>>> > if possible >>>> > >>>> > At this point I've had some exposure to the GHC build process >>>> (7.8.3), and >>>> > have poked around the GHC linker to gain some low level insight. >>>> > >>>> > >>>> > >>>> > Would anyone be available to fill me in on the current state of >>>> affairs with >>>> > mingw64 GHCi linking? For instance, is there ongoing work, or perhaps >>>> a >>>> > preferred direction but no available developer bandwidth to proceed? >>>> > >>>> > >>>> > >>>> > Thank you. >>>> > >>>> > >>>> > >>>> > Cheers, >>>> > >>>> > Darren >>>> > >>>> > >>>> >>>> >>>> >>> >>> >>> >>> -- >>> Gintautas Miliauskas >>> >> >> >> >> -- >> Sincerely yours, >> Roman Kuznetsov >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From kazu at iij.ad.jp Thu Feb 19 05:19:18 2015 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Thu, 19 Feb 2015 14:19:18 +0900 (JST) Subject: Behavior change of Data.Char Message-ID: <20150219.141918.573051813087533301.kazu@iij.ad.jp> Hi, It seems to me that some characters of GHC 7.10.1RC2 behave differently from those of GHC 7.8.4: 7.8.4 7.10.1RC2 isLower (char 170) True False isSymbol (chr 182) True False isPunctuation (chr 182) Fase True Is this intentional? I noticed this because I received a bug report: https://github.com/kazu-yamamoto/word8/issues/3 As you can see, 167 also behaves differently. --Kazu From david.feuer at gmail.com Thu Feb 19 06:04:00 2015 From: david.feuer at gmail.com (David Feuer) Date: Thu, 19 Feb 2015 01:04:00 -0500 Subject: Behavior change of Data.Char In-Reply-To: <20150219.141918.573051813087533301.kazu@iij.ad.jp> References: <20150219.141918.573051813087533301.kazu@iij.ad.jp> Message-ID: 7.10 uses a newer version of Unicode, which could explain differences. On Thu, Feb 19, 2015 at 12:19 AM, Kazu Yamamoto wrote: > Hi, > > It seems to me that some characters of GHC 7.10.1RC2 behave > differently from those of GHC 7.8.4: > > 7.8.4 7.10.1RC2 > isLower (char 170) True False > isSymbol (chr 182) True False > isPunctuation (chr 182) Fase True > > Is this intentional? > > I noticed this because I received a bug report: > > https://github.com/kazu-yamamoto/word8/issues/3 > > As you can see, 167 also behaves differently. > > --Kazu > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From kazu at iij.ad.jp Thu Feb 19 10:14:35 2015 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Thu, 19 Feb 2015 19:14:35 +0900 (JST) Subject: Behavior change of Data.Char In-Reply-To: References: <20150219.141918.573051813087533301.kazu@iij.ad.jp> Message-ID: <20150219.191435.356263373229106057.kazu@iij.ad.jp> David, Thank you for the information. I would like to know whether or not this behavior changes are intentional. If they are bugs, we need to fix them before releasing GHC 7.10.1. --Kazu > 7.10 uses a newer version of Unicode, which could explain differences. > > On Thu, Feb 19, 2015 at 12:19 AM, Kazu Yamamoto wrote: >> Hi, >> >> It seems to me that some characters of GHC 7.10.1RC2 behave >> differently from those of GHC 7.8.4: >> >> 7.8.4 7.10.1RC2 >> isLower (char 170) True False >> isSymbol (chr 182) True False >> isPunctuation (chr 182) Fase True >> >> Is this intentional? >> >> I noticed this because I received a bug report: >> >> https://github.com/kazu-yamamoto/word8/issues/3 >> >> As you can see, 167 also behaves differently. >> >> --Kazu >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From roma at ro-che.info Thu Feb 19 10:33:53 2015 From: roma at ro-che.info (Roman Cheplyaka) Date: Thu, 19 Feb 2015 12:33:53 +0200 Subject: Behavior change of Data.Char In-Reply-To: <20150219.191435.356263373229106057.kazu@iij.ad.jp> References: <20150219.141918.573051813087533301.kazu@iij.ad.jp> <20150219.191435.356263373229106057.kazu@iij.ad.jp> Message-ID: <54E5BC11.5010805@ro-che.info> These are not bugs ? these are changes in the Unicode standard. See http://www.unicode.org/Public/6.0.0/ucd/UnicodeData.txt (old) http://www.unicode.org/Public/7.0.0/ucd/UnicodeData.txt (new) On 19/02/15 12:14, Kazu Yamamoto (????) wrote: > David, > > Thank you for the information. > > I would like to know whether or not this behavior changes are > intentional. If they are bugs, we need to fix them before releasing > GHC 7.10.1. > > --Kazu > >> 7.10 uses a newer version of Unicode, which could explain differences. >> >> On Thu, Feb 19, 2015 at 12:19 AM, Kazu Yamamoto wrote: >>> Hi, >>> >>> It seems to me that some characters of GHC 7.10.1RC2 behave >>> differently from those of GHC 7.8.4: >>> >>> 7.8.4 7.10.1RC2 >>> isLower (char 170) True False >>> isSymbol (chr 182) True False >>> isPunctuation (chr 182) Fase True >>> >>> Is this intentional? >>> >>> I noticed this because I received a bug report: >>> >>> https://github.com/kazu-yamamoto/word8/issues/3 >>> >>> As you can see, 167 also behaves differently. >>> >>> --Kazu >>> _______________________________________________ >>> Libraries mailing list >>> Libraries at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > From hvriedel at gmail.com Thu Feb 19 10:42:28 2015 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Thu, 19 Feb 2015 11:42:28 +0100 Subject: Behavior change of Data.Char In-Reply-To: <20150219.141918.573051813087533301.kazu@iij.ad.jp> ("Kazu Yamamoto \=\?utf-8\?B\?KOWxseacrOWSjOW9pikiJ3M\=\?\= message of "Thu, 19 Feb 2015 14:19:18 +0900 (JST)") References: <20150219.141918.573051813087533301.kazu@iij.ad.jp> Message-ID: <87sie2gp2j.fsf@gmail.com> On 2015-02-19 at 06:19:18 +0100, Kazu Yamamoto (????) wrote: > It seems to me that some characters of GHC 7.10.1RC2 behave > differently from those of GHC 7.8.4: > > 7.8.4 7.10.1RC2 > isLower (char 170) True False Fwiw, the motivation for that particular change may be (I'm just guessing here) to have the following condition hold: \c -> isLower c `implies` (not . isLower . toUpper) c i.e. if something is 'lower-case', then applying 'toUpper' should result in a character that is not 'lower-case' anymore. This didn't hold with 7.8.4's Unicode 6, but now holds with 7.10.1's Unicode 7 definitions. Cheers, hvr From simonpj at microsoft.com Thu Feb 19 12:34:36 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 19 Feb 2015 12:34:36 +0000 Subject: Behavior change of Data.Char In-Reply-To: <87sie2gp2j.fsf@gmail.com> References: <20150219.141918.573051813087533301.kazu@iij.ad.jp> <87sie2gp2j.fsf@gmail.com> Message-ID: <618BE556AADD624C9C918AA5D5911BEF7BEA8C48@DB3PRD3001MB020.064d.mgd.msft.net> It'd be good to document this condition/invariant in the Haddocks, wouldn't it?! Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of | Herbert Valerio Riedel | Sent: 19 February 2015 10:42 | To: Kazu Yamamoto | Cc: libraries at haskell.org; ghc-devs at haskell.org | Subject: Re: Behavior change of Data.Char | | On 2015-02-19 at 06:19:18 +0100, Kazu Yamamoto (????) wrote: | > It seems to me that some characters of GHC 7.10.1RC2 behave | > differently from those of GHC 7.8.4: | > | > 7.8.4 7.10.1RC2 | > isLower (char 170) True False | | Fwiw, the motivation for that particular change may be (I'm just | guessing here) to have the following condition hold: | | \c -> isLower c `implies` (not . isLower . toUpper) c | | i.e. if something is 'lower-case', then applying 'toUpper' should | result in a character that is not 'lower-case' anymore. This didn't | hold with 7.8.4's Unicode 6, but now holds with 7.10.1's Unicode 7 | definitions. | | Cheers, | hvr | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From tomberek at gmail.com Fri Feb 20 07:58:14 2015 From: tomberek at gmail.com (Thomas Bereknyei) Date: Fri, 20 Feb 2015 02:58:14 -0500 Subject: Arrow Development Message-ID: I am looking at the proc notation de-sugar and I see results like this when using a Free Arrow (mostly copied from [1]): line2 = proc n -> do Effect getURLSum *** Effect getURLSum -< n Seq [Pure ] (Seq [Pure ] (Seq [Pure ] (Seq [Pure ](Par {Effect } ) ) ) ) while this is so much simpler: line2 = Effect getURLSum *** Effect getURLSum Par {Effect } Those `Seq [Pure ]` sequences come from application of (.) and I have noticed many similar inefficiencies in the Arrow preprocessor. Eventually the goal would be to optimize when possible, for example I started looking into this in order to use `concurrently` for (***) when in IO. There was a rewrite mentioned here [2]. The deSugar/DsArrows.hs [3] looks convoluted. Any progress or work needed? Or are Arrows not used much and not worth the effort? [1] http://stackoverflow.com/questions/12001350/useful-operations-on-free-arrows [2]https://mail.haskell.org/pipermail/haskell-cafe/2013-August/109795.html [3]https://github.com/ghc/ghc/blob/master/compiler/deSugar/DsArrows.hs -Tom -------------- next part -------------- An HTML attachment was scrubbed... URL: From jan.stolarek at p.lodz.pl Fri Feb 20 11:06:06 2015 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Fri, 20 Feb 2015 12:06:06 +0100 Subject: Arrow Development In-Reply-To: References: Message-ID: <201502201206.06858.jan.stolarek@p.lodz.pl> > There was a rewrite mentioned here [2]. The deSugar/DsArrows.hs [3] looks > convoluted. Any progress or work needed? Take a look at #7828 ticket. There was an intention to rewrite arrow desugarer and I worked on it for some time but eventually abandoned it. Sophie Taylor was planning to take up that work but I don't think she did (or at least she's been quiet for the past few months). > Or are Arrows not used much and not worth the effort? There are several open tickets about arrows (#5267, #5333, #5777, #344 and of course #7828) but at the moment it seems that no one really complains about these. If you use arrows and have a good idea how they work then perhaps you could fix these bugs? Janek --- Politechnika ??dzka Lodz University of Technology Tre?? tej wiadomo?ci zawiera informacje przeznaczone tylko dla adresata. Je?eli nie jeste?cie Pa?stwo jej adresatem, b?d? otrzymali?cie j? przez pomy?k? prosimy o powiadomienie o tym nadawcy oraz trwa?e jej usuni?cie. This email contains information intended solely for the use of the individual to whom it is addressed. If you are not the intended recipient or if you have received this message in error, please notify the sender and delete it from your system. From simonpj at microsoft.com Fri Feb 20 12:03:20 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 20 Feb 2015 12:03:20 +0000 Subject: 76-fold regression GHC 7.10->7.11 in T9961 byte-allocation In-Reply-To: <87mw505y61.fsf@gmail.com> References: <87mw505y61.fsf@gmail.com> Message-ID: <618BE556AADD624C9C918AA5D5911BEF7BEAB56E@DB3PRD3001MB020.064d.mgd.msft.net> Aha. I believe that the ghc-7.10 branch simply doesn't have the source file testsuite/tests/perf/compiler/T9961.hs but all.T still runs the test. So we get "does not exist: T9961.hs", and of course very little allocation. Austin or Herbert, could you add T9961.hs to the 7.10 branch? Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of | Herbert Valerio Riedel | Sent: 30 January 2015 11:03 | To: ghc-devs | Subject: 76-fold regression GHC 7.10->7.11 in T9961 byte-allocation | | Hello *, | | I noticed something odd while validating the GHC 7.10 branch: | | bytes allocated value is too low: | (If this is because you have improved GHC, please | update the test so that GHC doesn't regress again) | Expected T9961(normal) bytes allocated: 772510192 +/-5% | Lower bound T9961(normal) bytes allocated: 733884682 | Upper bound T9961(normal) bytes allocated: 811135702 | Actual T9961(normal) bytes allocated: 9766160 | Deviation T9961(normal) bytes allocated: -98.7 % | *** unexpected stat test failure for T9961(normal) | | | ...then I also ran ./validate against today's GHC HEAD, and re-ran the | T9961 test: | | Expected T9961(normal) bytes allocated: 772510192 +/-5% | Lower bound T9961(normal) bytes allocated: 733884682 | Upper bound T9961(normal) bytes allocated: 811135702 | Actual T9961(normal) bytes allocated: 748225848 | Deviation T9961(normal) bytes allocated: -3.1 % | | | I'm not sure if it's just the test-case being broken, or there's | something real regression between 7.10 and HEAD... | | However, I don't have time to investigate this. | | Cheers, | hvr | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs From david.feuer at gmail.com Fri Feb 20 13:20:20 2015 From: david.feuer at gmail.com (David Feuer) Date: Fri, 20 Feb 2015 08:20:20 -0500 Subject: Behavior change of Data.Char Message-ID: I don't think so. There's no guarantee that future versions will maintain it, and I don't know that we want to take responsibility for continually checking on that. David On Feb 20, 2015 Simon Peyton Jones wrote: > It'd be good to document this condition/invariant in the Haddocks, wouldn't it?! > > Simon > > | -----Original Message----- > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of > | Herbert Valerio Riedel > | Sent: 19 February 2015 10:42 > | To: Kazu Yamamoto > | Cc: libraries at haskell.org; ghc-devs at haskell.org > | Subject: Re: Behavior change of Data.Char > | > | On 2015-02-19 at 06:19:18 +0100, Kazu Yamamoto (????) wrote: > | > It seems to me that some characters of GHC 7.10.1RC2 behave > | > differently from those of GHC 7.8.4: > | > > | > 7.8.4 7.10.1RC2 > | > isLower (char 170) True False > | > | Fwiw, the motivation for that particular change may be (I'm just > | guessing here) to have the following condition hold: > | > | \c -> isLower c `implies` (not . isLower . toUpper) c > | > | i.e. if something is 'lower-case', then applying 'toUpper' should > | result in a character that is not 'lower-case' anymore. This didn't > | hold with 7.8.4's Unicode 6, but now holds with 7.10.1's Unicode 7 > | definitions. > | > | Cheers, > | hvr > | _______________________________________________ > | ghc-devs mailing list > | ghc-devs at haskell.org > | http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Fri Feb 20 13:36:08 2015 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 20 Feb 2015 14:36:08 +0100 Subject: Behavior change of Data.Char In-Reply-To: References: Message-ID: <1424439368.1986.20.camel@joachim-breitner.de> Hi the section header ?Character classification? could indicate that these predicates are based on the Unicode standard, and possibly for each predicate indicate the definition in terms of Unicode character classes. Greetings, Joachim Am Freitag, den 20.02.2015, 08:20 -0500 schrieb David Feuer: > I don't think so. There's no guarantee that future versions will > maintain it, and I don't know that we want to take responsibility for > continually checking on that. > > David > > On Feb 20, 2015 Simon Peyton Jones wrote: > > It'd be good to document this condition/invariant in the Haddocks, > wouldn't it?! > > > > Simon > > > > | -----Original Message----- > > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of > > | Herbert Valerio Riedel > > | Sent: 19 February 2015 10:42 > > | To: Kazu Yamamoto > > | Cc: libraries at haskell.org; ghc-devs at haskell.org > > | Subject: Re: Behavior change of Data.Char > > | > > | On 2015-02-19 at 06:19:18 +0100, Kazu Yamamoto (????) wrote: > > | > It seems to me that some characters of GHC 7.10.1RC2 behave > > | > differently from those of GHC 7.8.4: > > | > > > | > 7.8.4 7.10.1RC2 > > | > isLower (char 170) True False > > | > > | Fwiw, the motivation for that particular change may be (I'm just > > | guessing here) to have the following condition hold: > > | > > | \c -> isLower c `implies` (not . isLower . toUpper) c > > | > > | i.e. if something is 'lower-case', then applying 'toUpper' should > > | result in a character that is not 'lower-case' anymore. This > didn't > > | hold with 7.8.4's Unicode 6, but now holds with 7.10.1's Unicode > 7 > > | definitions. > > | > > | Cheers, > > | hvr > > | _______________________________________________ > > | ghc-devs mailing list > > | ghc-devs at haskell.org > > | http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0xF0FBF51F Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From R.Paterson at city.ac.uk Sat Feb 21 10:39:03 2015 From: R.Paterson at city.ac.uk (Ross Paterson) Date: Sat, 21 Feb 2015 10:39:03 +0000 Subject: Arrow Development In-Reply-To: References: Message-ID: <20150221103903.GA2507@city.ac.uk> On Fri, Feb 20, 2015 at 02:58:14AM -0500, Thomas Bereknyei wrote: > I am looking at the proc notation de-sugar and I see results like this when > using a Free Arrow (mostly copied from [1]): > line2 = proc n -> do > Effect getURLSum *** Effect getURLSum -< n > > Seq [Pure ] (Seq [Pure ] (Seq [Pure ] (Seq [Pure ](Par {Effect } ) ) ) ) > > while this is so much simpler: > line2 = Effect getURLSum *** Effect getURLSum > > Par {Effect } > > Those `Seq [Pure ]` sequences come from application of (.) and I have noticed > many similar inefficiencies in the Arrow preprocessor. Eventually the goal > would be to optimize when possible, for example I started looking into this in > order to use `concurrently` for (***) when in IO. > > There was a rewrite mentioned here [2]. The deSugar/DsArrows.hs [3] looks > convoluted. Any progress or work needed? Or are Arrows not used much and not > worth the effort? I don't think it's feasible to try to do optimization in the desugarer, which certainly is convoluted. You might have more luck using RULES to simplify the output. (The desugarer could be simplified -- a lot of what it does probably belongs in the renamer -- but I'm not sure that would help with optimization.) From ggreif at gmail.com Sat Feb 21 11:42:01 2015 From: ggreif at gmail.com (Gabor Greif) Date: Sat, 21 Feb 2015 12:42:01 +0100 Subject: Desugaring introduces Message-ID: Hi devs, before I file a bug, I'd like to double check on a strange desugaring behaviour with RankNTypes and RebindableSyntax. Here is the snippet {{{ {-# LANGUAGE RankNTypes, RebindableSyntax #-} {-# LANGUAGE ImpredicativeTypes #-} import qualified Prelude as P (>>=) :: a -> ((forall b . b) -> c) -> c a >>= f = f P.undefined return a = a fail s = P.undefined t1 = 'd' >>= (\_ -> 'k') t2 = do _ <- 'd' 'k' main = P.putStrLn [t1, t2] }}} Without ImpredicativeTypes I get this error: {{{ rebindtest.hs:13:9: Cannot instantiate unification variable ?t0? with a type involving foralls: forall b. b Perhaps you want ImpredicativeTypes In a stmt of a 'do' block: _ <- 'd' In the expression: do { _ <- 'd'; 'k' } In an equation for ?t2?: t2 = do { _ <- 'd'; 'k' } }}} t1 is supposed to be the desugaring of t2. Strangely t2 only compiles with ImpredicativeTypes. Why? Isn't desugaring a purely syntactic transformation (esp. with RebindableSyntax)? Any hints welcome! Cheers, Gabor From adam at well-typed.com Sat Feb 21 12:05:00 2015 From: adam at well-typed.com (Adam Gundry) Date: Sat, 21 Feb 2015 12:05:00 +0000 Subject: Desugaring introduces In-Reply-To: References: Message-ID: <54E8746C.5010602@well-typed.com> Hi Gabor, Interesting! While in principle it is true that t1 is the desugaring of t2, GHC does typechecking before desugaring (even with RebindableSyntax) in the interests of generating error messages that reflect what the user actually wrote. The typechecker probably should treat t1 and t2 identically, but in practice this may be difficult to ensure. In this case, I suspect the typechecking rules for do-notation assume that (>>=) has a more usual type. The user's guide section on RebindableSyntax says > In all cases (apart from arrow notation), the static semantics should > be that of the desugared form, even if that is a little unexpected. so on that basis you're probably justified in reporting this as a bug. Hope this helps, Adam On 21/02/15 11:42, Gabor Greif wrote: > Hi devs, > > before I file a bug, I'd like to double check on a strange desugaring > behaviour with RankNTypes and RebindableSyntax. > > Here is the snippet > {{{ > {-# LANGUAGE RankNTypes, RebindableSyntax #-} > {-# LANGUAGE ImpredicativeTypes #-} > > import qualified Prelude as P > > (>>=) :: a -> ((forall b . b) -> c) -> c > a >>= f = f P.undefined > return a = a > fail s = P.undefined > > t1 = 'd' >>= (\_ -> 'k') > > t2 = do _ <- 'd' > 'k' > > main = P.putStrLn [t1, t2] > }}} > > Without ImpredicativeTypes I get this error: > {{{ > rebindtest.hs:13:9: > Cannot instantiate unification variable ?t0? > with a type involving foralls: forall b. b > Perhaps you want ImpredicativeTypes > In a stmt of a 'do' block: _ <- 'd' > In the expression: > do { _ <- 'd'; > 'k' } > In an equation for ?t2?: > t2 > = do { _ <- 'd'; > 'k' } > }}} > > t1 is supposed to be the desugaring of t2. Strangely t2 only compiles > with ImpredicativeTypes. Why? Isn't desugaring a purely syntactic > transformation (esp. with RebindableSyntax)? > > Any hints welcome! > > Cheers, > > Gabor -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From mietek at bak.io Sat Feb 21 20:19:38 2015 From: mietek at bak.io (=?iso-8859-1?Q?Mi=EBtek_Bak?=) Date: Sat, 21 Feb 2015 20:19:38 +0000 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: <6650493F-F6BD-4352-B4F1-5EA0CAE9D868@bak.io> References: <6650493F-F6BD-4352-B4F1-5EA0CAE9D868@bak.io> Message-ID: <61A8F0FD-DA37-4861-BCDD-04891B295C87@bak.io> My previous email was about the x86_64 bindist GHC 7.10.1-rc2. I?ve now added i386 support to Halcyon, and it appears only the x86_64 version works fine on CentOS 6 (6.5), while the i386 version fails to configure: checking for path to top of build tree... utils/ghc-pwd/dist-install/build/tmp/ghc-pwd: symbol lookup error: libraries/integer-gmp2/dist-install/build/libHSinteg_21cuTlnn00eFNd4GMrxOMi-ghc7.10.0.20150123.so: undefined symbol: __gmpn_andn_n configure: error: cannot determine current directory -- Mi?tek On 2015-01-27, at 06:26, Mi?tek Bak wrote: > It appears GHC 7.10.1-rc2 doesn?t support glibc 2.11 ? specifically, 2.11.1 (Ubuntu 10.04 LTS) and 2.11.3 (Debian 6). glibc 2.12 (CentOS 6) seems to work fine. Symptoms include: > > Installing library in > /app/ghc/lib/ghc-7.10.0.20150123/ghc_0kOYffGYd794400D7yvIjm > "/app/ghc/lib/ghc-7.10.0.20150123/bin/ghc-pkg" --force --global-package-db "/app/ghc/lib/ghc-7.10.0.20150123/package.conf.d" update rts/dist/package.conf.install > Reading package info from "rts/dist/package.conf.install" ... done. > "utils/ghc-cabal/dist-install/build/tmp/ghc-cabal-bindist" register libraries/ghc-prim dist-install "/app/ghc/lib/ghc-7.10.0.20150123/bin/ghc" "/app/ghc/lib/ghc-7.10.0.20150123/bin/ghc-pkg" "/app/ghc/lib/ghc-7.10.0.20150123" '' '/app/ghc' '/app/ghc/lib/ghc-7.10.0.20150123' '/app/ghc/share/doc/ghc/html/libraries' NO > Warning: cannot determine version of /app/ghc/lib/ghc-7.10.0.20150123/bin/ghc > : > "" > ghc-cabal: '/app/ghc/lib/ghc-7.10.0.20150123/bin/ghc' exited with an error: > /app/ghc/lib/ghc-7.10.0.20150123/bin/ghc: symbol lookup error: > /app/ghc/lib/ghc-7.10.0.20150123/bin/../rts/libHSrts_thr-ghc7.10.0.20150123.so: > undefined symbol: pthread_setname_np > > The bindist name does mention 'deb7', so perhaps this is all working as intended. However, similarly named bindists for GHC 7.8.* work fine with glibc 2.11. > > > In other news, I?m happy to say Halcyon now supports GHC 7.10.1-rc2 on CentOS 6 and 7, Debian 7, Fedora 19, 20, and 21, and Ubuntu 12 and 14. > https://halcyon.sh/ > > $ halcyon install --ghc-version=7.10.1-rc2 --cabal-version=1.22.0.0 > > > Best, > > -- > Mi?tek > > > > > On 2015-01-27, at 00:13, Austin Seipp wrote: > >> We are pleased to announce the second release candidate for GHC 7.10.1: >> >> https://downloads.haskell.org/~ghc/7.10.1-rc2/ >> >> This includes the source tarball and bindists for 64bit/32bit Linux >> and Windows. Binary builds for other platforms will be available >> shortly. (CentOS 6.5 binaries are not available at this time like they >> were for 7.8.x). These binaries and tarballs have an accompanying >> SHA256SUMS file signed by my GPG key id (0x3B58D86F). >> >> We plan to make the 7.10.1 release sometime in February of 2015. >> >> Please test as much as possible; bugs are much cheaper if we find them >> before the release! >> >> -- >> Regards, >> >> Austin Seipp, Haskell Consultant >> Well-Typed LLP, http://www.well-typed.com/ >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://www.haskell.org/mailman/listinfo/ghc-devs > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 4203 bytes Desc: not available URL: From mietek at bak.io Sat Feb 21 22:01:37 2015 From: mietek at bak.io (=?iso-8859-1?Q?Mi=EBtek_Bak?=) Date: Sat, 21 Feb 2015 22:01:37 +0000 Subject: ANNOUNCE: GHC 7.10.1 Release Candidate 2 In-Reply-To: <61A8F0FD-DA37-4861-BCDD-04891B295C87@bak.io> References: <6650493F-F6BD-4352-B4F1-5EA0CAE9D868@bak.io> <61A8F0FD-DA37-4861-BCDD-04891B295C87@bak.io> Message-ID: GHC 7.10.1-rc2 i386 also fails in the same fashion on Red Hat Enterprise Linux 6.5, which might be more concerning. Both failures appear to be caused by a GMP 4 vs 5 problem, previously reported as Solaris-specific: https://ghc.haskell.org/trac/ghc/ticket/10003 -- Mi?tek On 2015-02-21, at 20:19, Mi?tek Bak wrote: > My previous email was about the x86_64 bindist GHC 7.10.1-rc2. I?ve now added i386 support to Halcyon, and it appears only the x86_64 version works fine on CentOS 6 (6.5), while the i386 version fails to configure: > > checking for path to top of build tree... utils/ghc-pwd/dist-install/build/tmp/ghc-pwd: symbol lookup error: libraries/integer-gmp2/dist-install/build/libHSinteg_21cuTlnn00eFNd4GMrxOMi-ghc7.10.0.20150123.so: undefined symbol: __gmpn_andn_n > configure: error: cannot determine current directory > > > -- > Mi?tek > > > > > On 2015-01-27, at 06:26, Mi?tek Bak wrote: > >> It appears GHC 7.10.1-rc2 doesn?t support glibc 2.11 ? specifically, 2.11.1 (Ubuntu 10.04 LTS) and 2.11.3 (Debian 6). glibc 2.12 (CentOS 6) seems to work fine. Symptoms include: >> >> Installing library in >> /app/ghc/lib/ghc-7.10.0.20150123/ghc_0kOYffGYd794400D7yvIjm >> "/app/ghc/lib/ghc-7.10.0.20150123/bin/ghc-pkg" --force --global-package-db "/app/ghc/lib/ghc-7.10.0.20150123/package.conf.d" update rts/dist/package.conf.install >> Reading package info from "rts/dist/package.conf.install" ... done. >> "utils/ghc-cabal/dist-install/build/tmp/ghc-cabal-bindist" register libraries/ghc-prim dist-install "/app/ghc/lib/ghc-7.10.0.20150123/bin/ghc" "/app/ghc/lib/ghc-7.10.0.20150123/bin/ghc-pkg" "/app/ghc/lib/ghc-7.10.0.20150123" '' '/app/ghc' '/app/ghc/lib/ghc-7.10.0.20150123' '/app/ghc/share/doc/ghc/html/libraries' NO >> Warning: cannot determine version of /app/ghc/lib/ghc-7.10.0.20150123/bin/ghc >> : >> "" >> ghc-cabal: '/app/ghc/lib/ghc-7.10.0.20150123/bin/ghc' exited with an error: >> /app/ghc/lib/ghc-7.10.0.20150123/bin/ghc: symbol lookup error: >> /app/ghc/lib/ghc-7.10.0.20150123/bin/../rts/libHSrts_thr-ghc7.10.0.20150123.so: >> undefined symbol: pthread_setname_np >> >> The bindist name does mention 'deb7', so perhaps this is all working as intended. However, similarly named bindists for GHC 7.8.* work fine with glibc 2.11. >> >> >> In other news, I?m happy to say Halcyon now supports GHC 7.10.1-rc2 on CentOS 6 and 7, Debian 7, Fedora 19, 20, and 21, and Ubuntu 12 and 14. >> https://halcyon.sh/ >> >> $ halcyon install --ghc-version=7.10.1-rc2 --cabal-version=1.22.0.0 >> >> >> Best, >> >> -- >> Mi?tek >> >> >> >> >> On 2015-01-27, at 00:13, Austin Seipp wrote: >> >>> We are pleased to announce the second release candidate for GHC 7.10.1: >>> >>> https://downloads.haskell.org/~ghc/7.10.1-rc2/ >>> >>> This includes the source tarball and bindists for 64bit/32bit Linux >>> and Windows. Binary builds for other platforms will be available >>> shortly. (CentOS 6.5 binaries are not available at this time like they >>> were for 7.8.x). These binaries and tarballs have an accompanying >>> SHA256SUMS file signed by my GPG key id (0x3B58D86F). >>> >>> We plan to make the 7.10.1 release sometime in February of 2015. >>> >>> Please test as much as possible; bugs are much cheaper if we find them >>> before the release! >>> >>> -- >>> Regards, >>> >>> Austin Seipp, Haskell Consultant >>> Well-Typed LLP, http://www.well-typed.com/ >>> _______________________________________________ >>> ghc-devs mailing list >>> ghc-devs at haskell.org >>> http://www.haskell.org/mailman/listinfo/ghc-devs >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 4203 bytes Desc: not available URL: From ihmeckler at gmail.com Sun Feb 22 06:11:39 2015 From: ihmeckler at gmail.com (Izzy Meckler) Date: Sun, 22 Feb 2015 00:11:39 -0600 Subject: Writing a subtype function Message-ID: <5AE1600B-D388-423E-8174-75B5A4D7AD25@gmail.com> Hi all, I apologize if this isn?t the right place for this sort of question, but I?m at a loss as to how to use TcUnify.tcSubType. My goal is to write a function of type Type -> Type -> Ghc Bool which checks whether the first argument is a subtype of the second. I assume this is possible to do using TcUnify.tcSubType and runTcInteractive, but it?s not clear to me how. Any pointers here would be greatly appreciated. From johan.tibell at gmail.com Sun Feb 22 12:35:33 2015 From: johan.tibell at gmail.com (Johan Tibell) Date: Sun, 22 Feb 2015 13:35:33 +0100 Subject: FYI: Cabal-1.22.1.0 has been released Message-ID: We will probably want to ship that with GHC 7.10. -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Sun Feb 22 16:53:39 2015 From: svenpanne at gmail.com (Sven Panne) Date: Sun, 22 Feb 2015 17:53:39 +0100 Subject: FYI: Cabal-1.22.1.0 has been released In-Reply-To: References: Message-ID: 2015-02-22 13:35 GMT+01:00 Johan Tibell : > We will probably want to ship that with GHC 7.10. My usual request: A Ubuntu package for this in Herbert's Ubuntu PPA. :-) This way we can thoroughly test things in various combinations on Travis CI. From hvriedel at gmail.com Sun Feb 22 17:08:20 2015 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Sun, 22 Feb 2015 18:08:20 +0100 Subject: FYI: Cabal-1.22.1.0 has been released In-Reply-To: (Johan Tibell's message of "Sun, 22 Feb 2015 13:35:33 +0100") References: Message-ID: <87twydho1n.fsf@gmail.com> On 2015-02-22 at 13:35:33 +0100, Johan Tibell wrote: > We will probably want to ship that with GHC 7.10. I've updated the ghc-7.10 branch's Cabal submodule to point to commit 9225192b7afc2b96062fb991cc3d16cccb9de1b0 (which corresponds to the Cabal-v1.22.1.0 tag) Cheers, hvr From omeragacan at gmail.com Sun Feb 22 18:51:02 2015 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Sun, 22 Feb 2015 13:51:02 -0500 Subject: FYI: Cabal-1.22.1.0 has been released In-Reply-To: <87twydho1n.fsf@gmail.com> References: <87twydho1n.fsf@gmail.com> Message-ID: Where can we see the changelog? https://github.com/haskell/cabal/blob/master/Cabal/changelog <- this file has not been updated. 2015-02-22 12:08 GMT-05:00 Herbert Valerio Riedel : > On 2015-02-22 at 13:35:33 +0100, Johan Tibell wrote: >> We will probably want to ship that with GHC 7.10. > > I've updated the ghc-7.10 branch's Cabal submodule to point to commit > 9225192b7afc2b96062fb991cc3d16cccb9de1b0 (which corresponds to the > Cabal-v1.22.1.0 tag) > > Cheers, > hvr > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From simonpj at microsoft.com Mon Feb 23 14:18:18 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 23 Feb 2015 14:18:18 +0000 Subject: Writing a subtype function In-Reply-To: <5AE1600B-D388-423E-8174-75B5A4D7AD25@gmail.com> References: <5AE1600B-D388-423E-8174-75B5A4D7AD25@gmail.com> Message-ID: <618BE556AADD624C9C918AA5D5911BEF7BEB2750@DB3PRD3001MB020.064d.mgd.msft.net> | I?m at a loss as to how to use TcUnify.tcSubType. My goal is to write a | function of type | | Type -> Type -> Ghc Bool I assume you are talking here about the GHC API? tcSubType is usually called during type inference, and it rightly does not return a Bool. Why? Because we may not know whether it will succeed or fail until we have walked the entire syntax tree of the program; perhaps there is a bit of code that forces a crucial unification. So tcSubType returns a `HsWrapper`, which you can use to wrap a term of type t1, to produce a term of type t2. It ALSO emits some constraints (in the monad) which can be solved later. If the constraints are soluble, we have a proof that t1 is a subtype of t2. If not, we don?t. In the context of the GHC API you probably need something like do { (_wrapper, constraints) <- captureConstraints (tcSubType t1 t2) ; tcSimplifyTop constraints } The 'captureConstraints' grabs the constraints generated by tcSubType; the tcSimplifyTop tries to solve them and reports errors. If you don?t want to report errors, you can doubtless use some variant of tcSimplifyTop. I hope this helps Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Izzy | Meckler | Sent: 22 February 2015 06:12 | To: ghc-devs at haskell.org | Subject: Writing a subtype function | | Hi all, | | I apologize if this isn?t the right place for this sort of question, but | I?m at a loss as to how to use TcUnify.tcSubType. My goal is to write a | function of type | | Type -> Type -> Ghc Bool | | which checks whether the first argument is a subtype of the second. I | assume this is possible to do using TcUnify.tcSubType and | runTcInteractive, but it?s not clear to me how. Any pointers here would | be greatly appreciated. | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From simonpj at microsoft.com Mon Feb 23 14:18:18 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 23 Feb 2015 14:18:18 +0000 Subject: Desugaring introduces In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF7BEB2764@DB3PRD3001MB020.064d.mgd.msft.net> Gabor You don't say which version of GHC you are using. I assume 7.8. Yes, you should really get the same behaviour with the surgared and desugared versions. Happily, with HEAD (and 7.6) it compiles fine without ImpredicativeTypes. Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Gabor | Greif | Sent: 21 February 2015 11:42 | To: ghc-devs | Subject: Desugaring introduces | | Hi devs, | | before I file a bug, I'd like to double check on a strange desugaring | behaviour with RankNTypes and RebindableSyntax. | | Here is the snippet | {{{ | {-# LANGUAGE RankNTypes, RebindableSyntax #-} | {-# LANGUAGE ImpredicativeTypes #-} | | import qualified Prelude as P | | (>>=) :: a -> ((forall b . b) -> c) -> c | a >>= f = f P.undefined | return a = a | fail s = P.undefined | | t1 = 'd' >>= (\_ -> 'k') | | t2 = do _ <- 'd' | 'k' | | main = P.putStrLn [t1, t2] | }}} | | Without ImpredicativeTypes I get this error: | {{{ | rebindtest.hs:13:9: | Cannot instantiate unification variable ?t0? | with a type involving foralls: forall b. b | Perhaps you want ImpredicativeTypes | In a stmt of a 'do' block: _ <- 'd' | In the expression: | do { _ <- 'd'; | 'k' } | In an equation for ?t2?: | t2 | = do { _ <- 'd'; | 'k' } | }}} | | t1 is supposed to be the desugaring of t2. Strangely t2 only compiles | with ImpredicativeTypes. Why? Isn't desugaring a purely syntactic | transformation (esp. with RebindableSyntax)? | | Any hints welcome! | | Cheers, | | Gabor | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From ggreif at gmail.com Mon Feb 23 14:52:03 2015 From: ggreif at gmail.com (Gabor Greif) Date: Mon, 23 Feb 2015 15:52:03 +0100 Subject: Desugaring introduces In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF7BEB2764@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF7BEB2764@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Yes, I am using 7.8. I'll also try HEAD now... ... and it works! :-) Thanks, I am happy now. Cheers, Gabor PS: Would it be worth adding this as a regression test? On 2/23/15, Simon Peyton Jones wrote: > Gabor > > You don't say which version of GHC you are using. I assume 7.8. > > Yes, you should really get the same behaviour with the surgared and > desugared versions. > > Happily, with HEAD (and 7.6) it compiles fine without ImpredicativeTypes. > > Simon > > | -----Original Message----- > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Gabor > | Greif > | Sent: 21 February 2015 11:42 > | To: ghc-devs > | Subject: Desugaring introduces > | > | Hi devs, > | > | before I file a bug, I'd like to double check on a strange desugaring > | behaviour with RankNTypes and RebindableSyntax. > | > | Here is the snippet > | {{{ > | {-# LANGUAGE RankNTypes, RebindableSyntax #-} > | {-# LANGUAGE ImpredicativeTypes #-} > | > | import qualified Prelude as P > | > | (>>=) :: a -> ((forall b . b) -> c) -> c > | a >>= f = f P.undefined > | return a = a > | fail s = P.undefined > | > | t1 = 'd' >>= (\_ -> 'k') > | > | t2 = do _ <- 'd' > | 'k' > | > | main = P.putStrLn [t1, t2] > | }}} > | > | Without ImpredicativeTypes I get this error: > | {{{ > | rebindtest.hs:13:9: > | Cannot instantiate unification variable ?t0? > | with a type involving foralls: forall b. b > | Perhaps you want ImpredicativeTypes > | In a stmt of a 'do' block: _ <- 'd' > | In the expression: > | do { _ <- 'd'; > | 'k' } > | In an equation for ?t2?: > | t2 > | = do { _ <- 'd'; > | 'k' } > | }}} > | > | t1 is supposed to be the desugaring of t2. Strangely t2 only compiles > | with ImpredicativeTypes. Why? Isn't desugaring a purely syntactic > | transformation (esp. with RebindableSyntax)? > | > | Any hints welcome! > | > | Cheers, > | > | Gabor > | _______________________________________________ > | ghc-devs mailing list > | ghc-devs at haskell.org > | http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From david.feuer at gmail.com Mon Feb 23 17:45:20 2015 From: david.feuer at gmail.com (David Feuer) Date: Mon, 23 Feb 2015 12:45:20 -0500 Subject: Proposal: Turn on ScopedTypeVariables by default In-Reply-To: References: Message-ID: I know this will be controversial, because it can break (weird) code and because it's not Haskell 2010, but hey, you can't make brain salad without breaking a few heads. ScopedTypeVariables is just awesome for two fundamental reasons: 1. It lets you write type signatures for more things. 2. It lets you write more precise type signatures for many things. As a consequence of those two, 3. It helps you get much better error messages from the type checker. And for all that, 4. It's really easy to use. What do other people think? -------------- next part -------------- An HTML attachment was scrubbed... URL: From afarmer at ittc.ku.edu Mon Feb 23 17:59:22 2015 From: afarmer at ittc.ku.edu (Andrew Farmer) Date: Mon, 23 Feb 2015 11:59:22 -0600 Subject: Proposal: Turn on ScopedTypeVariables by default In-Reply-To: References: Message-ID: I have often thought the same thing. This is probably the language extension I enable the most... a quick grep shows about 40% of my modules. I'm guessing the problem is that its not Haskell 98/2010? I think GHC has a policy to do only what the spec says by default. Is that still true now that AMP is implemented? You could just always include it in the 'extensions' field of your cabal file. Then it will apply to your whole project. On Mon, Feb 23, 2015 at 11:45 AM, David Feuer wrote: > I know this will be controversial, because it can break (weird) code and > because it's not Haskell 2010, but hey, you can't make brain salad without > breaking a few heads. ScopedTypeVariables is just awesome for two > fundamental reasons: > > 1. It lets you write type signatures for more things. > 2. It lets you write more precise type signatures for many things. > > As a consequence of those two, > > 3. It helps you get much better error messages from the type checker. > > And for all that, > > 4. It's really easy to use. > > What do other people think? > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From allbery.b at gmail.com Mon Feb 23 18:05:37 2015 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 23 Feb 2015 13:05:37 -0500 Subject: Proposal: Turn on ScopedTypeVariables by default In-Reply-To: References: Message-ID: On Mon, Feb 23, 2015 at 12:59 PM, Andrew Farmer wrote: > I'm guessing the problem is that its not Haskell 98/2010? I think GHC > has a policy to do only what the spec says by default. Is that still > true now that AMP is implemented? > I think the main worry is that it steals syntax, specifically the `forall` keyword, which is just an identifier in H'98 and H'2010. (And some bikeshedding over `forall` being inappropriate for this use, but I suspect that ship sailed long ago.) -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From johan.tibell at gmail.com Mon Feb 23 19:54:10 2015 From: johan.tibell at gmail.com (Johan Tibell) Date: Mon, 23 Feb 2015 20:54:10 +0100 Subject: FYI: Cabal-1.22.1.0 has been released In-Reply-To: References: <87twydho1n.fsf@gmail.com> Message-ID: I didn't have the energy to write one. On Sun, Feb 22, 2015 at 7:51 PM, ?mer Sinan A?acan wrote: > Where can we see the changelog? > https://github.com/haskell/cabal/blob/master/Cabal/changelog <- this > file has not been updated. > > 2015-02-22 12:08 GMT-05:00 Herbert Valerio Riedel : > > On 2015-02-22 at 13:35:33 +0100, Johan Tibell wrote: > >> We will probably want to ship that with GHC 7.10. > > > > I've updated the ghc-7.10 branch's Cabal submodule to point to commit > > 9225192b7afc2b96062fb991cc3d16cccb9de1b0 (which corresponds to the > > Cabal-v1.22.1.0 tag) > > > > Cheers, > > hvr > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From johan.tibell at gmail.com Mon Feb 23 19:54:32 2015 From: johan.tibell at gmail.com (Johan Tibell) Date: Mon, 23 Feb 2015 20:54:32 +0100 Subject: FYI: Cabal-1.22.1.0 has been released In-Reply-To: References: Message-ID: Make that 1.22.1.1. Had to fix a regression for Configure-based .cabal files. On Sun, Feb 22, 2015 at 1:35 PM, Johan Tibell wrote: > We will probably want to ship that with GHC 7.10. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From the.dead.shall.rise at gmail.com Mon Feb 23 20:13:32 2015 From: the.dead.shall.rise at gmail.com (Mikhail Glushenkov) Date: Mon, 23 Feb 2015 21:13:32 +0100 Subject: FYI: Cabal-1.22.1.0 has been released In-Reply-To: References: <87twydho1n.fsf@gmail.com> Message-ID: On 22 February 2015 at 19:51, ?mer Sinan A?acan wrote: > Where can we see the changelog? > https://github.com/haskell/cabal/blob/master/Cabal/changelog <- this > file has not been updated. It's a bugfix release. Check out https://github.com/haskell/cabal/compare/Cabal-v1.22.0.0...Cabal-v1.22.1.1 From ihmeckler at gmail.com Mon Feb 23 20:18:41 2015 From: ihmeckler at gmail.com (Izzy Meckler) Date: Mon, 23 Feb 2015 14:18:41 -0600 Subject: Writing a subtype function In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF7BEB2750@DB3PRD3001MB020.064d.mgd.msft.net> References: <5AE1600B-D388-423E-8174-75B5A4D7AD25@gmail.com> <618BE556AADD624C9C918AA5D5911BEF7BEB2750@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Wonderful, even more than I thought I needed (i.e., actually getting the evidence). Thanks Simon! > On Feb 23, 2015, at 8:18 AM, Simon Peyton Jones wrote: > > | I?m at a loss as to how to use TcUnify.tcSubType. My goal is to write a > | function of type > | > | Type -> Type -> Ghc Bool > > I assume you are talking here about the GHC API? tcSubType is usually called during type inference, and it rightly does not return a Bool. Why? Because we may not know whether it will succeed or fail until we have walked the entire syntax tree of the program; perhaps there is a bit of code that forces a crucial unification. > > So tcSubType returns a `HsWrapper`, which you can use to wrap a term of type t1, to produce a term of type t2. > > It ALSO emits some constraints (in the monad) which can be solved later. If the constraints are soluble, we have a proof that t1 is a subtype of t2. If not, we don?t. > > In the context of the GHC API you probably need something like > > do { (_wrapper, constraints) <- captureConstraints (tcSubType t1 t2) > ; tcSimplifyTop constraints } > > The 'captureConstraints' grabs the constraints generated by tcSubType; the tcSimplifyTop tries to solve them and reports errors. If you don?t want to report errors, you can doubtless use some variant of tcSimplifyTop. > > I hope this helps > > Simon > > | -----Original Message----- > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Izzy > | Meckler > | Sent: 22 February 2015 06:12 > | To: ghc-devs at haskell.org > | Subject: Writing a subtype function > | > | Hi all, > | > | I apologize if this isn?t the right place for this sort of question, but > | I?m at a loss as to how to use TcUnify.tcSubType. My goal is to write a > | function of type > | > | Type -> Type -> Ghc Bool > | > | which checks whether the first argument is a subtype of the second. I > | assume this is possible to do using TcUnify.tcSubType and > | runTcInteractive, but it?s not clear to me how. Any pointers here would > | be greatly appreciated. > | _______________________________________________ > | ghc-devs mailing list > | ghc-devs at haskell.org > | http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From greg at gregweber.info Mon Feb 23 20:45:00 2015 From: greg at gregweber.info (Greg Weber) Date: Mon, 23 Feb 2015 12:45:00 -0800 Subject: FYI: Cabal-1.22.1.0 has been released In-Reply-To: References: Message-ID: Rather than putting all the burden of the changelog on yourself and others doing the release. you could try asking on every pull request that is changelog-worthy for the author to put an entry in the changelog. This is what GHC does (similar with respect to the user guide). On Mon, Feb 23, 2015 at 11:54 AM, Johan Tibell wrote: > Make that 1.22.1.1. Had to fix a regression for Configure-based .cabal > files. > > On Sun, Feb 22, 2015 at 1:35 PM, Johan Tibell > wrote: > >> We will probably want to ship that with GHC 7.10. >> > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From johan.tibell at gmail.com Mon Feb 23 20:49:48 2015 From: johan.tibell at gmail.com (Johan Tibell) Date: Mon, 23 Feb 2015 21:49:48 +0100 Subject: FYI: Cabal-1.22.1.0 has been released In-Reply-To: References: Message-ID: Greg, Yes I agree. I forget sometimes and we haven't managed to make it a policy (I don't merge all pull requests myself.) On Mon, Feb 23, 2015 at 9:45 PM, Greg Weber wrote: > Rather than putting all the burden of the changelog on yourself and others > doing the release. you could try asking on every pull request that is > changelog-worthy for the author to put an entry in the changelog. This is > what GHC does (similar with respect to the user guide). > > On Mon, Feb 23, 2015 at 11:54 AM, Johan Tibell > wrote: > >> Make that 1.22.1.1. Had to fix a regression for Configure-based .cabal >> files. >> >> On Sun, Feb 22, 2015 at 1:35 PM, Johan Tibell >> wrote: >> >>> We will probably want to ship that with GHC 7.10. >>> >> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Feb 23 22:53:29 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 23 Feb 2015 22:53:29 +0000 Subject: GHC Type Inference In-Reply-To: <20150223105419.GA11479@csmvddesktop> References: <20150223105419.GA11479@csmvddesktop> Message-ID: <618BE556AADD624C9C918AA5D5911BEF7BEB3647@DB3PRD3001MB020.064d.mgd.msft.net> Marc For type-level literals, the man to talk to is Iavor Diatchki. He implemented the current system, and has been working on enhancements. I'm sure he'd welcome help! There's also quite an active sub-group (on ghc-devs) working on "plug-ins" for the type inference algorithm, aimed at allowing things like better arithmetic reasoning to be done without having to change GHC itself. Simon | -----Original Message----- | From: dongen [mailto:dongen at cs.ucc.ie] | Sent: 23 February 2015 10:54 | To: Simon Peyton Jones | Cc: ghc-devs at haskell.org | Subject: GHC Type Inference | | Dear Simon, | | | I am cc-ing _ghc-devs at haskell.org_ as requested on _ghc.haskell.org_. | | I hope you're fine. | | On _ghc.haskell.org_ I noticed you are the ``owner'' of _type | inference and interface files._ | | A year ago I started a project that requires integer type-level | literals but I soon had to drop it because GHC wasn't able to | simplify simple type equalities. As a consequence, I had to | add lots and lots of constraints to make my code work, which | effectively meant the code became unmaintainable because a small | change requlted in lots of errors. | | I know have a bit more time to work on the project and I'd like | to see if it's possible to ``talk'' to somebody in the GHC team | to see if we can improve type-level literal inference for natural | numbers. | | Is there somebody who's ``responsible'' for this area in the GHC | team? If yes, would you mind giving me their contact details? | | Regards, | | | Marc van Dongen From austin at well-typed.com Mon Feb 23 23:56:10 2015 From: austin at well-typed.com (Austin Seipp) Date: Mon, 23 Feb 2015 17:56:10 -0600 Subject: GHC Weekly News - 2015/02/23 Message-ID: (This post is available online at https://ghc.haskell.org/trac/ghc/blog/edit/weekly20150223) Hi *, It's once again time for your sometimes-slightly-irregularly-scheduled GHC news! This past Friday marked the end of the FTP vote for GHC 7.10, there's an RC on the way (see below), we've closed out a good set of patches and tickets from users and pushed them into `HEAD`, and to top it off - it's your editor's birthday today, so that's nice! Quick note: as said above GHC HQ is expecting to make a '''third''' release candidate for GHC 7.10.1 soon in early March since the delay has allowed us to pick up some more changes and bugfixes. We plan on the final release being close to the end of March (previously end of February). This week, GHC HQ met up again to discuss and write down our current priorities and thoughts: - After discussing our current timetable - as we're currently hovering around the ICFP deadline - we're hoping to make our third GHC 7.10.1 release candidate on '''Friday, March 13th''', with the final release on '''Friday, March 27th'''. This was the main take away from our meeting today. We've also had a little more list activity this week than we did before: - The FTP debate has ended, and the results are in: GHC 7.10.1 will continue with the generalized Prelude, known as "Plan FTP". https://mail.haskell.org/pipermail/libraries/2015-February/025009.html - Edward Kmett announced the `directory` package needed an active maintainer to step up - and luckily, Phil Ruffwind and Elliot Robinson did just that and stepped up as maintainers! https://mail.haskell.org/pipermail/ghc-devs/2015-February/008358.html - Kazu Yamamoto asked about a behavioral change in `ghc-7.10` for `Data.Char` - it turns out this difference looks like it's caused by GHC 7.10 shipping an update to use Unicode 7.0 datasets. https://mail.haskell.org/pipermail/ghc-devs/2015-February/008371.html - Thomas Bereknyei asked about a fundamental change in the Arrow desugarer, and whether or not something like this was worth it. Jan Stolarek and Ross Paterson stepped in to speak up to some specifics Thomas had about. https://mail.haskell.org/pipermail/ghc-devs/2015-February/008377.html - Gabor Grief spoke up about strange behavior in the desugarer when using `RebindableSyntax` and `RankNTypes`, which Adam Gundry popped in to say may be a deeper issue due to the way typechecking and desugaring interact - https://mail.haskell.org/pipermail/ghc-devs/2015-February/008383.html - Johan Tibell announced Cabal 1.22.1.0, which will ship with GHC 7.10. https://mail.haskell.org/pipermail/ghc-devs/2015-February/008388.html Some noteworthy commits that went into `ghc.git` in the past week include: - Commit 1b82619bc2ff36341d916c56b0cd67a378a9c222 - The `hpc` commands now take a configurable verbosity level (merged to `ghc-7.10) - Commit 0fa20726b0587530712677e50a56c2b03ba43095 - GHC now errors out on a module explicitly declared `Main` without a `main` export. Closed tickets the past week include: #9266, #10095, #9959, #10086, #9094, #9606, #9402, #10093, #9054, #10102, #4366, #7604, #9103, #10104, #7765, #7103, #10051, #7056, #9907, #10078, #10096, #10072, #10043, #9926, #10088, #10091, #8309, #9049, #9895, and #8539. -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From iavor.diatchki at gmail.com Tue Feb 24 00:38:21 2015 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Mon, 23 Feb 2015 16:38:21 -0800 Subject: GHC Type Inference In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF7BEB3647@DB3PRD3001MB020.064d.mgd.msft.net> References: <20150223105419.GA11479@csmvddesktop> <618BE556AADD624C9C918AA5D5911BEF7BEB3647@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: Greetings, The latest type-nat solver is available as a GHC plugin. The repo is here: https://github.com/yav/type-nat-solver I just pushed a small fix-up and now it works with the GHC 7.10 release candidate. The plugin makes use of an external solver (the plugin is currently hard-coded to use `cvc4` but we should really parametrize on this). I've not tested it a lot, but basic vector manipulation with GADTs works fairly well, so you can do things like the examples at the end of the e-mail. If Marc---or anyone else---is interested in hacking on this, I'd be most happy to collaborate, as I haven't had much time to work on this for the last couple of a months. We can push this is many interesting directions. Here are some ideas: - Work on writing a Haskell based decision procedure; this would remove the need for calling an external tool - Explore and improve the current support for type naturals (e.g., add rules to go beyond linear arithmetic). - Explore other theories: the code in the current plugin happens to use the theory of linear arithmetic, but most of the implementation is agnostic to the actual theory used (apart from recognizing the symbols that belong to the theory). So we have an opportunity to explore potential uses of other theories (e.g., bit-vectors at the type level could be used to implement finite sets, or type-level modulo arithmetic; some solvers have experimental support for the theory of sets, so we could have interesting reasoning about sets of various things: unions, intersections, etc). Lots of interesting work to do, and not enough hacking time! If there are questions, please drop me an e-mail directly, or we can chat on the ghc-devs list, in case there are other interested developers. Cheers, -Iavor Examples that work at the moment: f :: ((a + 6) ~ x) => Proxy x -> () f = g g :: ((6 <=? x) ~ True) => Proxy x -> () g _ = () data Vec :: Nat -> * -> * where Nil :: Vec 0 a Cons :: a -> Vec n a -> Vec (n + 1) a append :: Vec m a -> Vec n a -> Vec (n + m) a append Nil ys = ys append (Cons x xs) ys = Cons x (append xs ys) reverse = go Nil where go :: Vec m a -> Vec n a -> Vec (m + n) a go xs Nil = xs go xs (Cons y ys) = go (Cons y xs) ys f1 :: Proxy (2 + a) -> () f1 = g1 g1 :: Proxy (1 + a) -> () g1 _ = () On Mon, Feb 23, 2015 at 2:53 PM, Simon Peyton Jones wrote: > Marc > > For type-level literals, the man to talk to is Iavor Diatchki. He > implemented the current system, and has been working on enhancements. I'm > sure he'd welcome help! > > There's also quite an active sub-group (on ghc-devs) working on "plug-ins" > for the type inference algorithm, aimed at allowing things like better > arithmetic reasoning to be done without having to change GHC itself. > > Simon > > | -----Original Message----- > | From: dongen [mailto:dongen at cs.ucc.ie] > | Sent: 23 February 2015 10:54 > | To: Simon Peyton Jones > | Cc: ghc-devs at haskell.org > | Subject: GHC Type Inference > | > | Dear Simon, > | > | > | I am cc-ing _ghc-devs at haskell.org_ as requested on _ghc.haskell.org_. > | > | I hope you're fine. > | > | On _ghc.haskell.org_ I noticed you are the ``owner'' of _type > | inference and interface files._ > | > | A year ago I started a project that requires integer type-level > | literals but I soon had to drop it because GHC wasn't able to > | simplify simple type equalities. As a consequence, I had to > | add lots and lots of constraints to make my code work, which > | effectively meant the code became unmaintainable because a small > | change requlted in lots of errors. > | > | I know have a bit more time to work on the project and I'd like > | to see if it's possible to ``talk'' to somebody in the GHC team > | to see if we can improve type-level literal inference for natural > | numbers. > | > | Is there somebody who's ``responsible'' for this area in the GHC > | team? If yes, would you mind giving me their contact details? > | > | Regards, > | > | > | Marc van Dongen > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Tue Feb 24 08:32:01 2015 From: mail at joachim-breitner.de (Joachim Breitner) Date: Tue, 24 Feb 2015 09:32:01 +0100 Subject: Docs of the daily builds broken Message-ID: <1424766721.2136.6.camel@joachim-breitner.de> Hi, while the index at http://haskell.inf.elte.hu/docs/7.11.20150222.noWin32/html/libraries/index.html exists, navigating to http://haskell.inf.elte.hu/docs/7.11.20150222.noWin32/html/libraries/Data-Char.html yields a 404 error. Same for http://haskell.inf.elte.hu/docs/latest/html/libraries/Data-Char.html Additinally, the wiki page at https://ghc.haskell.org/trac/ghc/wiki/BuilderSummary does not list a point of contact for this (and I regularly forget these things. Was it Gabor?). Whoever runs this: Good job! Make sure you take the credit! :-) Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0xF0FBF51F Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From pali.gabor at gmail.com Tue Feb 24 10:26:47 2015 From: pali.gabor at gmail.com (=?UTF-8?B?UMOhbGkgR8OhYm9yIErDoW5vcw==?=) Date: Tue, 24 Feb 2015 11:26:47 +0100 Subject: Docs of the daily builds broken In-Reply-To: <1424766721.2136.6.camel@joachim-breitner.de> References: <1424766721.2136.6.camel@joachim-breitner.de> Message-ID: Hi there, 2015-02-24 9:32 GMT+01:00 Joachim Breitner : > while the index at > http://haskell.inf.elte.hu/docs/7.11.20150222.noWin32/html/libraries/index.html > exists, navigating to > http://haskell.inf.elte.hu/docs/7.11.20150222.noWin32/html/libraries/Data-Char.html > yields a 404 error. > > Same for > http://haskell.inf.elte.hu/docs/latest/html/libraries/Data-Char.html Yes, I can confirm this bug. For what it is worth, the files are all there, the link appears to be broken: it is missing the subdirectory with the name of the package. That is, the proper link should be something like that: http://haskell.inf.elte.hu/docs/7.9.20141222.noWin32/html/libraries/base-4.8.0.0/Data-Char.html (Note the missing "base-4.8.0.0".) I have checked this with GHC 7.8.3, and everything is right there, while this problem seems to appear with GHC 7.10 RC2 and GHC-HEAD (starting from somewhere between mid-September and November -- that is what a quick bisecting tells me). > Additinally, the wiki page at > https://ghc.haskell.org/trac/ghc/wiki/BuilderSummary > does not list a point of contact for this Indeed, it seems I forgot to add a link back to the GHC builder page :-) Thanks for noticing this, I will do this shortly. Cheers, Gabor From hvriedel at gmail.com Tue Feb 24 12:46:39 2015 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Tue, 24 Feb 2015 13:46:39 +0100 Subject: Proposal: Turn on ScopedTypeVariables by default In-Reply-To: (David Feuer's message of "Mon, 23 Feb 2015 12:45:20 -0500") References: Message-ID: <87fv9vjx3k.fsf@gmail.com> On 2015-02-23 at 18:45:20 +0100, David Feuer wrote: > I know this will be controversial, because it can break (weird) code and > because it's not Haskell 2010, but hey, you can't make brain salad without > breaking a few heads. Are you suggesting enabling -XScopedTypeVariables for -XHaskell98 and -XHaskell2010? or rather for the default when neither of those two modes is explicitly requested? Just be warned though: this is somewhat of a trick-question... :-) From roma at ro-che.info Tue Feb 24 12:55:32 2015 From: roma at ro-che.info (Roman Cheplyaka) Date: Tue, 24 Feb 2015 14:55:32 +0200 Subject: Proposal: Turn on ScopedTypeVariables by default In-Reply-To: <87fv9vjx3k.fsf@gmail.com> References: <87fv9vjx3k.fsf@gmail.com> Message-ID: <54EC74C4.8050605@ro-che.info> On 24/02/15 14:46, Herbert Valerio Riedel wrote: > On 2015-02-23 at 18:45:20 +0100, David Feuer wrote: >> I know this will be controversial, because it can break (weird) code and >> because it's not Haskell 2010, but hey, you can't make brain salad without >> breaking a few heads. > > Are you suggesting enabling -XScopedTypeVariables for -XHaskell98 and > -XHaskell2010? or rather for the default when neither of those two modes > is explicitly requested? > > Just be warned though: this is somewhat of a trick-question... :-) Maybe in addition to -XHaskell98 and -XHaskell2010 there should also be -XGhcHaskell. ghc already deviates from the standard by default (e.g. -XNondecreasingIndentation). OTOH we probably don't want end up with -fglasgow-exts once again. Roman From tomberek at gmail.com Tue Feb 24 14:52:51 2015 From: tomberek at gmail.com (Thomas Bereknyei) Date: Tue, 24 Feb 2015 09:52:51 -0500 Subject: Arrow Development In-Reply-To: <20150221103903.GA2507@city.ac.uk> References: <20150221103903.GA2507@city.ac.uk> Message-ID: Using RULES to simplify arrows in conjunction with proc-do notation doesn't seem feasible. (If i'm wrong, please tell me). The desugarer seems to use lambdas that can't be captured by RULES: (\ ds_d9Aj -> let! { (a_a851, b_a852) ~ _ <- ds_d9Aj } in ((a_a851, b_a852), ()))) or (\ ds_d9Ai -> let! { (ds_d9Ag, _) ~ _ <- ds_d9Ai } in ds_d9Ag)) or (\ ds_d9Ab -> let! { (a_a851, b_a852) ~ _ <- ds_d9Ab } in (((a_a851, b_a852), ()), ()))) The constant shuffling of the tuples in comparison to the point-free arrow style also seems to make it harder to optimize. This change [1] is stalled at the moment and I'm also not sure how much it would help. Would using named functions allow one to use RULES? On the other hand, how can we obtain a better result without the tuple overhead? Does proc notation require it and can we obtain a better translation of proc to a point-free style? [1](https://phabricator.haskell.org/D72) On Sat, Feb 21, 2015 at 5:39 AM, Ross Paterson wrote: > On Fri, Feb 20, 2015 at 02:58:14AM -0500, Thomas Bereknyei wrote: > > I am looking at the proc notation de-sugar and I see results like this > when > > using a Free Arrow (mostly copied from [1]): > > line2 = proc n -> do > > Effect getURLSum *** Effect getURLSum -< n > > > > Seq [Pure ] (Seq [Pure ] (Seq [Pure ] (Seq [Pure ](Par {Effect > } ) ) ) ) > > > > while this is so much simpler: > > line2 = Effect getURLSum *** Effect getURLSum > > > > Par {Effect } > > > > Those `Seq [Pure ]` sequences come from application of (.) and I have > noticed > > many similar inefficiencies in the Arrow preprocessor. Eventually the > goal > > would be to optimize when possible, for example I started looking into > this in > > order to use `concurrently` for (***) when in IO. > > > > There was a rewrite mentioned here [2]. The deSugar/DsArrows.hs [3] looks > > convoluted. Any progress or work needed? Or are Arrows not used much and > not > > worth the effort? > > I don't think it's feasible to try to do optimization in the desugarer, > which certainly is convoluted. You might have more luck using RULES to > simplify the output. > > (The desugarer could be simplified -- a lot of what it does probably > belongs > in the renamer -- but I'm not sure that would help with optimization.) > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Wed Feb 25 05:41:37 2015 From: michael at snoyman.com (Michael Snoyman) Date: Wed, 25 Feb 2015 05:41:37 +0000 Subject: Broken `cabal haddock --hoogle` with GHC 7.10 Message-ID: I'm not really able to follow the details of this, but I wanted to raise to everyone's attention a serious bug with the current GHC 7.10 RC, Cabal 1.22, and/or Haddock. Currently, running `cabal haddock --hoogle` does not work. There seem to be two different issues open about it: https://github.com/haskell/haddock/issues/361 https://github.com/haskell/cabal/issues/2297 I really don't understand the issues here, but I'd claim that the severity of this should probably be a blocker for a GHC 7.10 release. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Wed Feb 25 05:47:08 2015 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Wed, 25 Feb 2015 05:47:08 +0000 Subject: Broken `cabal haddock --hoogle` with GHC 7.10 In-Reply-To: References: Message-ID: <54ED61DC.4030400@fuuzetsu.co.uk> On 02/25/2015 05:41 AM, Michael Snoyman wrote: > I'm not really able to follow the details of this, but I wanted to raise to > everyone's attention a serious bug with the current GHC 7.10 RC, Cabal > 1.22, and/or Haddock. Currently, running `cabal haddock --hoogle` does not > work. There seem to be two different issues open about it: > > https://github.com/haskell/haddock/issues/361 > https://github.com/haskell/cabal/issues/2297 > > I really don't understand the issues here, but I'd claim that the severity > of this should probably be a blocker for a GHC 7.10 release. > > I think only work needs to go into cabal now. GHCs point of concern here is that it ships with a patched cabal for this when the patch does get crafted rather than only dumped onto the master branch. It's already fixed on Haddock side and I believe the change is on 7.10 branch. So I guess this is just a FYI that something is broken and we're awaiting cabal patch. -- Mateusz K. From jan.bracker at googlemail.com Wed Feb 25 10:55:43 2015 From: jan.bracker at googlemail.com (Jan Bracker) Date: Wed, 25 Feb 2015 10:55:43 +0000 Subject: EvTerms and how they are used Message-ID: Hello, I am trying to use the new type checker plugins [1] that are implemented in head. When successful a plugin has to return a [(EvTerm, Ct)] for the solved constraints. The documentation on EvTerms is scarce [2,3,4] and I could not find papers that explain them (many talk about 'evidence', but they never get concrete). So far I have figured out that "EvDFunApp DFunId [Type] [EvTerm]" selects a certain instance to be used for a constraint, though I don't know what the list of EvTerms in the end is for. I am also a bit unclear on how the "[Type]" is used.If I turn on '-dcore-lint' I get errors. So I still seem to be using it wrong. I have also asked in IRC, but did not get a response to my question. I am sorry if this is the wrong mailing list to ask. If there is a more apropriate place just point it out. Best, Jan [1]: https://ghc.haskell.org/trac/ghc/wiki/Plugins/TypeChecker [2]: http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/libraries/ghc-7.11.20150225/TcEvidence.html#t:EvTerm [3]: http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/libraries/ghc-7.11.20150225/src/TcEvidence.html#EvTerm [4]: http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/users_guide/compiler-plugins.html -------------- next part -------------- An HTML attachment was scrubbed... URL: From ndmitchell at gmail.com Wed Feb 25 10:57:40 2015 From: ndmitchell at gmail.com (Neil Mitchell) Date: Wed, 25 Feb 2015 10:57:40 +0000 Subject: Broken `cabal haddock --hoogle` with GHC 7.10 In-Reply-To: <54ED61DC.4030400@fuuzetsu.co.uk> References: <54ED61DC.4030400@fuuzetsu.co.uk> Message-ID: When you say "change is on the 7.10 branch", you mean a fix for Haddock, or changes to Cabal? There are also other issues with the --hoogle output, the newest regression being that constructors are wrapped in square brackets, for example: [Nothing] :: Maybe a Generally, the --hoogle output from Haddock keeps going downhill. When I first implemented it, there was a test suite, but that seems to no longer be catching issues. Thanks, Neil On Wed, Feb 25, 2015 at 5:47 AM, Mateusz Kowalczyk wrote: > On 02/25/2015 05:41 AM, Michael Snoyman wrote: >> I'm not really able to follow the details of this, but I wanted to raise to >> everyone's attention a serious bug with the current GHC 7.10 RC, Cabal >> 1.22, and/or Haddock. Currently, running `cabal haddock --hoogle` does not >> work. There seem to be two different issues open about it: >> >> https://github.com/haskell/haddock/issues/361 >> https://github.com/haskell/cabal/issues/2297 >> >> I really don't understand the issues here, but I'd claim that the severity >> of this should probably be a blocker for a GHC 7.10 release. >> >> > > I think only work needs to go into cabal now. GHCs point of concern here > is that it ships with a patched cabal for this when the patch does get > crafted rather than only dumped onto the master branch. It's already > fixed on Haddock side and I believe the change is on 7.10 branch. > > So I guess this is just a FYI that something is broken and we're > awaiting cabal patch. > > > -- > Mateusz K. > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From adam at well-typed.com Wed Feb 25 13:35:10 2015 From: adam at well-typed.com (Adam Gundry) Date: Wed, 25 Feb 2015 13:35:10 +0000 Subject: EvTerms and how they are used In-Reply-To: References: Message-ID: <54EDCF8E.1040903@well-typed.com> Hi Jan, Yes, unfortunately the meaning of EvTerm is a weak point of the current typechecker plugins story; it rather requires one to understand how GHC's constraint solver produces evidence. There are lots of papers on evidence for equality constraints in System FC, but typeclass constraints are generally ignored as they are just datatypes at the FC level. Let me try to give you some idea of what EvDFunApp means, then hopefully those with more knowledge of the GHC internals can correct me... If you write a class instance, e.g. instance (Show a, Show b) => Show (T a b) where ... then GHC generates a dfun (short for "dictionary function", I guess) $fShowT :: forall a b . (Show a, Show b) => Show (T a b) where Show is treated as a record data type containing a dictionary of methods for the class. At the core level, this is a normal term-level function (albeit with a strange name). Now when the typechecker has a constraint to solve, say Show (T Int Bool), it produces evidence for this by applying $fShowT to the appropriate types and to evidence for the superclass constraints, in this case something like $fShowT @Int @Bool $fShowInt $fShowBool where I'm using @ for type application. This is represented in EvTerm as EvDFunApp $fShowT [Int, Bool] [ EvDFunApp $fShowInt [] [] , EvDFunApp $fShowBool [] [] ] Thus the [Type] is the list of kinds/types at which to instantiate the dfun, and the [EvTerm] is the list of evidence terms to which it must be applied. Obviously this application should be well-typed, and -dcore-lint will complain if it is not. For typechecker plugins, it would be nice if we could write arbitrary core expressions as evidence, but this hasn't yet been implemented (partially because most of the examples so far solve equality constraints, rather than typeclass constraints). Hope this helps, Adam On 25/02/15 10:55, Jan Bracker wrote: > Hello, > > I am trying to use the new type checker plugins [1] that are implemented > in head. > > When successful a plugin has to return a [(EvTerm, Ct)] for the solved > constraints. The documentation on EvTerms is scarce [2,3,4] and I could > not find papers that explain them (many talk about 'evidence', but they > never get concrete). > > So far I have figured out that "EvDFunApp DFunId [Type] [EvTerm]" > selects a certain instance to be used for a constraint, though I don't > know what the list of EvTerms in the end is for. I am also a bit unclear > on how the "[Type]" is used.If I turn on '-dcore-lint' I get errors. So > I still seem to be using it wrong. > > I have also asked in IRC, but did not get a response to my question. > > I am sorry if this is the wrong mailing list to ask. If there is a more > apropriate place just point it out. > > Best, > Jan > > [1]: https://ghc.haskell.org/trac/ghc/wiki/Plugins/TypeChecker > [2]: http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/libraries/ghc-7.11.20150225/TcEvidence.html#t:EvTerm > [3]: http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/libraries/ghc-7.11.20150225/src/TcEvidence.html#EvTerm > [4]: http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/users_guide/compiler-plugins.html -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From ben at smart-cactus.org Wed Feb 25 17:00:49 2015 From: ben at smart-cactus.org (Ben Gamari) Date: Wed, 25 Feb 2015 12:00:49 -0500 Subject: Broken `cabal haddock --hoogle` with GHC 7.10 In-Reply-To: References: Message-ID: <87385ukjsu.fsf@gmail.com> Michael Snoyman writes: > I'm not really able to follow the details of this, but I wanted to raise to > everyone's attention a serious bug with the current GHC 7.10 RC, Cabal > 1.22, and/or Haddock. Currently, running `cabal haddock --hoogle` does not > work. There seem to be two different issues open about it: > > https://github.com/haskell/haddock/issues/361 > https://github.com/haskell/cabal/issues/2297 > > I really don't understand the issues here, but I'd claim that the severity > of this should probably be a blocker for a GHC 7.10 release. There may be more to this issue that I am seeing at the moment but I believe I have a fix here [1]. There's also a patch improving the error handling in Haddock here [2]. Cheers, - Ben [1] https://github.com/haskell/cabal/pull/2439 [2] https://github.com/haskell/haddock/pull/369 -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From ben at smart-cactus.org Wed Feb 25 17:19:21 2015 From: ben at smart-cactus.org (Ben Gamari) Date: Wed, 25 Feb 2015 12:19:21 -0500 Subject: Broken `cabal haddock --hoogle` with GHC 7.10 In-Reply-To: <87385ukjsu.fsf@gmail.com> References: <87385ukjsu.fsf@gmail.com> Message-ID: <87zj81kixy.fsf@gmail.com> Ben Gamari writes: > Michael Snoyman writes: > >> I'm not really able to follow the details of this, but I wanted to raise to >> everyone's attention a serious bug with the current GHC 7.10 RC, Cabal >> 1.22, and/or Haddock. Currently, running `cabal haddock --hoogle` does not >> work. There seem to be two different issues open about it: >> >> https://github.com/haskell/haddock/issues/361 >> https://github.com/haskell/cabal/issues/2297 >> >> I really don't understand the issues here, but I'd claim that the severity >> of this should probably be a blocker for a GHC 7.10 release. > > There may be more to this issue that I am seeing at the moment but I > believe I have a fix here [1]. There's also a patch improving the error > handling in Haddock here [2]. > s/that I am seeing/than I am seeing/ That's what I get for trying to tap out a message before the bus leaves Wifi range. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From carter.schonwald at gmail.com Wed Feb 25 17:22:33 2015 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 25 Feb 2015 12:22:33 -0500 Subject: [Haskell-cafe] PowerPC variants (GHC 7.8.3) In-Reply-To: <95d7f378e2a3c0bb237f2f14f4f86b95.squirrel@mail.jschneider.net> References: <95d7f378e2a3c0bb237f2f14f4f86b95.squirrel@mail.jschneider.net> Message-ID: Hey Jon, I do know that some of the GHC dev team is probably best equipped to answer your question, i'm cc'ing the ghc dev and users lists so they can jump in and help! -Carter On Wed, Feb 25, 2015 at 7:11 AM, Jon Schneider wrote: > Good morning, > > We have a product with an MPC8544E we might want to target. Also known as > PowerQUICC and e500v2. The ABI is gnuspe rather than gnueabi. > > I have built a powerpc---ghc cross compiler but the thing stopping "hello > world" is a SIGILL happening in StgCRun.c where the stfd and lfd > instructions are used to stash registers. The e500 has different > instructions but that cannot be dropped in trivially because of offset > encoding Commenting these out fixes "hello world" though this surely only > scratches the surface of what would need doing. > > I notice that whereas ARMv5, v6 and v7 appear to be catered for along with > various knobs and whistles there appears to be no such thing for PowerPC. > > Is anybody else out there working on this area ? > > Jon > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Feb 25 17:40:04 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 25 Feb 2015 17:40:04 +0000 Subject: Out of action Message-ID: <618BE556AADD624C9C918AA5D5911BEF7BEB6A1F@DB3PRD3001MB020.064d.mgd.msft.net> Folks Just to say that I'm very silent right now because of the ICFP deadline on Friday. Probably no cycles for GHC until Monday at earliest. Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Thu Feb 26 02:53:40 2015 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Thu, 26 Feb 2015 02:53:40 +0000 Subject: Broken `cabal haddock --hoogle` with GHC 7.10 In-Reply-To: References: <54ED61DC.4030400@fuuzetsu.co.uk> Message-ID: <54EE8AB4.9000000@fuuzetsu.co.uk> On 02/25/2015 10:57 AM, Neil Mitchell wrote: > When you say "change is on the 7.10 branch", you mean a fix for > Haddock, or changes to Cabal? To Haddock. > There are also other issues with the --hoogle output, the newest > regression being that constructors are wrapped in square brackets, for > example: > > [Nothing] :: Maybe a > > Generally, the --hoogle output from Haddock keeps going downhill. When > I first implemented it, there was a test suite, but that seems to no > longer be catching issues. I'm aware and really want to fix these issues (Hoogle is great!) but as always what little manpower becomes available tends to go into showstopper bugs instead as apparent by the sad commit list in Haddock? I think I will try to jump into Hoogle problems at start of March and just ignore other stuff. As always, my apologies. > Thanks, Neil > > > On Wed, Feb 25, 2015 at 5:47 AM, Mateusz Kowalczyk > wrote: >> On 02/25/2015 05:41 AM, Michael Snoyman wrote: >>> I'm not really able to follow the details of this, but I wanted to raise to >>> everyone's attention a serious bug with the current GHC 7.10 RC, Cabal >>> 1.22, and/or Haddock. Currently, running `cabal haddock --hoogle` does not >>> work. There seem to be two different issues open about it: >>> >>> https://github.com/haskell/haddock/issues/361 >>> https://github.com/haskell/cabal/issues/2297 >>> >>> I really don't understand the issues here, but I'd claim that the severity >>> of this should probably be a blocker for a GHC 7.10 release. >>> >>> >> >> I think only work needs to go into cabal now. GHCs point of concern here >> is that it ships with a patched cabal for this when the patch does get >> crafted rather than only dumped onto the master branch. It's already >> fixed on Haddock side and I believe the change is on 7.10 branch. >> >> So I guess this is just a FYI that something is broken and we're >> awaiting cabal patch. >> >> >> -- >> Mateusz K. >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -- Mateusz K. From jan.bracker at googlemail.com Thu Feb 26 10:07:12 2015 From: jan.bracker at googlemail.com (Jan Bracker) Date: Thu, 26 Feb 2015 10:07:12 +0000 Subject: Fwd: EvTerms and how they are used In-Reply-To: References: <54EDCF8E.1040903@well-typed.com> Message-ID: Hi Adam, thank you for your quick and detailed answer! I think I understand how to construct evidence for typeclass constraints now. But trying to apply this, I still have some problems. I have something along the following lines: class Polymonad m n p where -- Functions instance Polymonad Identity Identity Identity where -- Implementation -- Further instances and some small chunk of code involving them: The code implies the following constraint: Polymonad Identity n_abpq Identity As the ambiguity error I get says, when trying to compile this: There is only one matching instance (the one above, lets call it $fPolymonadIdentityIdentityIdentity). So my plugin tries to tell GHC to use that instance. As far as I understand it, since the parameters of $fPolymonadIdentityIdentityIdentity are no type variables and there is no superclass it should be as easy as saying: EvDFunApp $fPolymonadIdentityIdentityIdentity [] [] But when I run this with -dcore-lint I get the following error message: *** Core Lint errors : in result of Desugar (after optimization) *** : Warning: In the expression: >> @ Identity @ Any @ Identity $fPolymonadIdentityIdentityIdentity @ () @ () (idOp @ Bool True) (>>= @ Identity @ Identity @ Any $fPolymonadIdentityIdentityIdentity @ Char @ () (return @ Char @ Identity $fPolymonadIdentityIdentityIdentity (C# 'a')) (\ _ [Occ=Dead] -> return @ () @ Identity $fPolymonadIdentityIdentityIdentity ())) Argument value doesn't match argument type: Fun type: Polymonad Identity Any Identity => forall a_abdV[sk] b_abdW[sk]. Identity a_abdV[sk] -> Any b_abdW[sk] -> Identity b_abdW[sk] Arg type: Polymonad Identity Identity Identity Arg: $fPolymonadIdentityIdentityIdentity What am I missing? Why doesn't the argument type "Polymonad Identity Identity Identity" match the first argument of the function type "Polymonad Identity Any Identity => forall a_abdV[sk] b_abdW[sk]. Identity a_abdV[sk] -> Any b_abdW[sk] -> Identity b_abdW[sk]". Why is the type variable translated to "Any"? Best, Jan 2015-02-25 13:35 GMT+00:00 Adam Gundry : > Hi Jan, > > Yes, unfortunately the meaning of EvTerm is a weak point of the current > typechecker plugins story; it rather requires one to understand how > GHC's constraint solver produces evidence. There are lots of papers on > evidence for equality constraints in System FC, but typeclass > constraints are generally ignored as they are just datatypes at the FC > level. > > Let me try to give you some idea of what EvDFunApp means, then hopefully > those with more knowledge of the GHC internals can correct me... > > If you write a class instance, e.g. > > instance (Show a, Show b) => Show (T a b) where ... > > then GHC generates a dfun (short for "dictionary function", I guess) > > $fShowT :: forall a b . (Show a, Show b) => Show (T a b) > > where Show is treated as a record data type containing a dictionary of > methods for the class. At the core level, this is a normal term-level > function (albeit with a strange name). > > Now when the typechecker has a constraint to solve, say > > Show (T Int Bool), > > it produces evidence for this by applying $fShowT to the appropriate > types and to evidence for the superclass constraints, in this case > something like > > $fShowT @Int @Bool $fShowInt $fShowBool > > where I'm using @ for type application. This is represented in EvTerm as > > EvDFunApp $fShowT [Int, Bool] [ EvDFunApp $fShowInt [] [] > , EvDFunApp $fShowBool [] [] ] > > Thus the [Type] is the list of kinds/types at which to instantiate the > dfun, and the [EvTerm] is the list of evidence terms to which it must be > applied. Obviously this application should be well-typed, and > -dcore-lint will complain if it is not. > > For typechecker plugins, it would be nice if we could write arbitrary > core expressions as evidence, but this hasn't yet been implemented > (partially because most of the examples so far solve equality > constraints, rather than typeclass constraints). > > Hope this helps, > > Adam > > > On 25/02/15 10:55, Jan Bracker wrote: > > Hello, > > > > I am trying to use the new type checker plugins [1] that are implemented > > in head. > > > > When successful a plugin has to return a [(EvTerm, Ct)] for the solved > > constraints. The documentation on EvTerms is scarce [2,3,4] and I could > > not find papers that explain them (many talk about 'evidence', but they > > never get concrete). > > > > So far I have figured out that "EvDFunApp DFunId [Type] [EvTerm]" > > selects a certain instance to be used for a constraint, though I don't > > know what the list of EvTerms in the end is for. I am also a bit unclear > > on how the "[Type]" is used.If I turn on '-dcore-lint' I get errors. So > > I still seem to be using it wrong. > > > > I have also asked in IRC, but did not get a response to my question. > > > > I am sorry if this is the wrong mailing list to ask. If there is a more > > apropriate place just point it out. > > > > Best, > > Jan > > > > [1]: https://ghc.haskell.org/trac/ghc/wiki/Plugins/TypeChecker > > [2]: > http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/libraries/ghc-7.11.20150225/TcEvidence.html#t:EvTerm > > [3]: > http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/libraries/ghc-7.11.20150225/src/TcEvidence.html#EvTerm > > [4]: > http://haskell.inf.elte.hu/docs/7.11.20150225.noWin32/html/users_guide/compiler-plugins.html > > > -- > Adam Gundry, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ > -------------- next part -------------- An HTML attachment was scrubbed... URL: From kazu at iij.ad.jp Thu Feb 26 12:36:49 2015 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Thu, 26 Feb 2015 21:36:49 +0900 (JST) Subject: GHC with cabal-install Message-ID: <20150226.213649.1947408911926430723.kazu@iij.ad.jp> Hello, To my experience, it is easy to install GHC to Linux such as CentOS. But it is hard to install cabal-install after that. Are there any reasons to not include cabal-install in GHC binary packages? GHC provides Cabal library. Why not cabal-install? --Kazu From jackhill at jackhill.us Thu Feb 26 12:54:04 2015 From: jackhill at jackhill.us (Jack Hill) Date: Thu, 26 Feb 2015 07:54:04 -0500 (EST) Subject: GHC with cabal-install In-Reply-To: <20150226.213649.1947408911926430723.kazu@iij.ad.jp> References: <20150226.213649.1947408911926430723.kazu@iij.ad.jp> Message-ID: On Thu, 26 Feb 2015, Kazu Yamamoto (????) wrote: > Hello, > > To my experience, it is easy to install GHC to Linux such as > CentOS. But it is hard to install cabal-install after that. > > Are there any reasons to not include cabal-install in GHC binary > packages? > > GHC provides Cabal library. Why not cabal-install? > > --Kazu Kazu, I can't provide any guidance on what GHC might do, but I can from what other distributions have done. On both my Debian and Gentoo systems, there is a cabal-install package that is as easy to install as ghc. Perhaps CentOS could provide a similar package. I see that Fedora has a cabal-install package as well. Perhaps that could be added to epel or you could build it yourself for CentOS. Best, Jack From simonpj at microsoft.com Thu Feb 26 17:06:47 2015 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 26 Feb 2015 17:06:47 +0000 Subject: The suggested redundant import solution doesn't work for explicit import lists In-Reply-To: <87oaojjz9a.fsf@gmail.com> References: <87wq37k0oo.fsf@gmail.com> <618BE556AADD624C9C918AA5D5911BEF7BEB40D7@DB3PRD3001MB020.064d.mgd.msft.net> <87oaojjz9a.fsf@gmail.com> Message-ID: <618BE556AADD624C9C918AA5D5911BEF7BEB859F@DB3PRD3001MB020.064d.mgd.msft.net> OK. I've created a ticket https://ghc.haskell.org/trac/ghc/ticket/10117 In fact there is a pretty good specification here https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/UnusedImports So back to you: based on the existing, can you think of a variant that would work better? Simon | -----Original Message----- | From: Herbert Valerio Riedel [mailto:hvriedel at gmail.com] | Sent: 24 February 2015 12:00 | To: Simon Peyton Jones | Cc: Herbert Valerio Riedel; Johan Tibell; Edward Kmett; Austin Seipp | Subject: Re: The suggested redundant import solution doesn't work for | explicit import lists | | Simon, | | The problem: | | trying to avoid redundant-import warnings due symbols having moved to | 'Prelude' due to AMP/FTP w/o CPP usage | | e.g. | | import Control.Applicative (Applicative) | | foo :: Applicative f => ... | foo = ... | | now warns that 'Applicative' is redundant, as it's exported from | 'Prelude' now. 'Monoid' is another such example that's now re-exported | from 'Prelude' (but wasn't before GHC 7.10). | | | One thing that happens to work is the trick shown at | https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#GHCsaysTheimporto | f...isredundant | i.e. | | module Foo (Int, Word, Monoid(..)) where | | import Data.Monoid | import Data.Word | import Prelude | | as in that case, 'Prelude' is explicitly imported last, and so GHC | doesn't warn about Data.{Word,Monoid} being redundant (due to the way | the redundancy-check is implemented in GHC) | | However, if the example above is rewritten as | | module Foo (Int, Word, Monoid(..)) where | | import Data.Monoid (Monoid(..)) | import Data.Word (Word) | import Prelude | | GHC would warn, as it handles import-listed symbols differently than | wildcard imports... | | and the question is, whether we can easily get the latter example to | become warning free as well w/o risking breakages elsewhere... | | ...is it clearer now what I'm suggesting? | | Cheers, | hvr | | On 2015-02-24 at 12:50:35 +0100, Simon Peyton Jones wrote: | > I'm sorry, but can someone re-articulate the question? I'm deep | underwater, so reluctant to reverse-engineer the question from the | thread. | > I think you are asking for some feature. But I'm not sure what the | spec is. | > | > Simon | > | > | -----Original Message----- | > | From: Herbert Valerio Riedel [mailto:hvriedel at gmail.com] | > | Sent: 24 February 2015 11:29 | > | To: Johan Tibell | > | Cc: Edward Kmett; Simon Peyton Jones; Austin Seipp | > | Subject: Re: The suggested redundant import solution doesn't work | > | for explicit import lists | > | | > | Johan, | > | | > | You're right, I'm afraid the Prelude-trick doesn't work well with | > | import-lists... not sure though if it's worth the risk to tweak | GHC | > | 7.10.1's redundant-warning detection to make it work here too... | > | | > | @SPJ, any comments? | > | | > | for more context: | > | | > | - | > | | https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#GHCsaysTheimporto | f.. | > | .isredundant | > | - | > | | http://www.reddit.com/r/haskell/comments/2wx64g/ghc_710_will_use_pla | > | n_ftp | > | /covdas0 | > | | > | Cheers, | > | hvr | > | | > | On 2015-02-24 at 11:47:30 +0100, Johan Tibell wrote: | > | > The suggested fix for unused imports resulting from the move of | e.g. | > | > Data.Monoid doesn't work when using explicit import lists: | > | > | > | > $ cat Test.hs | > | > module Test where | > | > | > | > import Data.Monoid (Monoid) | > | > import Prelude | > | > | > | > f :: Monoid a => a | > | > f = undefined | > | > $ ghc-7.10.0.20150123 -Wall /tmp/Test.hs | > | > [1 of 1] Compiling Test ( /tmp/Test.hs, /tmp/Test.o | ) | > | > | > | > /tmp/Test.hs:3:1: Warning: | > | > The import of ?Data.Monoid? is redundant | > | > except perhaps to import instances from ?Data.Monoid? | > | > To import instances alone, use: import Data.Monoid() | > | > | > | > It does work if you don't have an import list (bad idea) or use | > | qualified | > | > imports (good idea). | > | > | > | > -- Johan | > | | > | -- | > | "Elegance is not optional" -- Richard O'Keefe | | -- | "Elegance is not optional" -- Richard O'Keefe From johan.tibell at gmail.com Thu Feb 26 20:21:30 2015 From: johan.tibell at gmail.com (Johan Tibell) Date: Thu, 26 Feb 2015 21:21:30 +0100 Subject: The suggested redundant import solution doesn't work for explicit import lists In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF7BEB859F@DB3PRD3001MB020.064d.mgd.msft.net> References: <87wq37k0oo.fsf@gmail.com> <618BE556AADD624C9C918AA5D5911BEF7BEB40D7@DB3PRD3001MB020.064d.mgd.msft.net> <87oaojjz9a.fsf@gmail.com> <618BE556AADD624C9C918AA5D5911BEF7BEB859F@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: I guess for re-exports we could relax the requirement that the symbol comes from only one module. I don't know if that is better though. If I saw import Data.Monoid (Monoid) import Prelude (Monoid) I'd say that code wasn't the pretties, because it would confuse users, who would have to figure out that the two were the same. Re-exports are generally confusing, because they break abstraction by saying that two things are the same and will continue to be so, which isn't always what you want. On Thu, Feb 26, 2015 at 6:06 PM, Simon Peyton Jones wrote: > OK. I've created a ticket > https://ghc.haskell.org/trac/ghc/ticket/10117 > > In fact there is a pretty good specification here > https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/UnusedImports > > So back to you: based on the existing, can you think of a variant that > would work better? > > Simon > > | -----Original Message----- > | From: Herbert Valerio Riedel [mailto:hvriedel at gmail.com] > | Sent: 24 February 2015 12:00 > | To: Simon Peyton Jones > | Cc: Herbert Valerio Riedel; Johan Tibell; Edward Kmett; Austin Seipp > | Subject: Re: The suggested redundant import solution doesn't work for > | explicit import lists > | > | Simon, > | > | The problem: > | > | trying to avoid redundant-import warnings due symbols having moved to > | 'Prelude' due to AMP/FTP w/o CPP usage > | > | e.g. > | > | import Control.Applicative (Applicative) > | > | foo :: Applicative f => ... > | foo = ... > | > | now warns that 'Applicative' is redundant, as it's exported from > | 'Prelude' now. 'Monoid' is another such example that's now re-exported > | from 'Prelude' (but wasn't before GHC 7.10). > | > | > | One thing that happens to work is the trick shown at > | https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#GHCsaysTheimporto > | f...isredundant > | i.e. > | > | module Foo (Int, Word, Monoid(..)) where > | > | import Data.Monoid > | import Data.Word > | import Prelude > | > | as in that case, 'Prelude' is explicitly imported last, and so GHC > | doesn't warn about Data.{Word,Monoid} being redundant (due to the way > | the redundancy-check is implemented in GHC) > | > | However, if the example above is rewritten as > | > | module Foo (Int, Word, Monoid(..)) where > | > | import Data.Monoid (Monoid(..)) > | import Data.Word (Word) > | import Prelude > | > | GHC would warn, as it handles import-listed symbols differently than > | wildcard imports... > | > | and the question is, whether we can easily get the latter example to > | become warning free as well w/o risking breakages elsewhere... > | > | ...is it clearer now what I'm suggesting? > | > | Cheers, > | hvr > | > | On 2015-02-24 at 12:50:35 +0100, Simon Peyton Jones wrote: > | > I'm sorry, but can someone re-articulate the question? I'm deep > | underwater, so reluctant to reverse-engineer the question from the > | thread. > | > I think you are asking for some feature. But I'm not sure what the > | spec is. > | > > | > Simon > | > > | > | -----Original Message----- > | > | From: Herbert Valerio Riedel [mailto:hvriedel at gmail.com] > | > | Sent: 24 February 2015 11:29 > | > | To: Johan Tibell > | > | Cc: Edward Kmett; Simon Peyton Jones; Austin Seipp > | > | Subject: Re: The suggested redundant import solution doesn't work > | > | for explicit import lists > | > | > | > | Johan, > | > | > | > | You're right, I'm afraid the Prelude-trick doesn't work well with > | > | import-lists... not sure though if it's worth the risk to tweak > | GHC > | > | 7.10.1's redundant-warning detection to make it work here too... > | > | > | > | @SPJ, any comments? > | > | > | > | for more context: > | > | > | > | - > | > | > | https://ghc.haskell.org/trac/ghc/wiki/Migration/7.10#GHCsaysTheimporto > | f.. > | > | .isredundant > | > | - > | > | > | http://www.reddit.com/r/haskell/comments/2wx64g/ghc_710_will_use_pla > | > | n_ftp > | > | /covdas0 > | > | > | > | Cheers, > | > | hvr > | > | > | > | On 2015-02-24 at 11:47:30 +0100, Johan Tibell wrote: > | > | > The suggested fix for unused imports resulting from the move of > | e.g. > | > | > Data.Monoid doesn't work when using explicit import lists: > | > | > > | > | > $ cat Test.hs > | > | > module Test where > | > | > > | > | > import Data.Monoid (Monoid) > | > | > import Prelude > | > | > > | > | > f :: Monoid a => a > | > | > f = undefined > | > | > $ ghc-7.10.0.20150123 -Wall /tmp/Test.hs > | > | > [1 of 1] Compiling Test ( /tmp/Test.hs, /tmp/Test.o > | ) > | > | > > | > | > /tmp/Test.hs:3:1: Warning: > | > | > The import of ?Data.Monoid? is redundant > | > | > except perhaps to import instances from ?Data.Monoid? > | > | > To import instances alone, use: import Data.Monoid() > | > | > > | > | > It does work if you don't have an import list (bad idea) or use > | > | qualified > | > | > imports (good idea). > | > | > > | > | > -- Johan > | > | > | > | -- > | > | "Elegance is not optional" -- Richard O'Keefe > | > | -- > | "Elegance is not optional" -- Richard O'Keefe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From kazu at iij.ad.jp Fri Feb 27 00:41:40 2015 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Fri, 27 Feb 2015 09:41:40 +0900 (JST) Subject: GHC with cabal-install In-Reply-To: References: <20150226.213649.1947408911926430723.kazu@iij.ad.jp> Message-ID: <20150227.094140.1830825633048954300.kazu@iij.ad.jp> Hi Jack, > I can't provide any guidance on what GHC might do, but I can from what > other distributions have done. On both my Debian and Gentoo systems, > there is a cabal-install package that is as easy to install as > ghc. Perhaps CentOS could provide a similar package. I see that Fedora > has a cabal-install package as well. Perhaps that could be added to > epel or you could build it yourself for CentOS. In my CentOS 7: % yum search cabal No matches found % yum provides cabal No matches found Anyway, I would like to know reasons why the GHC binary package does not provide the cabal command. --Kazu From jackhill at jackhill.us Fri Feb 27 01:29:25 2015 From: jackhill at jackhill.us (Jack Hill) Date: Thu, 26 Feb 2015 20:29:25 -0500 (EST) Subject: GHC with cabal-install In-Reply-To: <20150227.094140.1830825633048954300.kazu@iij.ad.jp> References: <20150226.213649.1947408911926430723.kazu@iij.ad.jp> <20150227.094140.1830825633048954300.kazu@iij.ad.jp> Message-ID: On Fri, 27 Feb 2015, Kazu Yamamoto (????) wrote: > Hi Jack, > >> I can't provide any guidance on what GHC might do, but I can from what >> other distributions have done. On both my Debian and Gentoo systems, >> there is a cabal-install package that is as easy to install as >> ghc. Perhaps CentOS could provide a similar package. I see that Fedora >> has a cabal-install package as well. Perhaps that could be added to >> epel or you could build it yourself for CentOS. > > In my CentOS 7: > > % yum search cabal > No matches found > % yum provides cabal > No matches found > > Anyway, I would like to know reasons why the GHC binary package does > not provide the cabal command. Ah, yes, I have no idea. This may help people get off the ground quicker. Would the Haskell Platform get you what you need? https://www.haskell.org/platform/linux.html You also may be interested in checking out EPEL (Fedora packages built for the Enterprise Linux family), which is where I got my Haskell (an other missing packages) from. https://fedoraproject.org/wiki/EPEL It is too bad that the Haskell Platform wasn't popular enough to make it into the base OS. Best, Jack From allbery.b at gmail.com Fri Feb 27 01:47:10 2015 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 26 Feb 2015 20:47:10 -0500 Subject: GHC with cabal-install In-Reply-To: <20150227.094140.1830825633048954300.kazu@iij.ad.jp> References: <20150226.213649.1947408911926430723.kazu@iij.ad.jp> <20150227.094140.1830825633048954300.kazu@iij.ad.jp> Message-ID: On Thu, Feb 26, 2015 at 7:41 PM, Kazu Yamamoto wrote: > Anyway, I would like to know reasons why the GHC binary package does > not provide the cabal command. > Too many additional dependencies. Note that https://www.haskell.org/cabal/download.html *does* provide binary packages, specifically to address this. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From kazu at iij.ad.jp Fri Feb 27 02:38:51 2015 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Fri, 27 Feb 2015 11:38:51 +0900 (JST) Subject: GHC with cabal-install In-Reply-To: References: <20150227.094140.1830825633048954300.kazu@iij.ad.jp> Message-ID: <20150227.113851.756999491348524354.kazu@iij.ad.jp> Hi Brandon, > Too many additional dependencies. OK. > Note that > https://www.haskell.org/cabal/download.html *does* provide binary packages, > specifically to address this. Oh. I did not know this page. Excellent. Thanks! --Kazu From adam at well-typed.com Fri Feb 27 15:48:47 2015 From: adam at well-typed.com (Adam Gundry) Date: Fri, 27 Feb 2015 15:48:47 +0000 Subject: Fwd: EvTerms and how they are used In-Reply-To: References: <54EDCF8E.1040903@well-typed.com> Message-ID: <54F091DF.1090907@well-typed.com> Hi Jan, It's a bit hard to know exactly what is going on without the full code, but I think what is happening is this: you have an unsolved constraint `Polymonad Identity n_abpq Identity` and your plugin provides an evidence term of type `Polymonad Identity Identity Identity`, but of course this is ill-typed, because `n_abpq` is not `Identity`. Hence Core Lint quite reasonably complains. The `Any` type is used by GHC to instantiate type variables whose values are irrelevant, because they do not occur in the type. The classic example is `null []`, where the type of the list is unimportant: rather than having an unsolved unification variable, GHC solves it with `Any`. I'm not sure exactly what you are trying to do, but I think the right way to approach this problem is to simulate a functional dependency on Polymonad (in fact, can you use an actual functional dependency)? When confronted with the constraint `Polymonad Identity n_abpq Identity`, do not try to solve it directly, but instead notice that you must have `n_abpq ~ Identity`. Your plugin can emit this as an additional derived constraint, which will allow GHC's built-in solver to instantiate the unification variable `n_abpq` and then solve the original constraint using the existing instance. No manual evidence generation needed! Emitting this extra derived constraint is essentially what happens if you specify the functional dependency class Polymonad m n p | m p -> n where but the plugin approach allows more fine-grained control over exactly when this applies. Out of interest, can you say anything about your aims here? I'm keen to find out about the range of applications of typechecker plugins. All the best, Adam On 26/02/15 10:07, Jan Bracker wrote: > Hi Adam, > > thank you for your quick and detailed answer! I think I understand how > to construct evidence for typeclass constraints now. But trying to apply > this, I still have some problems. > > I have something along the following lines: > > class Polymonad m n p where > -- Functions > > instance Polymonad Identity Identity Identity where > -- Implementation > > -- Further instances and some small chunk of code involving them: > > The code implies the following constraint: > Polymonad Identity n_abpq Identity > > As the ambiguity error I get says, when trying to compile this: There is > only one matching instance (the one above, lets call > it $fPolymonadIdentityIdentityIdentity). > > So my plugin tries to tell GHC to use that instance. As far as I > understand it, since the parameters > of $fPolymonadIdentityIdentityIdentity are no type variables and there > is no superclass it should be as easy as saying: > EvDFunApp $fPolymonadIdentityIdentityIdentity [] [] > > But when I run this with -dcore-lint I get the following error message: > > *** Core Lint errors : in result of Desugar (after optimization) *** > : Warning: > In the expression: >> > @ Identity > @ Any > @ Identity > $fPolymonadIdentityIdentityIdentity > @ () > @ () > (idOp @ Bool True) > (>>= > @ Identity > @ Identity > @ Any > $fPolymonadIdentityIdentityIdentity > @ Char > @ () > (return > @ Char @ Identity > $fPolymonadIdentityIdentityIdentity (C# 'a')) > (\ _ [Occ=Dead] -> > return @ () @ Identity > $fPolymonadIdentityIdentityIdentity ())) > Argument value doesn't match argument type: > Fun type: > Polymonad Identity Any Identity => > forall a_abdV[sk] b_abdW[sk]. > Identity a_abdV[sk] -> Any b_abdW[sk] -> Identity b_abdW[sk] > Arg type: Polymonad Identity Identity Identity > Arg: $fPolymonadIdentityIdentityIdentity > > What am I missing? Why doesn't the argument type "Polymonad Identity > Identity Identity" match the first argument of the function type > "Polymonad Identity Any Identity => forall a_abdV[sk] b_abdW[sk]. > Identity a_abdV[sk] -> Any b_abdW[sk] -> Identity b_abdW[sk]". Why is > the type variable translated to "Any"? > > Best, > Jan -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/