From merijn at inconsistent.nl Wed Sep 3 05:59:03 2014 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Tue, 2 Sep 2014 22:59:03 -0700 Subject: GHC not able to detect impossible GADT pattern Message-ID: I?ve been trying to stretch GHC?s type system again and somehow managed to get myself into a position where GHC warns about a non-exhaustive pattern where adding the (according to GHC) missing pattern results in a type error (as intended by me). It seems that even with closed type families GHC can?t infer some patterns can never occur? Complete code to reproduce the issue is including below, the non-exhaustive pattern happens in the local definitions ?f? of push and pull. I?m open to suggestions for other approaches. Kind regards, Merijn {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module Test where import Data.Proxy import GHC.Exts data Message data SocketType = Dealer | Push | Pull data SocketOperation = Read | Write type family Restrict (a :: SocketOperation) (as :: [SocketOperation]) :: Constraint where Restrict a (a ': as) = () Restrict x (a ': as) = Restrict x as Restrict x '[] = ("Error!" ~ "Tried to apply a restricted type!") type family Implements (t :: SocketType) :: [SocketOperation] where Implements Dealer = ['Read, Write] Implements Push = '[Write] Implements Pull = '[ 'Read] data SockOp :: SocketType -> SocketOperation -> * where SRead :: SockOp sock 'Read SWrite :: SockOp sock Write data Socket :: SocketType -> * where Socket :: proxy sock -> (forall op . Restrict op (Implements sock) => SockOp sock op -> Operation op) -> Socket sock type family Operation (op :: SocketOperation) :: * where Operation 'Read = IO Message Operation Write = Message -> IO () class Restrict 'Read (Implements t) => Readable t where readSocket :: Socket t -> Operation 'Read readSocket (Socket _ f) = f (SRead :: SockOp t 'Read) instance Readable Dealer type family Writable (t :: SocketType) :: Constraint where Writable Dealer = () Writable Push = () dealer :: Socket Dealer dealer = Socket (Proxy :: Proxy Dealer) f where f :: Restrict op (Implements Dealer) => SockOp Dealer op -> Operation op f SRead = undefined f SWrite = undefined push :: Socket Push push = Socket (Proxy :: Proxy Push) f where f :: Restrict op (Implements Push) => SockOp Push op -> Operation op f SWrite = undefined pull :: Socket Pull pull = Socket (Proxy :: Proxy Pull) f where f :: Restrict op (Implements Pull) => SockOp Pull op -> Operation op f SRead = undefined foo :: IO Message foo = readSocket dealer -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 801 bytes Desc: Message signed with OpenPGP using GPGMail URL: From simonpj at microsoft.com Wed Sep 3 06:21:34 2014 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 3 Sep 2014 06:21:34 +0000 Subject: GHC not able to detect impossible GADT pattern In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF221F9195@DB3PRD3001MB020.064d.mgd.msft.net> I believe this is probably an instance of https://ghc.haskell.org/trac/ghc/ticket/3927 There are numerous other similar tickets, about GHC's inadequate/misleading warnings for non-exhaustive patterns. A selection is #595, #5728, #3927, #5724, #5762, #4139, #6124, #7669, #322, #8016, #8494, #8853, #8970, #9113. Tom Schrijvers and colleagues are working on this right now, I'm glad to say. Please do add your example to #3927, so that we can be sure to use it as a regression test when testing Tom's shiny new version. Simon | -----Original Message----- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | bounces at haskell.org] On Behalf Of Merijn Verstraaten | Sent: 03 September 2014 06:59 | To: GHC Users List | Subject: GHC not able to detect impossible GADT pattern | | I've been trying to stretch GHC's type system again and somehow managed | to get myself into a position where GHC warns about a non-exhaustive | pattern where adding the (according to GHC) missing pattern results in a | type error (as intended by me). It seems that even with closed type | families GHC can't infer some patterns can never occur? Complete code to | reproduce the issue is including below, the non-exhaustive pattern | happens in the local definitions 'f' of push and pull. | | I'm open to suggestions for other approaches. | | Kind regards, | Merijn | | {-# LANGUAGE ConstraintKinds #-} | {-# LANGUAGE DataKinds #-} | {-# LANGUAGE GADTs #-} | {-# LANGUAGE RankNTypes #-} | {-# LANGUAGE ScopedTypeVariables #-} | {-# LANGUAGE TypeFamilies #-} | {-# LANGUAGE TypeOperators #-} | {-# LANGUAGE UndecidableInstances #-} | module Test where | | import Data.Proxy | import GHC.Exts | | data Message | | data SocketType = Dealer | Push | Pull | | data SocketOperation = Read | Write | | type family Restrict (a :: SocketOperation) (as :: [SocketOperation]) :: | Constraint where | Restrict a (a ': as) = () | Restrict x (a ': as) = Restrict x as | Restrict x '[] = ("Error!" ~ "Tried to apply a restricted type!") | | type family Implements (t :: SocketType) :: [SocketOperation] where | Implements Dealer = ['Read, Write] | Implements Push = '[Write] | Implements Pull = '[ 'Read] | | data SockOp :: SocketType -> SocketOperation -> * where | SRead :: SockOp sock 'Read | SWrite :: SockOp sock Write | | data Socket :: SocketType -> * where | Socket :: proxy sock | -> (forall op . Restrict op (Implements sock) => SockOp sock | op -> Operation op) | -> Socket sock | | type family Operation (op :: SocketOperation) :: * where | Operation 'Read = IO Message | Operation Write = Message -> IO () | | class Restrict 'Read (Implements t) => Readable t where | readSocket :: Socket t -> Operation 'Read | readSocket (Socket _ f) = f (SRead :: SockOp t 'Read) | | instance Readable Dealer | | type family Writable (t :: SocketType) :: Constraint where | Writable Dealer = () | Writable Push = () | | dealer :: Socket Dealer | dealer = Socket (Proxy :: Proxy Dealer) f | where | f :: Restrict op (Implements Dealer) => SockOp Dealer op -> Operation | op | f SRead = undefined | f SWrite = undefined | | push :: Socket Push | push = Socket (Proxy :: Proxy Push) f | where | f :: Restrict op (Implements Push) => SockOp Push op -> Operation op | f SWrite = undefined | | pull :: Socket Pull | pull = Socket (Proxy :: Proxy Pull) f | where | f :: Restrict op (Implements Pull) => SockOp Pull op -> Operation op | f SRead = undefined | | foo :: IO Message | foo = readSocket dealer From merijn at inconsistent.nl Wed Sep 3 08:21:40 2014 From: merijn at inconsistent.nl (Merijn Verstraaten) Date: Wed, 3 Sep 2014 01:21:40 -0700 Subject: GHC not able to detect impossible GADT pattern In-Reply-To: <618BE556AADD624C9C918AA5D5911BEF221F9195@DB3PRD3001MB020.064d.mgd.msft.net> References: <618BE556AADD624C9C918AA5D5911BEF221F9195@DB3PRD3001MB020.064d.mgd.msft.net> Message-ID: <24D07D6D-E383-47A9-95C1-C07ED3782684@inconsistent.nl> Hi Simon, Thanks for the clarification, I attached the code to that ticket. Does this mean improvements in this area are supposed to land in 7.10? Semi-relatedly, before attempting the current code (which at least compiles), I had a few other attempts and I was hoping you (or other readers) might be able to shed some light on this baffling error (full code at the end): Could not deduce (Readable sock) arising from a use of ?f? from the context (Readable sock) bound by the type signature for readSocket :: (Readable sock) => Socket sock -> IO Message at test-old.hs:52:15-70 Relevant bindings include f :: forall (op :: SocketOperation). (Foo op sock) => SockOp sock op -> Operation op (bound at test-old.hs:53:22) readSocket :: Socket sock -> IO Message (bound at test-old.hs:53:1) In the expression: f (SRead :: SockOp sock Read) In an equation for ?readSocket?: readSocket (Socket _ f) = f (SRead :: SockOp sock Read) It seems to me that ?Readable sock? should be trivially deducible from itself? Cheers, Merijn {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module Test where import Data.Proxy import GHC.Exts data Message data SocketType = Dealer | Push | Pull data SocketOperation = Read | Write data SockOp :: SocketType -> SocketOperation -> * where SRead :: Foo 'Read sock => SockOp sock 'Read SWrite :: Foo Write sock => SockOp sock Write data Socket :: SocketType -> * where Socket :: proxy sock -> (forall op . Foo op sock => SockOp sock op -> Operation op) -> Socket sock type family Foo (op :: SocketOperation) :: SocketType -> Constraint where Foo 'Read = Readable Foo Write = Writable type family Operation (op :: SocketOperation) :: * where Operation 'Read = IO Message Operation Write = Message -> IO () type family Readable (t :: SocketType) :: Constraint where Readable Dealer = () Readable Pull = () type family Writable (t :: SocketType) :: Constraint where Writable Dealer = () Writable Push = () dealer :: Socket Dealer dealer = undefined push :: Socket Push push = undefined pull :: Socket Pull pull = undefined readSocket :: forall sock . Readable sock => Socket sock -> IO Message readSocket (Socket _ f) = f (SRead :: SockOp sock 'Read) On 02 Sep 2014, at 23:21 , Simon Peyton Jones wrote: > I believe this is probably an instance of > https://ghc.haskell.org/trac/ghc/ticket/3927 > > There are numerous other similar tickets, about GHC's inadequate/misleading warnings for non-exhaustive patterns. A selection is > #595, #5728, #3927, #5724, #5762, #4139, #6124, #7669, #322, #8016, #8494, #8853, #8970, #9113. > > Tom Schrijvers and colleagues are working on this right now, I'm glad to say. > > Please do add your example to #3927, so that we can be sure to use it as a regression test when testing Tom's shiny new version. > > Simon > > | -----Original Message----- > | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- > | bounces at haskell.org] On Behalf Of Merijn Verstraaten > | Sent: 03 September 2014 06:59 > | To: GHC Users List > | Subject: GHC not able to detect impossible GADT pattern > | > | I've been trying to stretch GHC's type system again and somehow managed > | to get myself into a position where GHC warns about a non-exhaustive > | pattern where adding the (according to GHC) missing pattern results in a > | type error (as intended by me). It seems that even with closed type > | families GHC can't infer some patterns can never occur? Complete code to > | reproduce the issue is including below, the non-exhaustive pattern > | happens in the local definitions 'f' of push and pull. > | > | I'm open to suggestions for other approaches. > | > | Kind regards, > | Merijn > | > | {-# LANGUAGE ConstraintKinds #-} > | {-# LANGUAGE DataKinds #-} > | {-# LANGUAGE GADTs #-} > | {-# LANGUAGE RankNTypes #-} > | {-# LANGUAGE ScopedTypeVariables #-} > | {-# LANGUAGE TypeFamilies #-} > | {-# LANGUAGE TypeOperators #-} > | {-# LANGUAGE UndecidableInstances #-} > | module Test where > | > | import Data.Proxy > | import GHC.Exts > | > | data Message > | > | data SocketType = Dealer | Push | Pull > | > | data SocketOperation = Read | Write > | > | type family Restrict (a :: SocketOperation) (as :: [SocketOperation]) :: > | Constraint where > | Restrict a (a ': as) = () > | Restrict x (a ': as) = Restrict x as > | Restrict x '[] = ("Error!" ~ "Tried to apply a restricted type!") > | > | type family Implements (t :: SocketType) :: [SocketOperation] where > | Implements Dealer = ['Read, Write] > | Implements Push = '[Write] > | Implements Pull = '[ 'Read] > | > | data SockOp :: SocketType -> SocketOperation -> * where > | SRead :: SockOp sock 'Read > | SWrite :: SockOp sock Write > | > | data Socket :: SocketType -> * where > | Socket :: proxy sock > | -> (forall op . Restrict op (Implements sock) => SockOp sock > | op -> Operation op) > | -> Socket sock > | > | type family Operation (op :: SocketOperation) :: * where > | Operation 'Read = IO Message > | Operation Write = Message -> IO () > | > | class Restrict 'Read (Implements t) => Readable t where > | readSocket :: Socket t -> Operation 'Read > | readSocket (Socket _ f) = f (SRead :: SockOp t 'Read) > | > | instance Readable Dealer > | > | type family Writable (t :: SocketType) :: Constraint where > | Writable Dealer = () > | Writable Push = () > | > | dealer :: Socket Dealer > | dealer = Socket (Proxy :: Proxy Dealer) f > | where > | f :: Restrict op (Implements Dealer) => SockOp Dealer op -> Operation > | op > | f SRead = undefined > | f SWrite = undefined > | > | push :: Socket Push > | push = Socket (Proxy :: Proxy Push) f > | where > | f :: Restrict op (Implements Push) => SockOp Push op -> Operation op > | f SWrite = undefined > | > | pull :: Socket Pull > | pull = Socket (Proxy :: Proxy Pull) f > | where > | f :: Restrict op (Implements Pull) => SockOp Pull op -> Operation op > | f SRead = undefined > | > | foo :: IO Message > | foo = readSocket dealer -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 801 bytes Desc: Message signed with OpenPGP using GPGMail URL: From simonpj at microsoft.com Wed Sep 3 12:47:11 2014 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 3 Sep 2014 12:47:11 +0000 Subject: GHC not able to detect impossible GADT pattern In-Reply-To: <24D07D6D-E383-47A9-95C1-C07ED3782684@inconsistent.nl> References: <618BE556AADD624C9C918AA5D5911BEF221F9195@DB3PRD3001MB020.064d.mgd.msft.net> <24D07D6D-E383-47A9-95C1-C07ED3782684@inconsistent.nl> Message-ID: <618BE556AADD624C9C918AA5D5911BEF221F95C2@DB3PRD3001MB020.064d.mgd.msft.net> This is a bug in 7.8.3: https://ghc.haskell.org/trac/ghc/ticket/9433 You should get this error (and do in HEAD): Sock.hs:28:5: Type family 'Readable' should have 1 argument, but has been given none In the equations for closed type family 'Foo' So your program is indeed wrong, but the error message you are getting is entirely bogus. If you fix the above error you should be good to go. Indeed, if you change the defn of Foo thus, it compiles just fine type family Foo (op :: SocketOperation) (s :: SocketType) :: Constraint where Foo 'Read s = Readable s Foo Write s = Writable s Sorry about the egregious bug. Simon | -----Original Message----- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | bounces at haskell.org] On Behalf Of Merijn Verstraaten | Sent: 03 September 2014 09:22 | To: Simon Peyton Jones | Cc: Tom Schrijvers; GHC Users List | Subject: Re: GHC not able to detect impossible GADT pattern | | Hi Simon, | | Thanks for the clarification, I attached the code to that ticket. Does | this mean improvements in this area are supposed to land in 7.10? | | Semi-relatedly, before attempting the current code (which at least | compiles), I had a few other attempts and I was hoping you (or other | readers) might be able to shed some light on this baffling error (full | code at the end): | | Could not deduce (Readable sock) arising from a use of 'f' | from the context (Readable sock) | bound by the type signature for | readSocket :: (Readable sock) => Socket sock -> IO Message | at test-old.hs:52:15-70 | Relevant bindings include | f :: forall (op :: SocketOperation). | (Foo op sock) => | SockOp sock op -> Operation op | (bound at test-old.hs:53:22) | readSocket :: Socket sock -> IO Message (bound at test-old.hs:53:1) | In the expression: f (SRead :: SockOp sock Read) | In an equation for 'readSocket': | readSocket (Socket _ f) = f (SRead :: SockOp sock Read) | | It seems to me that "Readable sock" should be trivially deducible from | itself? | | Cheers, | Merijn | | {-# LANGUAGE ConstraintKinds #-} | {-# LANGUAGE DataKinds #-} | {-# LANGUAGE GADTs #-} | {-# LANGUAGE RankNTypes #-} | {-# LANGUAGE ScopedTypeVariables #-} | {-# LANGUAGE TypeFamilies #-} | module Test where | | import Data.Proxy | import GHC.Exts | | data Message | | data SocketType = Dealer | Push | Pull | | data SocketOperation = Read | Write | | data SockOp :: SocketType -> SocketOperation -> * where | SRead :: Foo 'Read sock => SockOp sock 'Read | SWrite :: Foo Write sock => SockOp sock Write | | data Socket :: SocketType -> * where | Socket :: proxy sock | -> (forall op . Foo op sock => SockOp sock op -> Operation op) | -> Socket sock | | type family Foo (op :: SocketOperation) :: SocketType -> Constraint where | Foo 'Read = Readable | Foo Write = Writable | | type family Operation (op :: SocketOperation) :: * where | Operation 'Read = IO Message | Operation Write = Message -> IO () | | type family Readable (t :: SocketType) :: Constraint where | Readable Dealer = () | Readable Pull = () | | type family Writable (t :: SocketType) :: Constraint where | Writable Dealer = () | Writable Push = () | | dealer :: Socket Dealer | dealer = undefined | | push :: Socket Push | push = undefined | | pull :: Socket Pull | pull = undefined | | readSocket :: forall sock . Readable sock => Socket sock -> IO Message | readSocket (Socket _ f) = f (SRead :: SockOp sock 'Read) | | On 02 Sep 2014, at 23:21 , Simon Peyton Jones | wrote: | > I believe this is probably an instance of | > https://ghc.haskell.org/trac/ghc/ticket/3927 | > | > There are numerous other similar tickets, about GHC's | inadequate/misleading warnings for non-exhaustive patterns. A selection | is | > #595, #5728, #3927, #5724, #5762, #4139, #6124, #7669, #322, #8016, | #8494, #8853, #8970, #9113. | > | > Tom Schrijvers and colleagues are working on this right now, I'm glad | to say. | > | > Please do add your example to #3927, so that we can be sure to use it | as a regression test when testing Tom's shiny new version. | > | > Simon | > | > | -----Original Message----- | > | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | > | bounces at haskell.org] On Behalf Of Merijn Verstraaten | > | Sent: 03 September 2014 06:59 | > | To: GHC Users List | > | Subject: GHC not able to detect impossible GADT pattern | > | | > | I've been trying to stretch GHC's type system again and somehow | managed | > | to get myself into a position where GHC warns about a non-exhaustive | > | pattern where adding the (according to GHC) missing pattern results | in a | > | type error (as intended by me). It seems that even with closed type | > | families GHC can't infer some patterns can never occur? Complete code | to | > | reproduce the issue is including below, the non-exhaustive pattern | > | happens in the local definitions 'f' of push and pull. | > | | > | I'm open to suggestions for other approaches. | > | | > | Kind regards, | > | Merijn | > | | > | {-# LANGUAGE ConstraintKinds #-} | > | {-# LANGUAGE DataKinds #-} | > | {-# LANGUAGE GADTs #-} | > | {-# LANGUAGE RankNTypes #-} | > | {-# LANGUAGE ScopedTypeVariables #-} | > | {-# LANGUAGE TypeFamilies #-} | > | {-# LANGUAGE TypeOperators #-} | > | {-# LANGUAGE UndecidableInstances #-} | > | module Test where | > | | > | import Data.Proxy | > | import GHC.Exts | > | | > | data Message | > | | > | data SocketType = Dealer | Push | Pull | > | | > | data SocketOperation = Read | Write | > | | > | type family Restrict (a :: SocketOperation) (as :: [SocketOperation]) | :: | > | Constraint where | > | Restrict a (a ': as) = () | > | Restrict x (a ': as) = Restrict x as | > | Restrict x '[] = ("Error!" ~ "Tried to apply a restricted type!") | > | | > | type family Implements (t :: SocketType) :: [SocketOperation] where | > | Implements Dealer = ['Read, Write] | > | Implements Push = '[Write] | > | Implements Pull = '[ 'Read] | > | | > | data SockOp :: SocketType -> SocketOperation -> * where | > | SRead :: SockOp sock 'Read | > | SWrite :: SockOp sock Write | > | | > | data Socket :: SocketType -> * where | > | Socket :: proxy sock | > | -> (forall op . Restrict op (Implements sock) => SockOp | sock | > | op -> Operation op) | > | -> Socket sock | > | | > | type family Operation (op :: SocketOperation) :: * where | > | Operation 'Read = IO Message | > | Operation Write = Message -> IO () | > | | > | class Restrict 'Read (Implements t) => Readable t where | > | readSocket :: Socket t -> Operation 'Read | > | readSocket (Socket _ f) = f (SRead :: SockOp t 'Read) | > | | > | instance Readable Dealer | > | | > | type family Writable (t :: SocketType) :: Constraint where | > | Writable Dealer = () | > | Writable Push = () | > | | > | dealer :: Socket Dealer | > | dealer = Socket (Proxy :: Proxy Dealer) f | > | where | > | f :: Restrict op (Implements Dealer) => SockOp Dealer op -> | Operation | > | op | > | f SRead = undefined | > | f SWrite = undefined | > | | > | push :: Socket Push | > | push = Socket (Proxy :: Proxy Push) f | > | where | > | f :: Restrict op (Implements Push) => SockOp Push op -> Operation | op | > | f SWrite = undefined | > | | > | pull :: Socket Pull | > | pull = Socket (Proxy :: Proxy Pull) f | > | where | > | f :: Restrict op (Implements Pull) => SockOp Pull op -> Operation | op | > | f SRead = undefined | > | | > | foo :: IO Message | > | foo = readSocket dealer From johnw at newartisans.com Thu Sep 11 13:57:28 2014 From: johnw at newartisans.com (John Wiegley) Date: Thu, 11 Sep 2014 14:57:28 +0100 Subject: The list fusion lab In-Reply-To: (David Feuer's message of "Thu, 11 Sep 2014 09:46:05 -0400") References: Message-ID: >>>>> David Feuer writes: > Joachim Breitner wrote: >> Together with John Wiegly at ICFP, I started to create a list >> performance laboratory. You can find it at: >> ? ? ? ? https://github.com/nomeata/list-fusion-lab > Many thanks to you both! This sounds like an excellent idea. I do hope > someone figures out a way around the criterion dependency > shortly. It might also be nice to generalize it a bit to allow for analysis of other kinds of performance issues as well. I know that in pipes/conduit world, there's a lot of that happening right now, and a comprehensive comparative analysis there could be quite interesting as well. John From adam at well-typed.com Fri Sep 12 16:41:59 2014 From: adam at well-typed.com (Adam Gundry) Date: Fri, 12 Sep 2014 17:41:59 +0100 Subject: Type checker plugins Message-ID: <54132257.4070803@well-typed.com> Hi folks, Those of you at HIW last week might have been subjected to my lightning talk on plugins for the GHC type checker, which should allow us to properly implement nifty features like units of measure or type-level numbers without recompiling GHC. I've written up a wiki page summarising the idea: https://ghc.haskell.org/trac/ghc/wiki/Plugins/TypeChecker Feedback is very welcome, particularly if (a) you have an interesting use for this feature or (b) you think this is a terrible idea! Thanks, Adam -- Adam Gundry, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From mikolaj at well-typed.com Fri Sep 12 17:12:53 2014 From: mikolaj at well-typed.com (Mikolaj Konarski) Date: Fri, 12 Sep 2014 19:12:53 +0200 Subject: win32 GHC 7.8.3 works under Wine and i386-linux GHC 7.8.3 works under amd64-linux In-Reply-To: References: Message-ID: (cross-com^H^H^Hposting to glasgow-haskell-users at haskell.org) Well, sorf-of. A few extra unobvious parameters and workarounds are required in each case, but it's doable, (arguably) simpler than real cross-compilation and already exhibits problems that real cross-compilation may in some circumstances face. Wiki pages (kudos to all previous authors): http://www.haskell.org/haskellwiki/GHC_under_Wine https://ghc.haskell.org/trac/ghc/wiki/Building/Compiling32on64 Examples of both kinds of binaries, for a project with gtk2hs and TH dependency: https://github.com/LambdaHack/LambdaHack/releases/tag/v0.4.99.0 Please share your success reports here or on the wiki and let's exchange ideas, file concrete tickets and propose patches to make the two processes more accessible. Some tickets are mentioned in the wikis or can be traced from there, but there may be others I'm not aware of, so let's link them where appropriate. Hope this helps somebody, Mikolaj From carter.schonwald at gmail.com Fri Sep 12 18:46:35 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 12 Sep 2014 14:46:35 -0400 Subject: Type checker plugins In-Reply-To: <54132257.4070803@well-typed.com> References: <54132257.4070803@well-typed.com> Message-ID: i'm looking at the record type data TcPlugin = forall t . TcPlugin { init :: TcM t , solve :: t -> [Ct] -> [Ct] -> TcS ([SolveResult], [Ct]) , close :: t -> TcM () } it might be helpful to add a remark that data Ct = ... is defined in compiler/typechecker/TcRnTypes.lhs so folks who aren't already intimately familiar with the constraint solver machinery in GHC can get some wee hints about where to start digging around if they wanted to understand the implications of the proposal :) On Fri, Sep 12, 2014 at 12:41 PM, Adam Gundry wrote: > Hi folks, > > Those of you at HIW last week might have been subjected to my lightning > talk on plugins for the GHC type checker, which should allow us to > properly implement nifty features like units of measure or type-level > numbers without recompiling GHC. I've written up a wiki page summarising > the idea: > > https://ghc.haskell.org/trac/ghc/wiki/Plugins/TypeChecker > > Feedback is very welcome, particularly if (a) you have an interesting > use for this feature or (b) you think this is a terrible idea! > > Thanks, > > Adam > > > -- > Adam Gundry, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ > _______________________________________________ > 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 johnw at newartisans.com Mon Sep 15 12:47:01 2014 From: johnw at newartisans.com (John Wiegley) Date: Mon, 15 Sep 2014 13:47:01 +0100 Subject: Preliminary proposal: Monoidal categories in base and proc notation support In-Reply-To: (Sophie Taylor's message of "Mon, 15 Sep 2014 17:30:35 +1000") References: Message-ID: >>>>> Sophie Taylor writes: > I am working on a proposal for some additions to the base library and some > modifications to GHC in the same style as the do notation support for > Applicatives. It is still very much a work in progress, but any input/ > constructive criticism would be greatly appreciated; this is the first one of > these I've written. Hi Sophie, The work you've proposed has an almost direct overlap with Edward Kmett's recent work in his "hask" library, so I'd prefer to see the dust settle out there to determine what the nicest interface could be. In particular Ed has discovered some nice expressions involving curried bifunctors that would be a shame to miss out on. As Simon said, this really should go to the libraries mailing list, where Edward is sure to weigh in. John From garious at gmail.com Fri Sep 26 03:09:51 2014 From: garious at gmail.com (Greg Fitzgerald) Date: Thu, 25 Sep 2014 20:09:51 -0700 Subject: __GLASGOW_HASKELL__=708? Message-ID: Using GHC 7.8.3 from the latest Haskell Platform on OS X 10.9.4, the __GLASGOW_HASKELL__ preprocessor symbol is being set to 708 instead of 783. I'd guess I have some stale files lying from previous versions GHC or HP, but I can't seem to find them. Any clues? $ cat wtf.hs {-# LANGUAGE CPP #-} $ ghc-7.8.3 -v -E wtf.hs 2>&1 | grep 708 /usr/bin/gcc -E -undef -traditional -Wno-invalid-pp-token -Wno-unicode -Wno-trigraphs -I /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/base-4.7.0.1/include -I /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/integer-gmp-0.5.1.0/include -I /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/include '-D__GLASGOW_HASKELL__=708' '-Ddarwin_BUILD_OS=1' '-Dx86_64_BUILD_ARCH=1' '-Ddarwin_HOST_OS=1' '-Dx86_64_HOST_ARCH=1' -U__PIC__ -D__PIC__ '-D__SSE__=1' '-D__SSE2__=1' -x assembler-with-cpp wtf.hs -o /var/folders/w7/_cxvr2k540163p59kwvqlzrc0000gn/T/ghc14288_0/ghc14288_1.hscpp Thanks, Greg From jwlato at gmail.com Fri Sep 26 03:20:40 2014 From: jwlato at gmail.com (John Lato) Date: Fri, 26 Sep 2014 11:20:40 +0800 Subject: __GLASGOW_HASKELL__=708? In-Reply-To: References: Message-ID: The value 708 is correct. From the user's guide, http://www.haskell.org/ghc/docs/latest/html/users_guide/options-phases.html#c-pre-processor : _GLASGOW_HASKELL__ For version x.y.z of GHC, the value of __GLASGOW_HASKELL__ is the integer xyy (if y is a single digit, then a leading zero is added, so for example in version 6.2 of GHC, __GLASGOW_HASKELL__==602). More information in Section 1.4, ?GHC version numbering policy?. On Fri, Sep 26, 2014 at 11:09 AM, Greg Fitzgerald wrote: > Using GHC 7.8.3 from the latest Haskell Platform on OS X 10.9.4, the > __GLASGOW_HASKELL__ preprocessor symbol is being set to 708 instead of > 783. I'd guess I have some stale files lying from previous versions > GHC or HP, but I can't seem to find them. Any clues? > > > $ cat wtf.hs > > {-# LANGUAGE CPP #-} > > $ ghc-7.8.3 -v -E wtf.hs 2>&1 | grep 708 > > /usr/bin/gcc -E -undef -traditional -Wno-invalid-pp-token -Wno-unicode > -Wno-trigraphs -I > > /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/base-4.7.0.1/include > -I > /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/integer-gmp-0.5.1.0/include > -I > /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/include > '-D__GLASGOW_HASKELL__=708' '-Ddarwin_BUILD_OS=1' > '-Dx86_64_BUILD_ARCH=1' '-Ddarwin_HOST_OS=1' '-Dx86_64_HOST_ARCH=1' > -U__PIC__ -D__PIC__ '-D__SSE__=1' '-D__SSE2__=1' -x assembler-with-cpp > wtf.hs -o > /var/folders/w7/_cxvr2k540163p59kwvqlzrc0000gn/T/ghc14288_0/ghc14288_1.hscpp > > > Thanks, > Greg > _______________________________________________ > 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 garious at gmail.com Fri Sep 26 03:39:33 2014 From: garious at gmail.com (Greg Fitzgerald) Date: Thu, 25 Sep 2014 20:39:33 -0700 Subject: __GLASGOW_HASKELL__=708? In-Reply-To: References: Message-ID: Thanks John. I see that the bug is in how that symbol is being used in the music-score package. Sorry for the noise. -Greg On Thu, Sep 25, 2014 at 8:20 PM, John Lato wrote: > The value 708 is correct. From the user's guide, > http://www.haskell.org/ghc/docs/latest/html/users_guide/options-phases.html#c-pre-processor: > > _GLASGOW_HASKELL__ > For version x.y.z of GHC, the value of __GLASGOW_HASKELL__ is the integer > xyy (if y is a single digit, then a leading zero is added, so for example in > version 6.2 of GHC, __GLASGOW_HASKELL__==602). More information in Section > 1.4, ?GHC version numbering policy?. > > > On Fri, Sep 26, 2014 at 11:09 AM, Greg Fitzgerald wrote: >> >> Using GHC 7.8.3 from the latest Haskell Platform on OS X 10.9.4, the >> __GLASGOW_HASKELL__ preprocessor symbol is being set to 708 instead of >> 783. I'd guess I have some stale files lying from previous versions >> GHC or HP, but I can't seem to find them. Any clues? >> >> >> $ cat wtf.hs >> >> {-# LANGUAGE CPP #-} >> >> $ ghc-7.8.3 -v -E wtf.hs 2>&1 | grep 708 >> >> /usr/bin/gcc -E -undef -traditional -Wno-invalid-pp-token -Wno-unicode >> -Wno-trigraphs -I >> >> /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/base-4.7.0.1/include >> -I >> /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/integer-gmp-0.5.1.0/include >> -I >> /Library/Frameworks/GHC.framework/Versions/7.8.3-x86_64/usr/lib/ghc-7.8.3/include >> '-D__GLASGOW_HASKELL__=708' '-Ddarwin_BUILD_OS=1' >> '-Dx86_64_BUILD_ARCH=1' '-Ddarwin_HOST_OS=1' '-Dx86_64_HOST_ARCH=1' >> -U__PIC__ -D__PIC__ '-D__SSE__=1' '-D__SSE2__=1' -x assembler-with-cpp >> wtf.hs -o >> /var/folders/w7/_cxvr2k540163p59kwvqlzrc0000gn/T/ghc14288_0/ghc14288_1.hscpp >> >> >> Thanks, >> Greg >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > > From johnw at newartisans.com Fri Sep 26 21:06:04 2014 From: johnw at newartisans.com (John Wiegley) Date: Fri, 26 Sep 2014 16:06:04 -0500 Subject: Permitting trailing commas for record syntax ADT declarations In-Reply-To: (Richard Eisenberg's message of "Fri, 26 Sep 2014 15:17:01 -0400") References: <5420168E.5020503@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22228446@DB3PRD3001MB020.064d.mgd.msft.net> <54211D1A.5050400@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22229BC6@DB3PRD3001MB020.064d.mgd.msft.net> <54229F0E.2040009@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF2222F36B@DB3PRD3001MB020.064d.mgd.msft.net> <87d2ak9fvi.fsf@gmail.com> <20140925113416.GA7340@machine> <877g0raopr.fsf@gmail.com> Message-ID: >>>>> Richard Eisenberg writes: > What if we just stopped requiring commas in import/export lists? As far as I > can tell, they're not necessary for proper parsing. +1 John From johan.tibell at gmail.com Fri Sep 26 21:12:42 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Fri, 26 Sep 2014 23:12:42 +0200 Subject: Permitting trailing commas for record syntax ADT declarations In-Reply-To: References: <5420168E.5020503@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22228446@DB3PRD3001MB020.064d.mgd.msft.net> <54211D1A.5050400@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22229BC6@DB3PRD3001MB020.064d.mgd.msft.net> <54229F0E.2040009@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF2222F36B@DB3PRD3001MB020.064d.mgd.msft.net> <87d2ak9fvi.fsf@gmail.com> <20140925113416.GA7340@machine> <877g0raopr.fsf@gmail.com> Message-ID: That would be nice if we had a clean slate, but I don't people are going to change their whole import lists now. Adding a comma at the end is less disruptive. On Fri, Sep 26, 2014 at 11:06 PM, John Wiegley wrote: > >>>>> Richard Eisenberg writes: > > > What if we just stopped requiring commas in import/export lists? As far > as I > > can tell, they're not necessary for proper parsing. > > +1 > > John > _______________________________________________ > 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 allbery.b at gmail.com Fri Sep 26 21:16:56 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 26 Sep 2014 17:16:56 -0400 Subject: Permitting trailing commas for record syntax ADT declarations In-Reply-To: References: <5420168E.5020503@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22228446@DB3PRD3001MB020.064d.mgd.msft.net> <54211D1A.5050400@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22229BC6@DB3PRD3001MB020.064d.mgd.msft.net> <54229F0E.2040009@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF2222F36B@DB3PRD3001MB020.064d.mgd.msft.net> <87d2ak9fvi.fsf@gmail.com> <20140925113416.GA7340@machine> <877g0raopr.fsf@gmail.com> Message-ID: On Fri, Sep 26, 2014 at 5:12 PM, Johan Tibell wrote: > That would be nice if we had a clean slate, but I don't people are going > to change their whole import lists now. I read the proposal as making all commas optional, not as requiring them to not be present. -- 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 Fri Sep 26 21:21:33 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Fri, 26 Sep 2014 23:21:33 +0200 Subject: Permitting trailing commas for record syntax ADT declarations In-Reply-To: References: <5420168E.5020503@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22228446@DB3PRD3001MB020.064d.mgd.msft.net> <54211D1A.5050400@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22229BC6@DB3PRD3001MB020.064d.mgd.msft.net> <54229F0E.2040009@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF2222F36B@DB3PRD3001MB020.064d.mgd.msft.net> <87d2ak9fvi.fsf@gmail.com> <20140925113416.GA7340@machine> <877g0raopr.fsf@gmail.com> Message-ID: I don't think that's necessarily is good style. I don't think we want two different ways of doing import lists. The original proposal was to address a quite small but important engineer issue: without allow *one* trailing comma your version control history gets messed up, because the wrong person gets "blamed" for a line of code. The standard programming language way of solving that problem is to allow a trailing comma. On Fri, Sep 26, 2014 at 11:16 PM, Brandon Allbery wrote: > On Fri, Sep 26, 2014 at 5:12 PM, Johan Tibell > wrote: > >> That would be nice if we had a clean slate, but I don't people are going >> to change their whole import lists now. > > > I read the proposal as making all commas optional, not as requiring them > to not be present. > > -- > 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 allbery.b at gmail.com Fri Sep 26 21:34:16 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 26 Sep 2014 17:34:16 -0400 Subject: Permitting trailing commas for record syntax ADT declarations In-Reply-To: References: <5420168E.5020503@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22228446@DB3PRD3001MB020.064d.mgd.msft.net> <54211D1A.5050400@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22229BC6@DB3PRD3001MB020.064d.mgd.msft.net> <54229F0E.2040009@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF2222F36B@DB3PRD3001MB020.064d.mgd.msft.net> <87d2ak9fvi.fsf@gmail.com> <20140925113416.GA7340@machine> <877g0raopr.fsf@gmail.com> Message-ID: On Fri, Sep 26, 2014 at 5:21 PM, Johan Tibell wrote: > I don't think that's necessarily is good style. I don't think we want two > different ways of doing import lists. Yes; I kinda hate the idea myself, it encourages an unreadable programming style. But it's not the wholesale breaking change you were suggesting, either. -- 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 hvr at gnu.org Mon Sep 29 08:19:04 2014 From: hvr at gnu.org (Herbert Valerio Riedel) Date: Mon, 29 Sep 2014 10:19:04 +0200 Subject: Aliasing current module qualifier Message-ID: <8761g66dqf.fsf@gnu.org> Hello *, Here's a situation I've encountered recently, which mades me wish to be able to define a local alias (in order to avoid CPP use). Consider the following stupid module: module AnnoyinglyLongModuleName ( AnnoyinglyLongModuleName.length , AnnoyinglyLongModuleName.null ) where length :: a -> Int length _ = 0 null :: a -> Bool null = (== 0) . AnnoyinglyLongModuleName.length Now it'd be great if I could do the following instead: module AnnoyinglyLongModuleName (M.length, M.null) where import AnnoyinglyLongModuleName as M -- <- does not work length :: a -> Int length _ = 0 null :: a -> Bool null = (== 0) . M.length However, if I try to compile this, GHC complains about AnnoyinglyLongModuleName.hs:4:1: Bad interface file: AnnoyinglyLongModuleName.hi AnnoyinglyLongModuleName.hi: openBinaryFile: does not exist (No such file or directory) while GHCi tells me: Module imports form a cycle: module ?AnnoyinglyLongModuleName? (AnnoyinglyLongModuleName.hs) imports itself Is there some other way (without CPP) to create a local alias for the current module-name? If not, is there a reason GHC couldn't support this special case of self-aliasing the current module name? PS: Alternatively, this could be done as a language extension but that'd require extending the Haskell grammar: module AnnoyinglyLongModuleName as M (M.length, M.null) where Cheers, hvr From jan.stolarek at p.lodz.pl Mon Sep 29 09:52:28 2014 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Mon, 29 Sep 2014 11:52:28 +0200 Subject: Aliasing current module qualifier In-Reply-To: <8761g66dqf.fsf@gnu.org> References: <8761g66dqf.fsf@gnu.org> Message-ID: <201409291152.28926.jan.stolarek@p.lodz.pl> On a somewhat related note, I'd love to be able to do this in Haskell: import Basics.Nat renaming (_?_ to _??_) (this is taken from Agda). Janek Dnia poniedzia?ek, 29 wrze?nia 2014, Herbert Valerio Riedel napisa?: > Hello *, > > Here's a situation I've encountered recently, which mades me wish to be > able to define a local alias (in order to avoid CPP use). Consider the > following stupid module: > > > module AnnoyinglyLongModuleName > ( AnnoyinglyLongModuleName.length > , AnnoyinglyLongModuleName.null > ) where > > length :: a -> Int > length _ = 0 > > null :: a -> Bool > null = (== 0) . AnnoyinglyLongModuleName.length > > > Now it'd be great if I could do the following instead: > > module AnnoyinglyLongModuleName (M.length, M.null) where > > import AnnoyinglyLongModuleName as M -- <- does not work > > length :: a -> Int > length _ = 0 > > null :: a -> Bool > null = (== 0) . M.length > > However, if I try to compile this, GHC complains about > > AnnoyinglyLongModuleName.hs:4:1: > Bad interface file: AnnoyinglyLongModuleName.hi > AnnoyinglyLongModuleName.hi: openBinaryFile: does not exist (No > such file or directory) > > while GHCi tells me: > > Module imports form a cycle: > module ?AnnoyinglyLongModuleName? (AnnoyinglyLongModuleName.hs) > imports itself > > > Is there some other way (without CPP) to create a local alias for the > current module-name? If not, is there a reason GHC couldn't support this > special case of self-aliasing the current module name? > > > PS: Alternatively, this could be done as a language extension but that'd > require extending the Haskell grammar: > > module AnnoyinglyLongModuleName as M (M.length, M.null) where > > > Cheers, > hvr > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users From Christian.Maeder at dfki.de Mon Sep 29 15:07:05 2014 From: Christian.Maeder at dfki.de (Christian Maeder) Date: Mon, 29 Sep 2014 17:07:05 +0200 Subject: Aliasing current module qualifier In-Reply-To: <8761g66dqf.fsf@gnu.org> References: <8761g66dqf.fsf@gnu.org> Message-ID: <54297599.2030601@dfki.de> Hi, rather than disambiguating a name from the current module by an abbreviated module name, I would prefer a disambiguation as is done for local names that shadows existing bindings. Then only imported names would need to be qualified (possibly using shorter module names). So names of the current module would simple shadow unqualified imported names. I think, that would only make previously ambiguous modules compile. However, this does not help for the case when the whole module plus some imported names need to be exported. module AnnoyinglyLongModuleName ( module AnnoyinglyLongModuleName , ... ) where (Without re-exports the whole export list could be omitted) Cheers Christian Am 29.09.2014 um 10:19 schrieb Herbert Valerio Riedel: > Hello *, > > Here's a situation I've encountered recently, which mades me wish to be > able to define a local alias (in order to avoid CPP use). Consider the > following stupid module: > > > module AnnoyinglyLongModuleName > ( AnnoyinglyLongModuleName.length > , AnnoyinglyLongModuleName.null > ) where > > length :: a -> Int > length _ = 0 > > null :: a -> Bool > null = (== 0) . AnnoyinglyLongModuleName.length > > > Now it'd be great if I could do the following instead: > > module AnnoyinglyLongModuleName (M.length, M.null) where > > import AnnoyinglyLongModuleName as M -- <- does not work > > length :: a -> Int > length _ = 0 > > null :: a -> Bool > null = (== 0) . M.length > > However, if I try to compile this, GHC complains about > > AnnoyinglyLongModuleName.hs:4:1: > Bad interface file: AnnoyinglyLongModuleName.hi > AnnoyinglyLongModuleName.hi: openBinaryFile: does not exist (No such file or directory) > > while GHCi tells me: > > Module imports form a cycle: > module ?AnnoyinglyLongModuleName? (AnnoyinglyLongModuleName.hs) imports itself > > > Is there some other way (without CPP) to create a local alias for the > current module-name? If not, is there a reason GHC couldn't support this > special case of self-aliasing the current module name? > > > PS: Alternatively, this could be done as a language extension but that'd > require extending the Haskell grammar: > > module AnnoyinglyLongModuleName as M (M.length, M.null) where > > > Cheers, > hvr > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > From eir at cis.upenn.edu Mon Sep 29 13:27:02 2014 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Mon, 29 Sep 2014 09:27:02 -0400 Subject: Permitting trailing commas for record syntax ADT declarations In-Reply-To: References: <5420168E.5020503@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22228446@DB3PRD3001MB020.064d.mgd.msft.net> <54211D1A.5050400@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22229BC6@DB3PRD3001MB020.064d.mgd.msft.net> <54229F0E.2040009@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF2222F36B@DB3PRD3001MB020.064d.mgd.msft.net> <87d2ak9fvi.fsf@gmail.com> <20140925113416.GA7340@machine> <877g0raopr.fsf@gmail.com> Message-ID: To be fair, I'm not sure I like the make-commas-optional approach either. But, the solution occurred to me as possible, so I thought it was worth considering as we're exploring the design space. And, yes, I was suggesting only to make them optional, not to require everyone remove them. Richard On Sep 26, 2014, at 5:34 PM, Brandon Allbery wrote: > On Fri, Sep 26, 2014 at 5:21 PM, Johan Tibell wrote: > I don't think that's necessarily is good style. I don't think we want two different ways of doing import lists. > > Yes; I kinda hate the idea myself, it encourages an unreadable programming style. But it's not the wholesale breaking change you were suggesting, either. > > -- > brandon s allbery kf8nh sine nomine associates > allbery.b at gmail.com ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net > _______________________________________________ > 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 allbery.b at gmail.com Mon Sep 29 15:47:13 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 29 Sep 2014 11:47:13 -0400 Subject: Aliasing current module qualifier In-Reply-To: <8761g66dqf.fsf@gnu.org> References: <8761g66dqf.fsf@gnu.org> Message-ID: On Mon, Sep 29, 2014 at 4:19 AM, Herbert Valerio Riedel wrote: > Now it'd be great if I could do the following instead: > > module AnnoyinglyLongModuleName (M.length, M.null) where > > import AnnoyinglyLongModuleName as M -- <- does not work > I think if I wanted this syntax, I'd go for: module AnnoyinglyLongModuleName as M where ... -- 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 ekmett at gmail.com Mon Sep 29 17:48:00 2014 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 29 Sep 2014 13:48:00 -0400 Subject: Permitting trailing commas for record syntax ADT declarations In-Reply-To: References: <5420168E.5020503@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22228446@DB3PRD3001MB020.064d.mgd.msft.net> <54211D1A.5050400@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF22229BC6@DB3PRD3001MB020.064d.mgd.msft.net> <54229F0E.2040009@plaimi.net> <618BE556AADD624C9C918AA5D5911BEF2222F36B@DB3PRD3001MB020.064d.mgd.msft.net> <87d2ak9fvi.fsf@gmail.com> <20140925113416.GA7340@machine> <877g0raopr.fsf@gmail.com> Message-ID: Not a concrete suggestion, but just a related data point / nod to the sanity of the suggestion: I'm not sure I'd remove them entirely either, but FWIW, we don't require commas in fixity declarations in Ermine and it works well. On the other hand, our import lists are rather more complicated than Haskell's due to a need for extensive renaming on import though, so we don't shed the commas, but wind up using layout-based separation there, instead, avoiding conflicts by another means. That ship, however, has sailed for Haskell. ;) -Edward On Mon, Sep 29, 2014 at 9:27 AM, Richard Eisenberg wrote: > To be fair, I'm not sure I like the make-commas-optional approach either. > But, the solution occurred to me as possible, so I thought it was worth > considering as we're exploring the design space. > > And, yes, I was suggesting only to make them optional, not to require > everyone remove them. > > Richard > > On Sep 26, 2014, at 5:34 PM, Brandon Allbery wrote: > > On Fri, Sep 26, 2014 at 5:21 PM, Johan Tibell > wrote: > >> I don't think that's necessarily is good style. I don't think we want two >> different ways of doing import lists. > > > Yes; I kinda hate the idea myself, it encourages an unreadable programming > style. But it's not the wholesale breaking change you were suggesting, > either. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > _______________________________________________ > 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 john at repetae.net Mon Sep 29 21:02:11 2014 From: john at repetae.net (John Meacham) Date: Mon, 29 Sep 2014 14:02:11 -0700 Subject: Aliasing current module qualifier In-Reply-To: References: <8761g66dqf.fsf@gnu.org> Message-ID: You don't need a new language construct, what i do is: module AnnoyinglyLongModuleName (M.length, M.null) where import AnnoyinglongLongModuleName as M I think ghc would need to be extended a little to make this convienient as it doesn't handle recursive module imports as transparently. John On Mon, Sep 29, 2014 at 8:47 AM, Brandon Allbery wrote: > On Mon, Sep 29, 2014 at 4:19 AM, Herbert Valerio Riedel > wrote: > >> Now it'd be great if I could do the following instead: >> >> module AnnoyinglyLongModuleName (M.length, M.null) where >> >> import AnnoyinglyLongModuleName as M -- <- does not work >> > > I think if I wanted this syntax, I'd go for: > > module AnnoyinglyLongModuleName as M where ... > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users > > -- John Meacham - http://notanumber.net/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Mon Sep 29 21:05:09 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 29 Sep 2014 17:05:09 -0400 Subject: Aliasing current module qualifier In-Reply-To: References: <8761g66dqf.fsf@gnu.org> Message-ID: On Mon, Sep 29, 2014 at 5:02 PM, John Meacham wrote: > You don't need a new language construct, what i do is: > > module AnnoyinglyLongModuleName (M.length, M.null) where > > import AnnoyinglongLongModuleName as M > Isn't that exactly what the OP said doesn't work? > On Mon, Sep 29, 2014 at 8:47 AM, Brandon Allbery > wrote: > >> On Mon, Sep 29, 2014 at 4:19 AM, Herbert Valerio Riedel >> wrote: >> >>> Now it'd be great if I could do the following instead: >>> >>> module AnnoyinglyLongModuleName (M.length, M.null) where >>> >>> import AnnoyinglyLongModuleName as M -- <- does not work >>> >> >> I think if I wanted this syntax, I'd go for: >> >> module AnnoyinglyLongModuleName as M where ... >> > -- 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 iavor.diatchki at gmail.com Tue Sep 30 12:18:06 2014 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Tue, 30 Sep 2014 14:18:06 +0200 Subject: Aliasing current module qualifier In-Reply-To: References: <8761g66dqf.fsf@gnu.org> Message-ID: Hello, What semantics are you using for recursive modules? As far as I see, if you take a least fixed point semantics (e.g. as described in "A Formal Specification for the Haskell 98 Module System", http://yav.github.io/publications/modules98.pdf ) this program is incorrect as the module does not export anything. While this may seem a bit counter intuitive at first, this semantics has the benefit of being precise, easily specified, and uniform (e.g it does not require any special treatment of the " current " module). As an example, consider the following variation of your program, where I just moved the definition in a sperate (still recursive) module: module A (M.x) where import B as M module B (M.x) where import A as M x = True I think that it'd be quite confusing if a single recursive module worked differently then a larger recursive group, but it is not at all obvious why B should export 'x'. And for those who like this kind of puzzle: what should happen if 'A' also had a definition for 'x'? Iavor On Sep 29, 2014 11:02 PM, "John Meacham" wrote: > You don't need a new language construct, what i do is: > > module AnnoyinglyLongModuleName (M.length, M.null) where > > import AnnoyinglongLongModuleName as M > > I think ghc would need to be extended a little to make this convienient as > it doesn't handle recursive module imports as transparently. > > John > > On Mon, Sep 29, 2014 at 8:47 AM, Brandon Allbery > wrote: > >> On Mon, Sep 29, 2014 at 4:19 AM, Herbert Valerio Riedel >> wrote: >> >>> Now it'd be great if I could do the following instead: >>> >>> module AnnoyinglyLongModuleName (M.length, M.null) where >>> >>> import AnnoyinglyLongModuleName as M -- <- does not work >>> >> >> I think if I wanted this syntax, I'd go for: >> >> module AnnoyinglyLongModuleName as M where ... >> >> -- >> brandon s allbery kf8nh sine nomine >> associates >> allbery.b at gmail.com >> ballbery at sinenomine.net >> unix, openafs, kerberos, infrastructure, xmonad >> http://sinenomine.net >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users >> >> > > > -- > John Meacham - http://notanumber.net/ > > _______________________________________________ > 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 Sep 30 18:20:17 2014 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 30 Sep 2014 18:20:17 +0000 Subject: Aliasing current module qualifier In-Reply-To: References: <8761g66dqf.fsf@gnu.org> Message-ID: <618BE556AADD624C9C918AA5D5911BEF2223D16C@DB3PRD3001MB020.064d.mgd.msft.net> If there is to be such a language feature, I strongly feel it should be via something like module Long.Name.M( f, g, h ) as K where ... I do not want to try to piggy-back on the possible meaning of a self-import; it?s just asking for trouble, as Iavor points out. Using ?as M? in the module header would be simple. It is easy to explain and fairly easy to implement. I don?t think there are any knock-on complications. So if enough people want it, and someone is prepared to implement it (with a language extension flag of course), then I?d be OK with that. I?m unsure that it?s worth the effort, but I?m happy to let users decide. Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Iavor Diatchki Sent: 30 September 2014 13:18 To: john at repetae.net Cc: GHC Users Mailing List; ghc-devs; Herbert Valerio Riedel Subject: Re: Aliasing current module qualifier Hello, What semantics are you using for recursive modules? As far as I see, if you take a least fixed point semantics (e.g. as described in "A Formal Specification for the Haskell 98 Module System", http://yav.github.io/publications/modules98.pdf ) this program is incorrect as the module does not export anything. While this may seem a bit counter intuitive at first, this semantics has the benefit of being precise, easily specified, and uniform (e.g it does not require any special treatment of the " current " module). As an example, consider the following variation of your program, where I just moved the definition in a sperate (still recursive) module: module A (M.x) where import B as M module B (M.x) where import A as M x = True I think that it'd be quite confusing if a single recursive module worked differently then a larger recursive group, but it is not at all obvious why B should export 'x'. And for those who like this kind of puzzle: what should happen if 'A' also had a definition for 'x'? Iavor On Sep 29, 2014 11:02 PM, "John Meacham" > wrote: You don't need a new language construct, what i do is: module AnnoyinglyLongModuleName (M.length, M.null) where import AnnoyinglongLongModuleName as M I think ghc would need to be extended a little to make this convienient as it doesn't handle recursive module imports as transparently. John On Mon, Sep 29, 2014 at 8:47 AM, Brandon Allbery > wrote: On Mon, Sep 29, 2014 at 4:19 AM, Herbert Valerio Riedel > wrote: Now it'd be great if I could do the following instead: module AnnoyinglyLongModuleName (M.length, M.null) where import AnnoyinglyLongModuleName as M -- <- does not work I think if I wanted this syntax, I'd go for: module AnnoyinglyLongModuleName as M where ... -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users at haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users -- John Meacham - http://notanumber.net/ _______________________________________________ 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 john at repetae.net Tue Sep 30 20:05:03 2014 From: john at repetae.net (John Meacham) Date: Tue, 30 Sep 2014 13:05:03 -0700 Subject: Aliasing current module qualifier In-Reply-To: References: <8761g66dqf.fsf@gnu.org> Message-ID: Yes, that is the semantics I use for recursive module imports in jhc. And you are right in that it does not accept those examples due to being unable to bootstrap the least fixed point. How would the 'as M' proposal interact? Would it actually be new entries in the name table or rewritten as a macro to the current module name? I can see some edge cases where it makes a difference. I am thinking the easiest would be to populate entries for all the M.toplevel names where toplevel are the top level definitions of the module, will implement it and see how it shakes out. John On Tue, Sep 30, 2014 at 5:18 AM, Iavor Diatchki wrote: > Hello, > > What semantics are you using for recursive modules? As far as I see, if > you take a least fixed point semantics (e.g. as described in "A Formal > Specification for the Haskell 98 Module System", > http://yav.github.io/publications/modules98.pdf ) this program is > incorrect as the module does not export anything. > > While this may seem a bit counter intuitive at first, this semantics has > the benefit of being precise, easily specified, and uniform (e.g it does > not require any special treatment of the " current " module). As an > example, consider the following variation of your program, where I just > moved the definition in a sperate (still recursive) module: > > module A (M.x) where > import B as M > > module B (M.x) where > import A as M > x = True > > I think that it'd be quite confusing if a single recursive module worked > differently then a larger recursive group, but it is not at all obvious why > B should export 'x'. And for those who like this kind of puzzle: what > should happen if 'A' also had a definition for 'x'? > > Iavor > On Sep 29, 2014 11:02 PM, "John Meacham" wrote: > >> You don't need a new language construct, what i do is: >> >> module AnnoyinglyLongModuleName (M.length, M.null) where >> >> import AnnoyinglongLongModuleName as M >> >> I think ghc would need to be extended a little to make this convienient >> as it doesn't handle recursive module imports as transparently. >> >> John >> >> On Mon, Sep 29, 2014 at 8:47 AM, Brandon Allbery >> wrote: >> >>> On Mon, Sep 29, 2014 at 4:19 AM, Herbert Valerio Riedel >>> wrote: >>> >>>> Now it'd be great if I could do the following instead: >>>> >>>> module AnnoyinglyLongModuleName (M.length, M.null) where >>>> >>>> import AnnoyinglyLongModuleName as M -- <- does not work >>>> >>> >>> I think if I wanted this syntax, I'd go for: >>> >>> module AnnoyinglyLongModuleName as M where ... >>> >>> -- >>> brandon s allbery kf8nh sine nomine >>> associates >>> allbery.b at gmail.com >>> ballbery at sinenomine.net >>> unix, openafs, kerberos, infrastructure, xmonad >>> http://sinenomine.net >>> >>> _______________________________________________ >>> Glasgow-haskell-users mailing list >>> Glasgow-haskell-users at haskell.org >>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users >>> >>> >> >> >> -- >> John Meacham - http://notanumber.net/ >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://www.haskell.org/mailman/listinfo/ghc-devs >> >> -- John Meacham - http://notanumber.net/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From austin at well-typed.com Tue Sep 30 20:21:16 2014 From: austin at well-typed.com (Austin Seipp) Date: Tue, 30 Sep 2014 15:21:16 -0500 Subject: The future of the haskell2010/haskell98 packages - AKA Trac #9590 Message-ID: Hello developers, users, friends, I'd like you all to weigh in on something - a GHC bug report, that has happened as a result of making Applicative a superclass of Monad: https://ghc.haskell.org/trac/ghc/ticket/9590 The very condensed version is this: because haskell2010/haskell98 packages try to be fairly strictly conforming, they do not have modules like Control.Applicative. Unfortunately, due to the way these packages are structured, many things are simply re-exported from base, like `Monad`. But `Applicative` is not, and cannot be imported if you use -XHaskell2010 and the haskell2010 package. The net result here is that haskell98/haskell2010 are hopelessly broken in the current state: it's impossible to define an instance of `Monad`, because you cannot define an instance of `Applicative`, because you can't import it in the first place! This leaves us in quite a pickle. So I ask: Friends, what do you think we should do? I am particularly interested in users/developers of current Haskell2010 packages - not just code that may *be* standard Haskell - code that implies a dependency on it. There was a short discussion between me and Simon Marlow about this in the morning, and again on IRC this morning between me, Duncan, Edward K, and Herbert. Basically, I only see one of two options: - We could make GHC support both: a version of `Monad` without `Applicative`, and one with it. This creates some complication in the desugarer, where GHC takes care of `do` syntax (and thus needs to be aware of `Monad`'s definition and location). But it is, perhaps, quite doable. - We change both packages to export `Applicative` and follow the API changes in `base` accordingly. Note that #1 above is contingent on three things: 1) There is interest in this actually happening, and these separate APIs being supported. If there is not significant interest in maintaining this, it's unclear if we should go for it. 2) It's not overly monstrously complex (I don't think it necessarily will be, but it might be.) 3) You can't like `haskell2010` packages and `base` packages together in the general case, but, AFAIK, this wasn't the case before either. I'd really appreciate your thoughts. This must be sorted out for 7.10 somehow; the current situation is hopelessly busted. -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From simonpj at microsoft.com Tue Sep 30 20:25:08 2014 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 30 Sep 2014 20:25:08 +0000 Subject: The future of the haskell2010/haskell98 packages - AKA Trac #9590 In-Reply-To: References: Message-ID: <618BE556AADD624C9C918AA5D5911BEF2223D825@DB3PRD3001MB020.064d.mgd.msft.net> I hate #1. Let's avoid if unless it's really crucial to some of our users. Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Austin | Seipp | Sent: 30 September 2014 21:21 | To: ghc-devs at haskell.org; glasgow-haskell-users at haskell.org | Subject: The future of the haskell2010/haskell98 packages - AKA Trac | #9590 | | Hello developers, users, friends, | | I'd like you all to weigh in on something - a GHC bug report, that has | happened as a result of making Applicative a superclass of Monad: | | https://ghc.haskell.org/trac/ghc/ticket/9590 | | The very condensed version is this: because haskell2010/haskell98 | packages try to be fairly strictly conforming, they do not have | modules like Control.Applicative. | | Unfortunately, due to the way these packages are structured, many | things are simply re-exported from base, like `Monad`. But | `Applicative` is not, and cannot be imported if you use -XHaskell2010 | and the haskell2010 package. | | The net result here is that haskell98/haskell2010 are hopelessly | broken in the current state: it's impossible to define an instance of | `Monad`, because you cannot define an instance of `Applicative`, | because you can't import it in the first place! | | This leaves us in quite a pickle. | | So I ask: Friends, what do you think we should do? I am particularly | interested in users/developers of current Haskell2010 packages - not | just code that may *be* standard Haskell - code that implies a | dependency on it. | | There was a short discussion between me and Simon Marlow about this in | the morning, and again on IRC this morning between me, Duncan, Edward | K, and Herbert. | | Basically, I only see one of two options: | | - We could make GHC support both: a version of `Monad` without | `Applicative`, and one with it. This creates some complication in the | desugarer, where GHC takes care of `do` syntax (and thus needs to be | aware of `Monad`'s definition and location). But it is, perhaps, quite | doable. | | - We change both packages to export `Applicative` and follow the API | changes in `base` accordingly. | | Note that #1 above is contingent on three things: | | 1) There is interest in this actually happening, and these separate | APIs being supported. If there is not significant interest in | maintaining this, it's unclear if we should go for it. | | 2) It's not overly monstrously complex (I don't think it necessarily | will be, but it might be.) | | 3) You can't like `haskell2010` packages and `base` packages together | in the general case, but, AFAIK, this wasn't the case before either. | | I'd really appreciate your thoughts. This must be sorted out for 7.10 | somehow; the current situation is hopelessly busted. | | -- | 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 From malcolm.wallace at me.com Tue Sep 30 21:00:57 2014 From: malcolm.wallace at me.com (Malcolm Wallace) Date: Tue, 30 Sep 2014 22:00:57 +0100 Subject: The future of the haskell2010/haskell98 packages - AKA Trac #9590 In-Reply-To: References: Message-ID: <5F743CA1-227C-4F5C-B38E-1DD860659168@me.com> How about doing the honest thing, and withdrawing both packages in ghc-7.10? Haskell'98 is now 15 years old, and the 2010 standard was never really popular anyway. Regards, Malcolm On 30 Sep 2014, at 21:21, Austin Seipp wrote: Hello developers, users, friends, I'd like you all to weigh in on something - a GHC bug report, that has happened as a result of making Applicative a superclass of Monad: https://ghc.haskell.org/trac/ghc/ticket/9590 The very condensed version is this: because haskell2010/haskell98 packages try to be fairly strictly conforming, they do not have modules like Control.Applicative. Unfortunately, due to the way these packages are structured, many things are simply re-exported from base, like `Monad`. But `Applicative` is not, and cannot be imported if you use -XHaskell2010 and the haskell2010 package. The net result here is that haskell98/haskell2010 are hopelessly broken in the current state: it's impossible to define an instance of `Monad`, because you cannot define an instance of `Applicative`, because you can't import it in the first place! This leaves us in quite a pickle. So I ask: Friends, what do you think we should do? I am particularly interested in users/developers of current Haskell2010 packages - not just code that may *be* standard Haskell - code that implies a dependency on it. There was a short discussion between me and Simon Marlow about this in the morning, and again on IRC this morning between me, Duncan, Edward K, and Herbert. Basically, I only see one of two options: - We could make GHC support both: a version of `Monad` without `Applicative`, and one with it. This creates some complication in the desugarer, where GHC takes care of `do` syntax (and thus needs to be aware of `Monad`'s definition and location). But it is, perhaps, quite doable. - We change both packages to export `Applicative` and follow the API changes in `base` accordingly. Note that #1 above is contingent on three things: 1) There is interest in this actually happening, and these separate APIs being supported. If there is not significant interest in maintaining this, it's unclear if we should go for it. 2) It's not overly monstrously complex (I don't think it necessarily will be, but it might be.) 3) You can't like `haskell2010` packages and `base` packages together in the general case, but, AFAIK, this wasn't the case before either. I'd really appreciate your thoughts. This must be sorted out for 7.10 somehow; the current situation is hopelessly busted. -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users at haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users From allbery.b at gmail.com Tue Sep 30 21:02:54 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 30 Sep 2014 17:02:54 -0400 Subject: The future of the haskell2010/haskell98 packages - AKA Trac #9590 In-Reply-To: <5F743CA1-227C-4F5C-B38E-1DD860659168@me.com> References: <5F743CA1-227C-4F5C-B38E-1DD860659168@me.com> Message-ID: On Tue, Sep 30, 2014 at 5:00 PM, Malcolm Wallace wrote: > How about doing the honest thing, and withdrawing both packages in > ghc-7.10? Haskell'98 is now 15 years old, and the 2010 standard was never > really popular anyway. There are apparently educators using both, although they're not used much if at all in production. -- brandon s allbery kf8nh sine nomine associates 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 ryan.trinkle at gmail.com Tue Sep 30 23:04:14 2014 From: ryan.trinkle at gmail.com (Ryan Trinkle) Date: Tue, 30 Sep 2014 19:04:14 -0400 Subject: The future of the haskell2010/haskell98 packages - AKA Trac #9590 In-Reply-To: References: <5F743CA1-227C-4F5C-B38E-1DD860659168@me.com> Message-ID: Would something like John Meacham's class alias proposal ( http://repetae.net/recent/out/classalias.html) help alleviate this problem? On Tue, Sep 30, 2014 at 5:02 PM, Brandon Allbery wrote: > On Tue, Sep 30, 2014 at 5:00 PM, Malcolm Wallace > wrote: > >> How about doing the honest thing, and withdrawing both packages in >> ghc-7.10? Haskell'98 is now 15 years old, and the 2010 standard was never >> really popular anyway. > > > There are apparently educators using both, although they're not used much > if at all in production. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > > _______________________________________________ > 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: