[GHC] #9642: LANGUAGE pragma synonyms

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Here are the first 20 lines of a typical Haskell file of mine: {{{ {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LiberalTypeSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE AutoDeriveTypeable #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE OverlappingInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ConstraintKinds #-} }}} Over a couple of modules in a small package, I find myself copy-pasting these 20 lines, as either I will use these extensions, or they won't really cause any harm to the code I'm writing. As a way to simplify this, and reduce code duplication, I propose introducing LANGUAGE pragma synonyms: {{{ {-# LANGUAGE PedrosHaskell = EmptyDataDecls, FlexibleContexts, FlexibleInstances , LiberalTypeSynonyms, ScopedTypeVariables , RankNTypes, StandaloneDeriving, AutoDeriveTypeable , DeriveDataTypeable, DeriveGeneric, DefaultSignatures , OverlappingInstances, UndecidableInstances , MultiParamTypeClasses, TypeOperators, TypeFamilies , GADTs, DataKinds, PolyKinds, ConstraintKinds #-} }}} After writing this, in that same module or any module that imports it, I could just write: {{{ {-# LANGUAGE PedrosHaskell #-} }}} And all the pragmas above would be enabled. Besides making my life easier, I suspect this will also help increase modularity of certain packages. For example, packages could define a package-specific language pragma that should be enabled in order to use that package. Then, if the package maintainer upgrades one datatype to become a GADT, the pragma would be updated to include `GADTs`, and user code (that could now be requiring that pragma) would automatically enable `GADTs` too. Furthermore, it can also make the language standardisation process simpler. After all, {{{ {-# LANGUAGE Haskell2010 = PatternGuards, NoNPlusKPatterns, RelaxedPolyRec , EmptyDataDecls, ForeignFunctionInterface #-} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by jstolarek): Are you aware of the possibility of specifying extensions in package's `.cabal` file? Here's an example: {{{ library hs-source-dirs: src exposed-modules: ... build-depends: ... extensions: BangPatterns EmptyDataDecls FlexibleContexts FlexibleInstances ... }}} This addresses the issue of code duplication. It does not address auto- enabling of LANGUAGE extensions for modules that import a package. Personally I don't like the idea of having extensions automatically (and implicitly) enabled without my knowledge just because I imported a module. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dreixel): Replying to [comment:1 jstolarek]:
Are you aware of the possibility of specifying extensions in package's `.cabal` file?
Yes, but I don't think that addresses the same issues that my proposal does. Replying to [comment:1 jstolarek]:
Personally I don't like the idea of having extensions automatically (and implicitly) enabled without my knowledge just because I imported a module.
It wouldn't be automatically enabled. It would just be available for use; you'd still have to write {{{ {-# LANGUAGE PedrosHaskell #-} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by jstolarek): Replying to [comment:2 dreixel]:
Yes, but I don't think that addresses the same issues that my proposal does. Well, it address only one of them (avoiding copy-pastes).
It wouldn't be automatically enabled. It would just be available for use; you'd still have to write {{{ {-# LANGUAGE PedrosHaskell #-} }}} I see.
But wouldn't your proposal impose artificial dependencies between modules, where one module needs to import another just to use the LANGUAGE synonym? I imagine this could become a problem in some circumstances. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by hvr): What about using {{{#!hs {-# LANGUAGE CPP #-} #include "pedros_haskell.inc" }}} ? :-) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by rodlogic): What about introducing an official (GHC-official, not Haskell standard) BleedingEdge pragma (or something like that) that is an amalgamation of most used and bleeding pragmas in GHC? Then if I want to use GHC with all or most features I would only have to add: {{{ #!haskell {-# LANGUAGE BleedingEdge #-} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by hvr): Replying to [comment:5 rodlogic]:
What about introducing an official (GHC-official, not Haskell standard) BleedingEdge pragma (or something like that) that is an amalgamation of most used and bleeding pragmas in GHC? Then if I want to use GHC with all or most features I would only have to add:
That sounds a lot like the `-fglasgow-exts` flag that was deprecated a few years ago in favour of specifying individual extensions... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by nomeata): I like it. I worry that the implementation is non-trivial: After all, you’d want the parser to know about the pragmas, and you need the parsed module before knowing the import list. How about putting these aliases into the package database? This is loaded before an individual module is loaded and avoids module dependencies? I.e. a new stanza: {{{ language PedrosHaskell extensions: BangPatterns EmptyDataDecls FlexibleContexts FlexibleInstances }}} in some dependencies’ `.cabal` file? (This opens the way to other `cabal` flags to be used here, e.g. compiler flags to load a specific plugin, which might be very useful, but let’s not go there with this proposal yet.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by jstolarek): Replying to [comment:7 nomeata]:
How about putting these aliases into the package database? But then loading a module from the package into GHCi would require knowing about aliases in the `.cabal` file.
(This opens the way to other `cabal` flags to be used here, e.g. compiler flags to load a specific plugin, which might be very useful, but let’s not go there with this proposal yet.) That's a feature I would like to see. In the past I struggled a lot because I had to duplicate in the `benchmark` section all language extensions and compilation options specified in `library` section. But then again this is a Cabal feature request, not GHC.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by nomeata):
But then loading a module from the package into GHCi would require knowing about aliases in the .cabal file.
True, it would only help providing synonyms across package boundaries (or imaginably when using `cabal repl` using some weird trick), not when trying to re-use a synonym within a package. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): Just a data point: Now that cabal 2 supports multiple library sections, relegating this to `extensions` is even less of a viable alternative. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9642: LANGUAGE pragma synonyms -------------------------------------+------------------------------------- Reporter: dreixel | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Ed, I am not sure I understand your statement. It is less viable to have `extensions` on the top-level cabal file level? Less viable as a statement within a `library` stanza? Less viable anywhere in a `cabal` file? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9642#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC