named-0.1.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 must declare their parameter names in the type signature:

replace ::
  Text `Named` "needle" ->
  Text `Named` "replacement" ->
  Text `Named` "haystack" ->
  Text
replace (Named needle) (Named replacement) (Named haystack) =
  ...

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

foo :: A -> B -> C `Named` "x" -> 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           :: A `Named` "x" -> B `Named` "y" -> IO ()
bar ! #y b    :: A `Named` "x"                  -> IO ()
with #y b bar :: A `Named` "x"                  -> IO ()

Synopsis

Core interface

newtype Named a (name :: Symbol) Source #

Assign a name to a value of type a. This is a simple wrapper intended for use with -XOverloadedLabels:

#verbose True :: Named Bool "verbose"

Constructors

Named 

Fields

Instances

((~) Symbol name name', (~) * a a') => IsLabel name (a -> Named a' name') Source # 

Methods

fromLabel :: a -> Named a' name' #

(!) :: Apply name a fn fn' => fn -> Named a name -> fn' infixl 9 Source #

Supply a keyword argument to a function:

function ! #param_name value

data Name (name :: Symbol) Source #

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

#verbose :: Name "verbose"

Constructors

Name 

Instances

(~) Symbol name name' => IsLabel name' (Name name) Source # 

Methods

fromLabel :: Name name #

with :: Apply name a fn fn' => Name name -> a -> fn -> fn' Source #

Supply a keyword argument to a function:

with #param_name value function

Specialized synonyms

type Flag = Named Bool Source #

Snake oil to cure boolean blindness.

pattern Flag :: Bool -> Flag name Source #

Match on a flag, a version of Named specialized to Bool.

Internal

type Apply (name :: Symbol) (a :: Type) (fn :: Type) (fn' :: Type) = Apply' (Decide name fn) name a fn fn' Source #

Supply a parameter of type a named name to a function fn, resulting in fn'.

For example:

Apply "x" Char
  (Named Bool "b" -> Named Char "x" -> r)
  (Named Bool "b" -> r)

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

apply :: Apply' decision name a fn fn' => fn -> Named a name -> fn' Source #

Apply a function to a keyword argument.

named :: Name name -> a -> Named a name Source #

Annotate a value with a name.