[GHC] #12360: Extend support for binding implicit parameters
GHC
ghc-devs at haskell.org
Sat Jul 2 21:13:56 UTC 2016
#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
More information about the ghc-tickets
mailing list