[GHC] #12376: Allow function definitions in record syntax

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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: -------------------------------------+------------------------------------- Would it be possible to write {{{#!hs propertyMap :: (Monad m, Ord k) => v -> PropertyMap m k v propertyMap v0 = go v0 Map.empty where go v m = PropertyMap { getP = \k -> return $ maybe v id (Map.lookup k m) , putP = \k v' -> return $ go v (Map.insert k v' m) } }}} as {{{#!hs propertyMap :: (Monad m, Ord k) => v -> PropertyMap m k v propertyMap v0 = go v0 Map.empty where go v m = PropertyMap { getP k = return $ maybe v id (Map.lookup k m) , putP k v' = return $ go v (Map.insert k v' m) } }}} Simpler example `MkFoo { id = \x -> x }` as {{{#!hs MkFoo { id x = x } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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 Iceland_jack): Motivating example from [https://hackage.haskell.org/package/graphs-0.7/docs/src/Data-Graph- PropertyMap.html Data.Graph.PropertyMap] -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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 simonpj): One more piece of syntactic sugar. I see no difficulty in principle. What about recursion? Currently record fields are in scope in the RHS, but only as record selectors, not as the function being defined. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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 Iceland_jack): I'm not sure about that, it's possible that there would be more ''bang''-per-''buck'' in extending `LambdaCase` with `\case2`, `\case3`. Take an example of dictionary translation from [https://skillsmatter.com/skillscasts/8978-checking-and-translating-type- classes Checking and translating type classes]: {{{#!hs import Prelude hiding (Eq (..)) data Eq a = MkEq { (==) :: a -> a -> Bool , (/=) :: a -> a -> Bool } }}} {{{#!hs -- Default definition of (/=) neqDef :: Eq a -> a -> a -> Bool neqDef = not .:: (/=) where (.::) = fmap.fmap.fmap eqList :: forall a. Eq a -> Eq [a] eqList a = MkEq { (==) = aux , (/=) = neqDef (eqList a) } where aux :: [a] -> [a] -> Bool aux [] [] = True aux (x:xs) (y:ys) = (==) a x y && (==) (eqList a) xs ys aux _ _ = False }}} Now if we wanted to inline `aux` using this ticket, they would presumably translate into lambdas (single clause): {{{#!hs eqList a = MkEq { a == b = case (a, b) of ([], []) -> True (x:xs, y:ys) -> ... (_, _) -> False -- Translates into -- -- eqList a = MkEq -- { (==) = \a b -> ... }}} A hypothetical `\case2` may be better {{{#!hs eqList a = MkEq { (==) = \case2 ([], []) -> True (x:xs, y:ys) -> ... (_, _) -> False , (/=) = neqDef (eqList a) } }}} Given an extension that allows user to omit tuple parentheses when un- ambiguous (similar to Agda's `_,_` constructor which looks like `a , b` when applied to two arguments) this looks even better {{{#!hs eqList a = MkEq { (==) = \case2 [], [] -> True x:xs, y:ys -> ... _, _ -> False , (/=) = neqDef (eqList a) } }}} Should I create a ticket for these ideas or use the new [https://github.com/ghc-proposals/ghc-proposals GHC Proposals]? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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 carter): Am I seeing copatterns here or is it just me? @icelandjack I have nontrivial examples involving gadts and such Could we collaborate on this? This winds up being intimately related to coinduction and modelling protocols and interesting examples of linear logic -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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 nomeata): Replying to [comment:3 Iceland_jack]:
A hypothetical `\case2` may be better
{{{#!hs eqList a = MkEq { (==) = \case2 ([], []) -> True (x:xs, y:ys) -> ... (_, _) -> False , (/=) = neqDef (eqList a) } }}}
Given an extension that allows user to omit tuple parentheses when un- ambiguous (similar to Agda's `_,_` constructor which looks like `a , b` when applied to two arguments) this looks even better
{{{#!hs eqList a = MkEq { (==) = \case2 [], [] -> True x:xs, y:ys -> ... _, _ -> False , (/=) = neqDef (eqList a) } }}}
Why not go all the way and allow the full syntax of function definitions here, just as in a module scope, in an instance declaration, in a where clause or in a let clause: {{{#!hs eqList a = MkEq { [] == = True (x:xs) == (y:ys) = … _ == _ = False , (/=) = neqDef (eqList a) } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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 rwbarton): This doesn't seem to work well with the layout rules. Given that you can't define a function by multiple equations in this way, the payoff here seems very low... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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 ezyang): It's worth mentioning that you can almost directly simulate the desired syntax here using record wildcards: {{{ propertyMap :: (Monad m, Ord k) => v -> PropertyMap m k v propertyMap v0 = go v0 Map.empty where go v m = PropertyMap{..} where getP k = return $ maybe v id (Map.lookup k m) putP k v' = return $ go v (Map.insert k v' m) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- 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): Replying to [comment:7 ezyang]:
It's worth mentioning that you can almost directly simulate the desired syntax here using record wildcards: ...
Indeed. This pattern is the one and only time I've made profitable use of record wildcards. In general, I think this one isn't quite worth its weight. But, @Iceland_jack, I encourage you to use the ghc-proposals process for ideas like this, as it's now the official place for the community to weigh in on new language ideas. Posting to Trac reaches a smaller subset of the community. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12376: Allow function definitions in record syntax -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) 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 Iceland_jack): Replying to [comment:8 goldfire]:
But, @Iceland_jack, I encourage you to use the ghc-proposals process for ideas like this, as it's now the official place for the community to weigh in on new language ideas.
I'm not sure if this is worth the effort but I did similar sugar in [https://www.microsoft.com/en-us/research/wp- content/uploads/2016/02/scopedlabels.pdf Extensible records with scoped labels]:
As convenient syntactic sugar, we abbreviate the binding of a functional value `(l = \x1 ... xn → e)` as `(l x1 ... xn = e)`.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12376#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC