| Safe Haskell | None |
|---|
Data.Implicit
Description
Data.Implicit provides both named and unnamed implicit parameters that
support default values (given by the Default class from the data-default
package). It makes no use of the ImplicitParams extension and instead
everything is done using type classes.
Here is an example of unnamed implicit parameters:
{-# LANGUAGE FlexibleContexts #-}
import Data.Implicit
putParam :: Implicit_ String => IO ()
putParam = putStrLn $ "Param was: " ++ show (param_ :: String)
We define putParam, which is a simple function which takes an implicit
parameter of type String, and prints it to the screen. The param_ function
is used to retrieve the unnamed implicit parameter of type String from
putParam's context. The type signature is necessary to force param_ to
return a String, as this cannot be inferred due to the polymorphism of
show.
>>>putParamParam was ""
This is how we call putParam without specifying its implicit parameters. If
an implicit parameter is left unspecified, its value is defaulted to def,
assuming that its type has a Default instance. If not, then it is a type
error not to specify the value of an implicit parameter.
>>>putParam $~ "hello, world"Param was "hello, world"
The operator $~ takes a function f and a value to which to set the
homotypic implicit parameter on f. It applies the implicit parameter to f
and returns the result. There is also a prefix version of $~ whose arguments
are flipped called setParam_.
Here is an example of named implicit parameters:
{-# LANGUAGE DataKinds, FlexibleContexts, RankNTypes #-}
import Data.Implicit
import Data.Proxy
foo :: Proxy "foo"
foo = Proxy
bar :: Proxy "bar"
bar = Proxy
putFooBar :: (Implicit "foo" String, Implicit "bar" String) => IO ()
putFooBar = do
putStrLn $ "foo was: " ++ show (param foo :: String)
putStrLn $ "bar was: " ++ show (param bar :: String)
The Implicit constraint is the named equivalent of Implicit_. It takes an
additional argument s to specify the name of the implicit parameter.
Implicit parameters can be "named" using any type (of any kind, on compilers
that support the PolyKinds extension). (The above code uses type-level
strings of the Symbol kind from the GHC.TypeLits module, which is the
recommended way to name implicit parameters. However, Symbol requires the
DataKinds extension and at least version 7.8 of GHC (7.6 is broken; see GHC
bug #7502), so you are free to use other types of other kinds if you want to
support older versions of GHC.) param and setParam work like their unnamed
counterparts param_ and setParam_, but they also take a proxy argument to
specify the name of the implicit parameter. The code above defines foo and
bar to hide away the (slightly ugly) proxy stuff.
>>>putFooBarfoo was: "" bar was: ""
Once again, the defaults of unspecified implicit parameters are given by the
Default class.
>>>setParam foo "hello, world" putFooBarfoo was: "hello, world" bar was: ""
>>>setParam bar "goodbye" $ setParam foo "hello, world" putFooBarfoo was: "hello, world" bar was: "goodbye"
An infix version of setParam is also provided, ~$. Using ~$, the above
example would be:
>>>putFooBar ~$ foo ~$ bar $$ "goodbye" $$ "hello, world"foo was: "hello, world" bar was: "goodbye
- class Implicit s a where
- param :: proxy s -> a
- setParam :: forall a b proxy s. proxy s -> a -> (Implicit s a => b) -> b
- (~$) :: forall a b proxy s. (Implicit s a => b) -> proxy s -> a -> b
- (~..) :: Implicit s a => (Implicit s b => c) -> proxy s -> (a -> b) -> c
- ($$) :: (a -> b) -> a -> b
- class Implicit_ a where
- param_ :: a
- setParam_ :: forall a b. a -> (Implicit_ a => b) -> b
- ($~) :: forall a b. (Implicit_ a => b) -> a -> b
- (~.) :: Implicit_ a => (Implicit_ b => c) -> (a -> b) -> c
Documentation
class Implicit s a whereSource
The constraint on a function Implicit "foo" Stringf indicates
that an implicit parameter named "foo" of type String is passed to
f.
Methods
setParam :: forall a b proxy s. proxy s -> a -> (Implicit s a => b) -> bSource
setParam supplies a value for an implicit parameter named s to a
function which takes a homotypic and homonymous implicit parameter. The
name s is specified by a proxy argument passed to setParam.
(~$) :: forall a b proxy s. (Implicit s a => b) -> proxy s -> a -> bSource
An infix version of setParam with flipped arguments.
(~..) :: Implicit s a => (Implicit s b => c) -> proxy s -> (a -> b) -> cSource
Modify a named implicit parameter.
The constraint on a function Implicit_ Stringf indicates that an
unnamed implicit parameter of type String is passed to f.
Methods
setParam_ :: forall a b. a -> (Implicit_ a => b) -> bSource
setParam_ supplies a value for an unnamed implicit parameter to a
function which takes a homotypic implicit parameter.