named-0.3.0.0: Named parameters (keyword arguments) for Haskell

Safe HaskellNone
LanguageHaskell2010

Named

Contents

Description

Named parameters, also known as keyword arguments, have several advantages over positional arguments:

  • convenience: they can be supplied in arbitrary order
  • readability: their names serve as documentation at call site
  • safety: it is impossible to accidentally mix them up

Consider a function to replace a substring with another string:

Text.replace path "$HOME" "/home/username/"

We want to replace references to the $HOME environment variable with a concrete directory. There is but one problem – we have supplied the text arguments in the wrong order.

Compare that to a newtype-based solution:

Text.replace
  (Needle "$HOME")
  (Replacement "/home/username/")
  (Haystack path)

Now that the function requires each argument to be wrapped in a newtype, we cannot mix them up – the compiler will report an error, and newtype constructors serve as documentation.

The problem with newtypes is that it is bothersome to create them for each parameter, they pollute the global namespace, and we still cannot supply wrapped arguments in arbitrary order.

With keyword arguments, none of that is a problem:

Text.replace ! #haystack path
             ! #needle "$HOME"
             ! #replacement "/home/username/"

Functions can declare their parameter names in pattern bindings:

replace (arg #needle -> n) (arg #replacement -> r) (arg #haystack -> h) =
  ...

Types are inferred, but it is possible to specify them. When the parameter names are specified in the type signature, they can be omitted from the pattern bindings:

replace ::
  "needle"      :! Text ->
  "replacement" :! Text ->
  "haystack"    :! Text ->
  Text
replace (Arg n) (Arg r) (Arg h) =
  ...

Keyword arguments have seamless interoperability with positional arguments when the function takes them last. Consider this function:

foo :: A -> B -> "x" :! C -> IO ()

There are several ways to invoke it:

(foo a b) ! #x c     -- parentheses for clarity
(foo a ! #x c) b     -- parentheses required
(foo ! #x c) a b     -- parentheses required

We can also supply keyword arguments using the with combinator instead of the ! operator:

(with (#x c) foo) a b  -- parentheses for clarity
with (#x c) (foo a b)  -- has the same effect

Both ! and with work in a similar manner: they traverse the spine of the function and supply the first keyword argument with a matching name.

For example:

bar             :: "x" :! A -> "y" :! B -> IO ()
bar ! #y b      :: "x" :! A             -> IO ()
with (#y b) bar :: "x" :! A             -> IO ()

There is also support for optional parameters. A function can specify default values for some of its arguments:

log ::
  "message"  :! Text ->
  "severity" :? Severity ->
  "handle"   :? Handle ->
  IO ()
log (arg    #message          -> msg)
    (argDef #severity Error   -> sev)
    (argDef #handle   stderr  -> hndl)
  = ...

Optional parameters are denoted with (:?) instead of (:!). Instead of arg to match on them, we must use either argDef to provide a default value or argF to get a value wrapped in Maybe (Just when the parameter was specified, Nothing when omitted).

At call site, optional parameters are passed using the same (!) operator:

log ! #message "All your base are belong to us"
    ! #severity Info
    ! #handle stdout

To use the default values for all unspecified optional parameters, we can pass defaults to the function:

log ! #message "Could not match type Int with type Bool"
    ! defaults
log ! #message "The password must contain a letter, \
               \a digit, and a plot twist"
    ! #severity Warning
    ! defaults

We can also pass defaults using with, which has the same effect as the (!) operator:

with defaults $
  log ! #message "Connection interrupted"
      ! #handle logfile
Synopsis

Call site

(!) :: forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn' infixl 9 Source #

Supply a parameter to a function:

function ! #param_name value
function ! #x 7 ! #y 42 ! defaults

This is an infix version of with.

class WithParam p fn fn' | p fn -> fn' where Source #

Supply a parameter p to a function fn, resulting in fn'.

For example, when we pass a single named parameter, we get a function without this parameter:

WithParam
                 ("x" :! Char)       -- p
  ("b" :! Bool -> "x" :! Char -> r)  -- fn
  ("b" :! Bool                -> r)  -- fn'

In case the parameter cannot be supplied, this constraint will become a type error.

Methods

with :: Param p -> fn -> fn' Source #

Supply a parameter to a function:

 with (#param_name value) function
 
 with defaults function
 

This is a prefix version of the (!) operator.

Instances
WithParam' (Decide p fn) p fn fn' => WithParam p fn fn' Source # 
Instance details

Defined in Named.Internal

Methods

with :: Param p -> fn -> fn' Source #

param :: Name name -> a -> Param (name :! a) Source #

Explicitly build a function parameter:

fn ! param #param_name value

This is equivalent to the implicit notation:

fn ! #param_name value

paramF :: Name name -> f a -> Param (NamedF f a name) Source #

Explicitly build a function parameter inside an arity wrapper:

fn ! paramF #param_name (Identity value)
fn ! paramF #param_name (Just value)
fn ! paramF #param_name Nothing

This has no equivalent implicit notation.

defaults :: Param Defaults Source #

Passing defaults to a function fills all unspecified optional parameters with Nothing:

fn            :: "b" :! Bool -> "x" :? Char -> Int -> IO ()
fn ! defaults :: "b" :! Bool ->                Int -> IO ()

Definition site

type (:!) name a = NamedF Identity a name Source #

Infix notation for the type of a named parameter.

type (:?) name a = NamedF Maybe a name Source #

Infix notation for the type of an optional named parameter.

newtype NamedF f (a :: Type) (name :: Symbol) Source #

Assign a name to a value of type a wrapped in f.

#verbose True :: NamedF Identity Bool "verbose"

Constructors

ArgF (f a)

Match on an F-argument without specifying its name. See also: argF.

Bundled Patterns

pattern Arg :: a -> name :! a

Match on an argument without specifying its name. See also: arg.

Instances
(name ~ name', a ~ a', InjValue f) => IsLabel name (a -> NamedF f a' name') Source # 
Instance details

Defined in Named.Internal

Methods

fromLabel :: a -> NamedF f a' name' #

data Name (name :: Symbol) Source #

A proxy for a name, intended for use with -XOverloadedLabels:

#verbose :: Name "verbose"

Constructors

Name 
Instances
name ~ name' => IsLabel name' (Name name) Source # 
Instance details

Defined in Named.Internal

Methods

fromLabel :: Name name #

arg :: Name name -> (name :! a) -> a Source #

arg unwraps a named parameter with the specified name. One way to use it is to match on arguments with -XViewPatterns:

fn (arg #t -> t) (arg #f -> f) = ...

This way, the names of parameters can be inferred from the patterns: no type signature for fn is required. In case a type signature for fn is provided, the parameters must come in the same order:

fn :: "t" :! Integer -> "f" :! Integer -> ...
fn (arg #t -> t) (arg #f -> f) = ... -- ok
fn (arg #f -> f) (arg #t -> t) = ... -- does not typecheck

argDef :: Name name -> a -> (name :? a) -> a Source #

A variation of arg for optional arguments. Requires a default value to handle the case when the optional argument was omitted:

fn (argDef #answer 42 -> ans) = ...

In case you want to get a value wrapped in Maybe instead, use argF or ArgF.

argF :: Name name -> NamedF f a name -> f a Source #

argF is similar to arg: it unwraps a named parameter with the specified name. The difference is that the result of argF is inside an arity wrapper, which is Identity for normal parameters and Maybe for optional parameters.