[GHC] #12465: Evil idea: Allow empty record field update syntax for types.

#12465: Evil idea: Allow empty record field update syntax for types. -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Use case: Visible type application. I often work with constructors with many arguments, then I want to instantiate type variables with them: {{{#!hs show @(Vector _ _) :: Show a => Vector n a -> String -- Type arguments reversed, see https://github.com/ekmett/distributive/pull/18 cotraverse @_ @(Vector _) :: (NATTY n, Functor f) => (f a -> b) -> (f (Vector n a) -> Vector n a') fmap @(Bazaar _ _ _) :: (t -> t') -> (Bazaar p a b t -> Bazaar p a b t') show @(Magma _ _ _ _) :: (Show a, Show i) => Magma i t b a -> String }}} This makes no sense since types have nothing to do with record or updates thereof but that syntax is often used to avoid parentheses and unneeded wildcard arguments: {{{#!hs isBar (Bar _ _ _ _ _) = True -- ===> isBar Bar{} = True }}} This also means you don't need to worry about the kind of your constructor wrt the type (class) variable it instantiates. ---- Thus the proposal is to allow: {{{#!hs show @Vector{} :: Show a => Vector n a -> String cotraverse @_ @Vector{} :: (NATTY n, Functor f) => (f a -> b) -> (f (Vector n a) -> Vector n a') fmap @Bazaar{} :: (t -> t') -> (Bazaar p a b t -> Bazaar p a b t') show @Magma{} :: (Show a, Show i) => Magma i t b a -> String }}} ---- This would save quite a few keystrokes in my daily coding but more importantly it saves cognitive load but I expect skepticism, especially since GHC would have to determine whether to interpret `show @Vector{}` to `show @Vector`, `show @(Vector _n)` or `show @(Vector _n _a)`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12465 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12465: Evil idea: Allow empty record field update syntax for types. -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -3,2 +3,2 @@ - I often work with constructors with many arguments, then I want to - instantiate type variables with them: + I often work with constructors with many arguments that I want to + instantiate type variables with: New description: Use case: Visible type application. I often work with constructors with many arguments that I want to instantiate type variables with: {{{#!hs show @(Vector _ _) :: Show a => Vector n a -> String -- Type arguments reversed, see https://github.com/ekmett/distributive/pull/18 cotraverse @_ @(Vector _) :: (NATTY n, Functor f) => (f a -> b) -> (f (Vector n a) -> Vector n a') fmap @(Bazaar _ _ _) :: (t -> t') -> (Bazaar p a b t -> Bazaar p a b t') show @(Magma _ _ _ _) :: (Show a, Show i) => Magma i t b a -> String }}} This makes no sense since types have nothing to do with record or updates thereof but that syntax is often used to avoid parentheses and unneeded wildcard arguments: {{{#!hs isBar (Bar _ _ _ _ _) = True -- ===> isBar Bar{} = True }}} This also means you don't need to worry about the kind of your constructor wrt the type (class) variable it instantiates. ---- Thus the proposal is to allow: {{{#!hs show @Vector{} :: Show a => Vector n a -> String cotraverse @_ @Vector{} :: (NATTY n, Functor f) => (f a -> b) -> (f (Vector n a) -> Vector n a') fmap @Bazaar{} :: (t -> t') -> (Bazaar p a b t -> Bazaar p a b t') show @Magma{} :: (Show a, Show i) => Magma i t b a -> String }}} ---- This would save quite a few keystrokes in my daily coding but more importantly it saves cognitive load but I expect skepticism, especially since GHC would have to determine whether to interpret `show @Vector{}` to `show @Vector`, `show @(Vector _n)` or `show @(Vector _n _a)`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12465#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12465: Evil idea: Allow empty record field update syntax for types. -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -58,3 +58,4 @@ - importantly it saves cognitive load but I expect skepticism, especially - since GHC would have to determine whether to interpret `show @Vector{}` to - `show @Vector`, `show @(Vector _n)` or `show @(Vector _n _a)`. + importantly it saves cognitive load but I expect raised eyebrows + (especially since GHC would have to determine whether to interpret `show + @Vector{}` to `show @Vector`, `show @(Vector _n)` or `show @(Vector _n + _a)`). New description: Use case: Visible type application. I often work with constructors with many arguments that I want to instantiate type variables with: {{{#!hs show @(Vector _ _) :: Show a => Vector n a -> String -- Type arguments reversed, see https://github.com/ekmett/distributive/pull/18 cotraverse @_ @(Vector _) :: (NATTY n, Functor f) => (f a -> b) -> (f (Vector n a) -> Vector n a') fmap @(Bazaar _ _ _) :: (t -> t') -> (Bazaar p a b t -> Bazaar p a b t') show @(Magma _ _ _ _) :: (Show a, Show i) => Magma i t b a -> String }}} This makes no sense since types have nothing to do with record or updates thereof but that syntax is often used to avoid parentheses and unneeded wildcard arguments: {{{#!hs isBar (Bar _ _ _ _ _) = True -- ===> isBar Bar{} = True }}} This also means you don't need to worry about the kind of your constructor wrt the type (class) variable it instantiates. ---- Thus the proposal is to allow: {{{#!hs show @Vector{} :: Show a => Vector n a -> String cotraverse @_ @Vector{} :: (NATTY n, Functor f) => (f a -> b) -> (f (Vector n a) -> Vector n a') fmap @Bazaar{} :: (t -> t') -> (Bazaar p a b t -> Bazaar p a b t') show @Magma{} :: (Show a, Show i) => Magma i t b a -> String }}} ---- This would save quite a few keystrokes in my daily coding but more importantly it saves cognitive load but I expect raised eyebrows (especially since GHC would have to determine whether to interpret `show @Vector{}` to `show @Vector`, `show @(Vector _n)` or `show @(Vector _n _a)`). -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12465#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12465: Evil idea: Allow empty record field update syntax for types. -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -60,1 +60,1 @@ - @Vector{}` to `show @Vector`, `show @(Vector _n)` or `show @(Vector _n + @Vector{}` as `show @Vector`, `show @(Vector _n)` or `show @(Vector _n New description: Use case: Visible type application. I often work with constructors with many arguments that I want to instantiate type variables with: {{{#!hs show @(Vector _ _) :: Show a => Vector n a -> String -- Type arguments reversed, see https://github.com/ekmett/distributive/pull/18 cotraverse @_ @(Vector _) :: (NATTY n, Functor f) => (f a -> b) -> (f (Vector n a) -> Vector n a') fmap @(Bazaar _ _ _) :: (t -> t') -> (Bazaar p a b t -> Bazaar p a b t') show @(Magma _ _ _ _) :: (Show a, Show i) => Magma i t b a -> String }}} This makes no sense since types have nothing to do with record or updates thereof but that syntax is often used to avoid parentheses and unneeded wildcard arguments: {{{#!hs isBar (Bar _ _ _ _ _) = True -- ===> isBar Bar{} = True }}} This also means you don't need to worry about the kind of your constructor wrt the type (class) variable it instantiates. ---- Thus the proposal is to allow: {{{#!hs show @Vector{} :: Show a => Vector n a -> String cotraverse @_ @Vector{} :: (NATTY n, Functor f) => (f a -> b) -> (f (Vector n a) -> Vector n a') fmap @Bazaar{} :: (t -> t') -> (Bazaar p a b t -> Bazaar p a b t') show @Magma{} :: (Show a, Show i) => Magma i t b a -> String }}} ---- This would save quite a few keystrokes in my daily coding but more importantly it saves cognitive load but I expect raised eyebrows (especially since GHC would have to determine whether to interpret `show @Vector{}` as `show @Vector`, `show @(Vector _n)` or `show @(Vector _n _a)`). -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12465#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12465: Evil idea: Allow empty record field update syntax for types. -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 goldfire): I would love to see full support for record-like syntax at the type level. This would be (almost) forward-compatible with such an idea. I like it, with one exception: empty braces always always mean that the type is fully applied. If you wish for it to be partially applied, then use underscores. The (almost) part above is that you mean the type `Vector {}` to have a subtly different meaning than an expression `MkRec {}`. In the former, you wish for GHC to infer the values for the arguments. In the latter, you wish for GHC to use `undefined`. In some future world where we can sometimes infer the value of term-level arguments (because we have dependent types), perhaps we can have `MkRec {}` mean "infer arguments where possible, otherwise use `undefined`". Such an interpretation of `MkRec {}` seems fully backward-compatible, for two reasons: (1) no term- level arguments can be inferred today, and (2) even if they could, we would simply be making a term-level value be more defined, which can't hurt the semantics of a program. So I, for one, support this move. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12465#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC