[GHC] #12360: Extend support for binding implicit parameters

#12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | 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: -------------------------------------+------------------------------------- Implicit parameters can only be bound using simple let and where declarations. In this example, one would expect ?t to be bound to the result of getCurrentTime, however the program is rejected with a syntax error: {{{ {-# LANGUAGE ImplicitParams #-} import Data.Time.Clock printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ?t main = do ?t <- getCurrentTime printTime }}} Instead, one must first bind to a regular variable and then bind the implicit parameter to it: {{{ {-# LANGUAGE ImplicitParams #-} import Data.Time.Clock printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ?t main = do t <- getCurrentTime let ?t = t printTime }}} In general, it seems like any pattern binding involving implicit parameters could be rewritten as a pattern binding to ordinary variables, followed by a binding of the implicit parameters to the ordinary variables. So you could bind implicit parameters buried in variables, tuples, record fields, etc.: Sugared: {{{ {-# LANGUAGE ImplicitParams #-} data Example = Example { a :: Int, b :: Int, c :: Int } f :: (?a :: Int, ?b :: Int, ?c :: Int) => Int f = ?a + ?b + ?c main = do let x = Example 1 2 3 let (Example { a = ?a, b = ?b, c = ?c }) = x let y = f putStrLn $ show y }}} Desugared: {{{ {-# LANGUAGE ImplicitParams #-} data Example = Example { a :: Int, b :: Int, c :: Int } f :: (?a :: Int, ?b :: Int, ?c :: Int) => Int f = ?a + ?b + ?c main = do let x = Example 1 2 3 let (Example { a = a, b = b, c = c }) = x let ?a = a ?b = b ?c = c let y = f putStrLn $ show y }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12360 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | 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 MichaelBurge: @@ -54,2 +54,1 @@ - let y = f - putStrLn $ show y + putStrLn $ show f @@ -73,2 +72,1 @@ - let y = f - putStrLn $ show y + putStrLn $ show f New description: Implicit parameters can only be bound using simple let and where declarations. In this example, one would expect ?t to be bound to the result of getCurrentTime, however the program is rejected with a syntax error: {{{ {-# LANGUAGE ImplicitParams #-} import Data.Time.Clock printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ?t main = do ?t <- getCurrentTime printTime }}} Instead, one must first bind to a regular variable and then bind the implicit parameter to it: {{{ {-# LANGUAGE ImplicitParams #-} import Data.Time.Clock printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ?t main = do t <- getCurrentTime let ?t = t printTime }}} In general, it seems like any pattern binding involving implicit parameters could be rewritten as a pattern binding to ordinary variables, followed by a binding of the implicit parameters to the ordinary variables. So you could bind implicit parameters buried in variables, tuples, record fields, etc.: Sugared: {{{ {-# LANGUAGE ImplicitParams #-} data Example = Example { a :: Int, b :: Int, c :: Int } f :: (?a :: Int, ?b :: Int, ?c :: Int) => Int f = ?a + ?b + ?c main = do let x = Example 1 2 3 let (Example { a = ?a, b = ?b, c = ?c }) = x putStrLn $ show f }}} Desugared: {{{ {-# LANGUAGE ImplicitParams #-} data Example = Example { a :: Int, b :: Int, c :: Int } f :: (?a :: Int, ?b :: Int, ?c :: Int) => Int f = ?a + ?b + ?c main = do let x = Example 1 2 3 let (Example { a = a, b = b, c = c }) = x let ?a = a ?b = b ?c = c putStrLn $ show f }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12360#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | 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: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12360#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | 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): I see no technical difficulties here. The question is: how common is the situation where this feature would be useful? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12360#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | 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 MichaelBurge): I use implicit parameters a lot in my larger programs, and pattern-binding seems like a fundamental feature. Usually I set them in a top-level function for configuration files or similar, where the workaround in this ticket isn't too inconvenient. I did have one creative use that I thought would be confusing without this feature: {{{ {-# LANGUAGE ImplicitParams,RankNTypes #-} type UserId = Int data UserLoggedIn = UserLoggedIn UserId newtype Authorized a = Authorized a class Authorizable a where authorize :: a -> IO (Authorized a) instance Authorizable UserLoggedIn where authorize userId = undefined -- Imagine checking the user's cookies or the database or something fetchLatestUnreadMessage :: (?u :: Authorized UserLoggedIn) => IO (Maybe String) fetchLatestUnreadMessage = undefined -- No need to check authentication; the fact that we have an Authorized UserLoggedIn means the user has already been authenticated. type WebsitePage = String showUserHomepage :: IO WebsitePage showUserHomepage = do -- u <- authorize $ UserLoggedIn undefined -- let ?u = u mMessage <- fetchLatestUnreadMessage case mMessage of Nothing -> return "" Just message -> return message main = do homepage <- showUserHomepage putStrLn homepage }}} In this example, the idea is based on the common pattern of requiring the user to retrieve a token from your API before he can call any of the other functions. Sometimes it is annoying to keep the token around, since its only use is to enforce the order that you call functions in. By hiding the token in an implicit variable, we get a type error if you don't authorize yourself before executing an action requiring authorization. The example code gives a compile error, but uncommenting the 2 lines will cause it to succeed. I thought it would be confusing to have 2 such tokens in scope(u and ?u), so I opted not to use this design. Looking in my project, here are the only other uses of implicit parameters: * Break module dependencies(if f depends on g and g depends on f and they are in different modules, make g depend on ?f and break the dependency in a top-level module by assigning ?f = f. * Read configuration files at the start. This also happens in a top-level module. * I use the new (?c :: CallStack) feature for ease-of-debugging. I don't see much code on Hackage using implicit parameters, and they're not as useful on smaller projects. But they certainly do see some use. And I will probably continue to find new uses for them, where this pattern- binding feature could help. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12360#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | 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): This is a bad idea right: {{{#!hs pattern ImplicitTime :: (?t::UTCTime) => UTCTime pattern ImplicitTime = ?t printTime :: (?t :: UTCTime) => IO () printTime = putStrLn $ show ImplicitTime main = do ImplicitTime <- getCurrentTime printTime }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12360#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12360: Extend support for binding implicit parameters -------------------------------------+------------------------------------- Reporter: MichaelBurge | 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): Iceland_jack: I could not parse your comments. But currently GHC does allow this: {{{ data X where MkX :: (?x :: Int) => X f :: X -> Int -> Int f MkX y = ?x + y -- The pattern match on MkX binds an -- implicit parameter ?x g = let ?x = 7 in f MkX 5 -- Here the MkX needs a ?x constraint, which it gets from -- the let-binding. So g = 12 }}} Function `f` looks a bit odd because it has a use of `?x` but it is far from clear where it is bound: you have to look at the captured constraints for the pattern-matched constructors. But there is nothing technically complicated or unsound about this. Pattern synonyms are just sugar on top of this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12360#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC