Safe Haskell | None |
---|---|
Language | Haskell2010 |
The public interface is exposed in CommonMain#Kw
- class Kw fn arg_def r where
- class IsKeyFN t flag | t -> flag
- recToKW :: forall a b. (HMapCxt HList TaggedToKW a b, HConcat b) => Record a -> HList (HConcatR b)
- data K s c = K
- data ErrReqdArgNotFound x
- data ErrUnexpectedKW x
- class KWApply f arg_values r where
- class KWApply' flag f arg_values r where
- newtype Arg arg_types arg_values = Arg (HList arg_values)
- reflect_fk :: ReflectFK fn kws => fn -> Arg kws []
- class ReflectFK f kws
- class ReflectFK' flag f kws
- class KW f arg_desc arg_def r where
- class KW' rflag f arg_desc arg_def r where
- class KWAcc arg_desc kw a f arg_def r where
- class KWMerge arg_needed arg_values arg_def f r where
- class KWMerge' kw list atail arg_values arg_def f r where
- class KWMerge'' flag kw list atail arg_values arg_def f r where
- class HDelete e l l'
- class HDelete' flag e l l'
- data TaggedToKW
main
class Kw fn arg_def r where Source
kw
takes a HList
whose first element is a function, and the rest
of the elements are default values.
A useful trick is to have a final argument ()
which is not
eaten up by a label (A only takes 1 argument). That way when you supply
the () it knows there are no more arguments (?).
>>>
data A = A
>>>
instance IsKeyFN (A -> a -> b) True
>>>
let f A a () = a + 1
>>>
let f' = f .*. A .*. 1 .*. HNil
>>>
kw f' A 0 ()
1
>>>
kw f' ()
2
class IsKeyFN t flag | t -> flag Source
All our keywords must be registered
(~) Bool False flag => IsKeyFN t flag | overlapping/fallback case |
IsKeyFN (Label Symbol s -> a -> b) True | labels that impose no restriction on the type of the (single) argument which follows
|
(~) * r (c -> b) => IsKeyFN (K k s c -> r) True | The purpose of this instance is to be able to use the same Symbol
(type-level string) at different types. If they are supposed to be the same,
then use
therefore the following options works:
But you cannot leave off all |
recToKW :: forall a b. (HMapCxt HList TaggedToKW a b, HConcat b) => Record a -> HList (HConcatR b) Source
convert a Record
into a list that can supply
default arguments for kw
A bit of setup:
>>>
:set -XQuasiQuotes
>>>
import Data.HList.RecordPuns
>>>
let f (_ :: Label "a") a (_ :: Label "b") b () = a `div` b
>>>
let a = 2; b = 1; f' = f .*. recToKW [pun| a b |]
>>>
kw f' ()
2
>>>
kw f' (Label :: Label "a") 10 ()
10
another label type
(~) * r (c -> b) => IsKeyFN (K k s c -> r) True | The purpose of this instance is to be able to use the same Symbol
(type-level string) at different types. If they are supposed to be the same,
then use
therefore the following options works:
But you cannot leave off all |
types for user error
data ErrReqdArgNotFound x Source
data ErrUnexpectedKW x Source
demo
setup data types
>>>
:set -XDataKinds -XFlexibleInstances -XMultiParamTypeClasses
>>>
:set -XScopedTypeVariables -XOverlappingInstances -XTypeFamilies
>>>
:set -fcontext-stack=100
We will be using an example inspired by a graphics toolkit -- the area which really benefits from keyword arguments. We first define our labels and useful datatypes
>>>
data Color = Color
>>>
data Size = Size
>>>
data Origin = Origin
>>>
data RaisedBorder = RaisedBorder
The number of arguments each keyword must be specified by an IsKeyFN
instance.
>>>
instance IsKeyFN (Color->a->b) True
>>>
instance IsKeyFN (Size->a->b) True
>>>
instance (a ~ (Int,Int)) => IsKeyFN (Origin->a->b) True
>>>
instance IsKeyFN (RaisedBorder->a->b) True
Note that if a keyword is always followed by a certain type, that can be specified above using an instance like the one for Origin.
>>>
data CommonColor = Red | Green | Blue deriving Show
>>>
data RGBColor = RGBColor Int Int Int deriving Show
and two functions:
>>>
:{
let make_square Size n Origin (x0,y0) Color (color::CommonColor) = unwords ["Square:", show (n :: Int), "at", show (x0,y0), show color] ++ "\n" :}
>>>
:{
let make_rect Size (nx,ny) Origin (x0,y0) Color (color::RGBColor) RaisedBorder border = unwords ["Rectangle:", show (nx,ny), "at", show (x0,y0), show color, if border then "raised border" else ""] ++ "\n" :}
Implementation details
One of the key tools of the implementation is kwapply
, which applies
a function to a polymorphic collection of that function's arguments.
The order of the arguments in the collection is irrelevant. The
contraption kwapply can handle polymorphic functions with arbitrary
number of labeled arguments.
For example, if we define
f1 Size n = show n f2 Size n Color m = unwords ["size:", show n, "color:", show m] f3 Origin x Color m Size n = unwords ["origin:", show x, "size:", show n, "color:",show m]
then we can run
katest1 = kwapply f1 (Size .*. () .*. HNil) katest11 = kwapply f1 (Size .*. "Large" .*. HNil) katest2 = kwapply f2 (Size .*. (1::Int) .*. Color .*. Red .*. HNil) katest21 = kwapply f2 (Color .*. Red .*. Size .*. (1::Int) .*. HNil) katest3 = kwapply f3 (Size .*. (1::Int) .*. Origin .*. (2.0::Float) .*. Color .*. Red .*. HNil)
class KWApply' flag f arg_values r where Source
((~) [*] (HAppendListR * tail ((:) * kw ((:) * v ([] *)))) l', HAppendList tail ((:) * kw ((:) * v ([] *))), KWApply f l' r) => KWApply' Bool False f ((:) * kw ((:) * v tail)) r | Rotate the arg list ... |
((~) * v' v, KWApply f' tail r) => KWApply' Bool True (kw -> v -> f') ((:) * kw ((:) * v' tail)) r |
newtype Arg arg_types arg_values Source
The datatype Arg below is to maintain the state of keyword
accumulation: which keywords we need, and which keyword and values we
have already got.
arg_types is the phantom HList of keywords that are yet to be satisfied.
arg_values is the HList (kw .*. kw_value .*. etc)
of already found keywords and their values.
KWMerge k arg_needed arg_values arg_def f r => KW' Bool False f (Arg k arg_needed arg_values) arg_def r | If the continuation r does not promise any more keyword arguments, apply the defaults |
Show (HList vals) => Show (Arg k tys vals) | |
(HDelete k * kw arg_types arg_types', KW f (Arg [k] arg_types' ((:) * kw ((:) * a arg_values))) arg_def r) => KWAcc (Arg [k] arg_types arg_values) kw a f arg_def r |
producing lists from a function's arguments
reflect_fk :: ReflectFK fn kws => fn -> Arg kws [] Source
that reflects on a user-supplied function. It converts the *type* of a
user function to a collection of keywords required by that
function. This and the previous contraptions may be used to define an
extended
version of some user function that takes more arguments --
without the need to enumerate all arguments of the original
function. We thus infringe on the area of object and module systems.
The rest of the implementation is just to convert `kw fn defaults' into the application of kwapply.
Another key contraption is
Reflection on a function: Given a function, return the type list of its keywords
>>>
:t reflect_fk (undefined::Size->Int->Color->CommonColor->String)
reflect_fk (undefined::Size->Int->Color->CommonColor->String) :: Arg '[Size, Color] '[]
>>>
:t reflect_fk (undefined::Size->Int->()->Int)
reflect_fk (undefined::Size->Int->()->Int) :: Arg '[Size] '[]
(IsKeyFN f flag, ReflectFK' * [*] flag f kws) => ReflectFK * f kws |
class ReflectFK' flag f kws Source
(~) [k] ([] k) nil => ReflectFK' k [k] False f nil | |
((~) [*] kkws ((:) * kw kws), ReflectFK * rest kws) => ReflectFK' * [*] True (kw -> a -> rest) kkws |
collecting arguments
class KW' rflag f arg_desc arg_def r where Source
(KWAcc arg_desc kw a f arg_def r, (~) * (kw -> a -> r) kwar) => KW' Bool True f arg_desc arg_def kwar | Otherwise, collect the supplied keyword and its value, and recurse for more: |
KWMerge k arg_needed arg_values arg_def f r => KW' Bool False f (Arg k arg_needed arg_values) arg_def r | If the continuation r does not promise any more keyword arguments, apply the defaults |
class KWAcc arg_desc kw a f arg_def r where Source
Add the real argument to the Arg structure, and continue
merging default with supplied arguments
class KWMerge arg_needed arg_values arg_def f r where Source
Add the needed arguments from arg_def to arg_values and continue with kwapply.
That is, we try to satisfy the missing arguments from the defaults. It will be a type error if some required arguments are missing
class KWMerge' kw list atail arg_values arg_def f r where Source
(Fail * (ErrReqdArgNotFound * kw), (~) * nff (ErrReqdArgNotFound * kw)) => KWMerge' k kw ([] *) atail arg_values arg_def f nff | |
(HEq * kw kw' flag, KWMerge'' k flag kw ((:) * kw' etc) atail arg_values arg_def f r) => KWMerge' k kw ((:) * kw' etc) atail arg_values arg_def f r |
class KWMerge'' flag kw list atail arg_values arg_def f r where Source
Delete e from l to yield l' The element e must occur in l
original introduction
From oleg-at-okmij.org Fri Aug 13 14:58:35 2004 To: haskell@haskell.org Subject: Keyword arguments From: oleg-at-pobox.com Message-ID: <20040813215834.F1FF3AB7E@Adric.metnet.navy.mil> Date: Fri, 13 Aug 2004 14:58:34 -0700 (PDT) Status: OR
We show the Haskell implementation of keyword arguments, which goes well beyond records (e.g., in permitting the re-use of labels). Keyword arguments indeed look just like regular, positional arguments. However, keyword arguments may appear in any order. Furthermore, one may associate defaults with some keywords; the corresponding arguments may then be omitted. It is a type error to omit a required keyword argument. The latter property is in stark contrast with the conventional way of emulating keyword arguments via records. Also in marked contrast with records, keyword labels may be reused throughout the code with no restriction; the same label may be associated with arguments of different types in different functions. Labels of Haskell records may not be re-used. Our solution is essentially equivalent to keyword arguments of DSSSL Scheme or labels of OCaml.
Keyword argument functions are naturally polyvariadic: Haskell does support varargs! Keyword argument functions may be polymorphic. As usual, functions with keyword arguments may be partially applied. On the downside, sometimes one has to specify the type of the return value of the function (if the keyword argument function has no signature -- the latter is the norm, see below) -- provided that the compiler cannot figure the return type out on its own. This is usually only the case when we use keyword functions at the top level (GHCi prompt).
Our solution requires no special extensions to Haskell and works with the existing Haskell compilers; it is tested on GHC 6.0.1. The overlapping instances extension is not necessary (albeit it is convenient).
The gist of our implementation is the realization that the type of a function is a polymorphic collection of its argument types -- a collection that we can traverse. This message thus illustrates a limited form of the reflection on a function.
Our implementation is a trivial extension of the strongly-typed polymorphic open records described in http://homepages.cwi.nl/~ralf/HList/
In fact, the implementation relies on the HList library. To run the code (which this message is), one needs to download the HList library from the above site.
The HList paper discusses the issue of labels in some detail. The paper gives three different representations. One of them needs no overlapping instances and is very portable. In this message, we chose a representation that relies on generic type equality and therefore needs overlapping instances as implemented in GHC. Again, this is merely an outcome of our non-deterministic choice. It should be emphasized that other choices are possible, which do not depend on overlapping instances at all. Please see the HList paper for details.
todo
better instances for Symbol
There isn't a pair (K2 "Origin" (Int, Int))
(K "hi")
that behaves just like Origin below.
something is possible between constraintkinds. See Fun
instance (a ~ (Int,Int)) => IsKeyFN (Origin->a->b) True
wildcard/catchall
like in R. This would be a special keyword for keyword args that didn't match.
They would be put in a HList/Record argument like ...
investigate first-classness of varargs
- for whatever reason you can't have
f = kw fn blah
and then pass more arguments on to fn. This is bad. It used to work (in the ghc6.0 days and probably up to 6.12). Some convenience functions/operators should be added which do the same thing as:
fn `hAppendList` hBuild a b c d e
internal for type signature prettiness
data TaggedToKW Source
((~) * x (Tagged k l v), (~) * y (HList ((:) * (Label k l) ((:) * v ([] *))))) => ApplyAB TaggedToKW x y |