[GHC] #13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC.

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I wrote this little piece of code to show that the compiler could very well execute the pragma by itself without being ordered to do so.\\ {{{ module Testfoo where import Language.Haskell.TH.Lib import Data.Kind tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ]) data T = MkT (forall a. [a] -> [a]) answer_read = show (read @Int "3") data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Song (a :: k) }}} By compiling the code without the Pragmas, GHC responds:\\ * 1) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:13:7: error: parse error on input `$' Perhaps you intended to use TemplateHaskell\\ * 2) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:15:23: error: Illegal symbol '.' in type Perhaps you intended to use {{{RankNTypes}}} or a similar language extension to enable explicit-forall syntax: forall <tvs>.<type>\\ * 3) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:19:16: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo.hs:19:28: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo.hs:22:1: error: Unexpected kind variable `k' Perhaps you intended to use {{{PolyKinds}}} In the declaration for type family `Song' testfoo.hs:22:24: error: Illegal kind signature: `k' Perhaps you intended to use KindSignatures In the declaration for type family `Song'\\ * 4) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:18:21: error: Pattern syntax in expression context: read@Int Did you mean to enable {{{TypeApplications}}}?\\ * 5) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:20:1: error: * Illegal generalised algebraic data declaration for `Foo' (Use {{{GADTs}}} to allow GADTs) * In the data declaration for `Foo'\\ * 6) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:23:1: error: * Illegal family declaration for `Song' Use {{{TypeFamilies}}} to allow indexed type families * In the data family declaration for `Song'\\ * 7) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) c:\Testghc>\\ Here is the code once completed. {{{ {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} module Testfoo where import Language.Haskell.TH.Lib import Data.Kind tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ]) data T = MkT (forall a. [a] -> [a]) answer_read = show (read @Int "3") data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Song (a :: k) }}} As you may notice, GHC suggests the appropriate pragma.\\ If we add manually in the code the Pragmas one after the other and we arrive at the end, the code is fully compiled without error.\\ The compiler could do this alone.\\ We could test it using a "-auto" option on the compiler command line.\\ This is a start to the compiler automation technology, what do you think of that? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -4,1 +4,1 @@ - {{{ + {{{#!hs @@ -20,1 +20,1 @@ - By compiling the code without the Pragmas, GHC responds:\\ + By compiling the code without the Pragmas, GHC responds: @@ -22,0 +22,1 @@ + {{{ @@ -81,0 +82,1 @@ + }}} @@ -84,1 +86,1 @@ - {{{ + {{{#!hs New description: I wrote this little piece of code to show that the compiler could very well execute the pragma by itself without being ordered to do so.\\ {{{#!hs module Testfoo where import Language.Haskell.TH.Lib import Data.Kind tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ]) data T = MkT (forall a. [a] -> [a]) answer_read = show (read @Int "3") data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Song (a :: k) }}} By compiling the code without the Pragmas, GHC responds: {{{ * 1) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:13:7: error: parse error on input `$' Perhaps you intended to use TemplateHaskell\\ * 2) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:15:23: error: Illegal symbol '.' in type Perhaps you intended to use {{{RankNTypes}}} or a similar language extension to enable explicit-forall syntax: forall <tvs>.<type>\\ * 3) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:19:16: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo.hs:19:28: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo.hs:22:1: error: Unexpected kind variable `k' Perhaps you intended to use {{{PolyKinds}}} In the declaration for type family `Song' testfoo.hs:22:24: error: Illegal kind signature: `k' Perhaps you intended to use KindSignatures In the declaration for type family `Song'\\ * 4) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:18:21: error: Pattern syntax in expression context: read@Int Did you mean to enable {{{TypeApplications}}}?\\ * 5) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:20:1: error: * Illegal generalised algebraic data declaration for `Foo' (Use {{{GADTs}}} to allow GADTs) * In the data declaration for `Foo'\\ * 6) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) testfoo.hs:23:1: error: * Illegal family declaration for `Song' Use {{{TypeFamilies}}} to allow indexed type families * In the data family declaration for `Song'\\ * 7) c:\Testghc>ghc testfoo.hs [1 of 1] Compiling Testfoo ( testfoo.hs, testfoo.o ) c:\Testghc>\\ }}} Here is the code once completed. {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} module Testfoo where import Language.Haskell.TH.Lib import Data.Kind tup = $(tupE $ take 4 $ cycle [ [| "hi" |] , [| 5 |] ]) data T = MkT (forall a. [a] -> [a]) answer_read = show (read @Int "3") data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Song (a :: k) }}} As you may notice, GHC suggests the appropriate pragma.\\ If we add manually in the code the Pragmas one after the other and we arrive at the end, the code is fully compiled without error.\\ The compiler could do this alone.\\ We could test it using a "-auto" option on the compiler command line.\\ This is a start to the compiler automation technology, what do you think of that? -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Making pragmas implicit, even with a flag, is a slippery slope that I don't believe we want to head down. GHC's pragma suggestions are just that: suggestions. They are the result of heuristics and by no means are these heuristics always correct. I suspect that making the compiler's behavior conditional on these heuristics would at best result in some very confusing error messages. There are many ways that wee might want to reduce the cost of pragmas. Even today you can enable them with project-level granularity in your Cabal file. Moreover, IDE tooling quickly approaching the point where it can help the user make pragma changes. In the future we might also consider adding a few more "meta-extensions" (e.g. `-XDependentHaskell`) capturing sets of commonly needed pragmas. Does this help? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replying to bgamari\\
I suspect that making the compiler's behavior conditional on these heuristics would at best result in some very confusing error messages.\\ Maybe or maybe not. GHC messages should not be underestimated. Here he answered well.\\ Take a look at this other example.\\
{{{ module Testfoo2 where import Data.Kind data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b }}} GHC responds\\ {{{ Prelude> :l testfoo2 [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:10:16: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo2.hs:10:28: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:11:1: error: * Illegal generalised algebraic data declaration for `Foo' (Use GADTs to allow GADTs) * In the data declaration for `Foo' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) Ok, modules loaded: Testfoo2. }}} If the second function is added {{{ data family Song (a :: k) }}} and that we start again, GHC respond:\\ {{{ *Testfoo2> :l testfoo2 [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:13:16: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo2.hs:13:28: error: Illegal kind signature: `Type' Perhaps you intended to use KindSignatures In the data type declaration for `Foo' testfoo2.hs:16:1: error: Unexpected kind variable `k' Perhaps you intended to use PolyKinds In the declaration for type family `Song' testfoo2.hs:16:24: error: Illegal kind signature: `k' Perhaps you intended to use KindSignatures In the declaration for type family `Song' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:16:1: error: Unexpected kind variable `k' Perhaps you intended to use PolyKinds In the declaration for type family `Song' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:13:1: error: * Illegal generalised algebraic data declaration for `Foo' (Use GADTs to allow GADTs) * In the data declaration for `Foo' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) testfoo2.hs:16:1: error: * Illegal family declaration for `Song' Use TypeFamilies to allow indexed type families * In the data family declaration for `Song' Failed, modules loaded: none. Prelude> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) Ok, modules loaded: Testfoo2. *Testfoo2> :r [1 of 1] Compiling Testfoo2 ( testfoo2.hs, interpreted ) Ok, modules loaded: Testfoo2. }}} If you look closer you can even remove the pragma {{{ {- # LANGUAGE KindSignatures # -} }}} And the program still compiles well. And GHC did it all alone without my help.\\ I think that has the merit of being studied. You have to be enthusiastic about doing that. Maybe in twenty years someone will code that? They will be compilers worthy of the twenty-first century. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vanto): Replying to bgamari (2)\\ I forgot to say this. Because GHC will have to make several go and return to find the right solution in order to use it for compilation, I suggest using the backtracking algorithm found in the Prolog language. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix Comment: Feel free to write an external tool (perhaps linking against the `ghc` API) to perform the search that your propose. However, I don't believe the compiler is the right place for this sort of logic. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

However, I don't believe the compiler is the right place for this sort of logic. It is established that you do not know the Ada language compiler.\\ I think your answer is an arbitrary answer. Besides you are not the only one to have this kind of answer in the Committee. Often your responses
#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vanto): * status: closed => new * resolution: wontfix => Comment: that do not relate to a bug are arbitrary and seems to be controlled by anything other than rational reason.\\ If you close this ticket, you do not correct anything and you forget. I reopen it even if you do not follow it, someone else later will take it into account for a more complete exploitation.\\ You are forty people on the Committee, your opinion alone does not make law to close this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => wontfix Comment: If you wish to get a wider opinion from the committee, I suggest you make a ghc-proposal using the established process that we have pointed you to in the past. This is a user-facing change and thus must go through that process. If the proposal is accepted by the committee, we can reopen this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vanto): * status: closed => new * resolution: wontfix => Comment: Replying to [[span(style=color: #FF0000, goldfire )]]\\ This idea is an idea and someone could take it up for study. Once again goldfire you are not alone. The others have the right as much as you to read this ticket and make their choice. This ticket is for everyone. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13884: To an automatic compilation of file-header LANGUAGE pragmas in GHC. -------------------------------------+------------------------------------- Reporter: vanto | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AntC): Replying to [comment:8 vanto]:
Replying to [[span(style=color: #FF0000, goldfire )]]\\
-1 from me. I usually want to use a minimum of flags; the compiler messages help me switch them on in a controlled, deliberate sequence. Flags/pragmas around Overlaps and `IncoherentInstances` I would never want to be enabled automatically: if I've written instances needing incoherence, I've done something wrong. I echo @goldfire's suggestion to use the established process, not Trac, to get a wider opinion. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13884#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC