[GHC] #12360: Extend support for binding implicit parameters
GHC
ghc-devs at haskell.org
Wed Jul 6 03:08:07 UTC 2016
#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
More information about the ghc-tickets
mailing list