- Have you seen the Turtle "How would"?
“No,” said Alice. - I don't even know who that is.
“Of course,” said the Queen. - This is what “Turtle Soup” is made of.
Lewis Carroll,
"Alice in Wonderland"
- Judging by your speeches, do you know Fangorn well? - Aragorn asked in response.
- What is there! - responded the old man. - A hundred lives are not enough for this. But I sometimes come back here.
John R. R. Tolkien,
"Lord of the Rings" - to the word of my knowledge of Haskell;)
Homines dum docent, discunt. (Explain to others - you will understand.) popular Latin saying
Everyone knows that any Haskell function is inherently a function of a single parameter. The “as if” functions of several parameters simply taking the first argument, return another function that takes the second argument (of the original function) and returns the return function, etc. before the final function, which already returns a value of a non-functional type (
currying ).
')
It would seem what variable number of parameters can we talk about in this situation? However, on reflection, looking at the source of
printf or simply reading
wiki.haskell it becomes obvious that just the
OP provides the key to a rather beautiful, although somewhat "casuistic" solution of this problem.
In this publication, I will look at one of the ways to implement such a mechanism using simple examples, and also offer some generalized solution based on
Template Haskell to turn a family of ordinary functions with the last parameter of the list type into a function with “as if with a variable number of parameter” (further the text is simply “with a variable number of parameters”).
I will briefly describe the essence of the solution, starting with an extremely simple example.
{-# LANGUAGE FlexibleInstances, RankNTypes #-}
What happens here and how is it possible to transfer the magic functions not only to an arbitrary number of parameters, but also to parameters of different types?
So in (1) we declare the class
VarArgs with the only method
prc simply able to create a value of a given type from a string. Further, in (2) we implement an instance of this class for the type String (also known as [Char]). Please note that you had to use the FlexibleInstances (0) extension - otherwise this instance will be “out of the law”.
There is an alternative solution, but it also uses the TypeFamilies extension or GADTs. {-# LANGUAGE TypeFamilies #-} instance a ~ Char => VarArgs [a] where prc = id
The
VarArgs String instance is actually the “body” of a function with a variable number of parameters. In the example, we simply return the accumulated parameters. We now turn to the most interesting, in (3) we declare a
VarArgs instance for the functional type
(a -> r) , while requiring that the type of the argument
a be able to be displayed on the string, and the type of the result
r would again belong to the class
VarArgs .
This is where “the dog rummaged” - by instantiating a class with a functional type with a return type that also allows (in particular) a function, we allow the
prc method, depending on the call context, to return both the final value of the
String type if the context requires a string, and The result type of the
prc call is derived from the context as functional.
Now consider the definition of
prc for an instance of
VarArgs (a -> r) . If we print the type
prc , we get
prc :: (Show a, VarArgs r) => String -> (a -> r)
Those. we have to return a function that does something with a value representable as a string. The
acc argument is the essence of the “accumulator” of the result of the sequential processing of parameters. In this case, we simply add to it a string representation of the parameter separated by a space.
The important point is that we do not just return the incremental “accumulator”, but call (in the “body” of the resulting function) recursively
prc to get the desired type of result
r . What kind of
prc implementation will be called (i.e., what type will be output) depends on the context (do not forget that the Haskell functions are equations, and the calculation process is the successive substitution of expressions with the actualization of parameters).
The most interesting thing is that despite the “semi-legal” status, we can quite transfer (4) and use (5) a function with a variable number of parameters as an argument to another function. True, for this we had to use another extension,
RankNTypes (0) and the
forall quantifier in the definition of the calling function (4).
It sounds a bit confusing, so let's take a look at how the expression to the right of
$ in (4) is calculated:
- magic (also prc [] ) is called with parameter 1 i.e. used in a functional context, so the instance is running
VarArgs (a -> r) , eventually returns ... - ... again function we again have argument 2 i. functional context present again
- qwe and [1,2,3] are processed in the same way
- finally, the result of the last call of the prc function with accumulated string representations of the previous parameters and the current parameter 123.456 will already require a string context, like the parameter of the putStrLn function — the prc is started from the VarArgs String instance
Now let's look at another, slightly more complicated example: the calculator of expressions in
reverse Polish notation . Something like:
> calcRPN 5 8 (*) 2 (+)
The most primitive implementation might look something like this:
{-# LANGUAGE ExtendedDefaultRules, FlexibleInstances, GADTs #-} data Expr = Num Double | Op (Double -> Double -> Double) calcRPN' :: [Expr] -> Double calcRPN' = head . foldr rpnStep [] . reverse rpnStep :: Expr -> [Double] -> [Double] rpnStep (Num n) stack = n : stack rpnStep (Op f) (x:y:stack) = (fxy) : stack class ArgPrc a where prc :: [Expr] -> a class ArgSrc a where toArg :: a -> Expr instance ArgPrc Double where prc = calcRPN' . reverse instance (ArgSrc a, ArgPrc r) => ArgPrc (a -> r) where prc acc = prc . (: acc) . toArg
The scheme for implementing a variable number of parameters is the same as in the previous example, only now we will be:
- accumulate arguments (of type Expr ) in the list for further processing instead of immediately building the result (2);
- use the “wrapper” class ArgSrc for type declarations that can act as “expressions” ( Expr )
- use some "trick" (extension GADTs) to implement an instance
instance a ~ Double => ArgSrc (a -> a -> a)
Finally, let's look at a schematic implementation of the printf function:
{-# LANGUAGE GADTs, FlexibleInstances, ExtendedDefaultRules #-} type FmtRes = (String, String) class PfVal a where doFmt :: (String, String) -> a -> FmtRes instance PfVal Integer where doFmt (fmt, res) x = let (b, s) = span (/= '%') fmt in (res ++ (tail . tail $ s), b ++ show x) instance PfVal String where doFmt (fmt, res) x = let (b, s) = span (/= '%') fmt in (res ++ (tail . tail $ s), b ++ x) class ArgProc a where prc :: FmtRes -> a instance ArgProc String where prc = uncurry (++) instance ArgProc (IO ()) where prc = putStrLn . uncurry (++) instance (PfVal a, ArgProc r) => ArgProc (a -> r) where prc st = prc . doFmt st printf fmt = prc (fmt, "") main :: IO() main = do putStrLn $ printf "%d %s" 1 "qwe" printf "%s %d" "This is" 123
I suppose the code does not need any special comments, I’ll just note that now we are again generating the result on the fly, instead of accumulating parameters and implementing
two terminal instances of the
ArgProc class: for the
String type and for the
IO () type .
If we generalize the illustrated scheme, we can distinguish the following elements:
- Some type is a battery (let's call it A ) a preliminary result of calculations based on parameters of type a . The degree of “preliminary” can vary from a simple accumulation of parameters in some kind of list-type container (as in the example with reverse Polish notation ) to an almost finished result for the current parameter set (as in the example with printf ). All we need from this type is the presence of an operation like
A -> a -> A
- The main class (let's call it ArgProc ), through the instances of which the whole “mechanics” of a variable number of parameters is implemented. This class has a single method (let's call it prc ) that does something with battery A :
class ArgProc a where prc :: A -> a
- A class of types that can act as parameters (let's call ArgSrc ) supporting the function of converting values into a type of parameters (some type a admitting an operation :: A -> a -> A )
- An instance of the main class that is responsible for processing parameters and accumulating a preliminary result:
instance (ArgSrc a, ArgProc r) ArgProc (a -> r) where prc :: A -> (a -> r)
In the example with printf , the result is immediately accumulated (the second element of the pair) and the state (format string) is processed simultaneously. In the example with reverse Polish notation, the parameters are simply added to the list for further processing.
- Terminal instance (s) of the main class, responsible for the final processing of the preliminary result:
instance ArgProc R1 where prc :: A -> R1 instance ArgProc R2 where prc :: A -> R2 ...
In the example with the reverse Polish notation, there is only one such instance for the resulting type Double - it simply starts the calculation for the list of previously accumulated parameters. In the example with printf, an instance for String simply concatenates a formatted string with the remainder of the format (meaning that flat text is left there). The instance for IO () additionally displays the result.
- The initializer of the initial state of the preliminary result of the calculation A. In general, it is a function of a set of fixed parameters, in the examples it is the constant value [] and the function
\x -> (x, "") :: String -> (String -> String)
It is easy to see that such a scheme can be implemented by means of "black magic"
Template Haskell . This is a good exercise to consolidate the material, as well as a good platform for
dancing with a tambourine experiments with
Template Haskell .
In the current implementation, I limited myself to a subset of the general scheme: a drive is simply a list of values of a certain type, the initializer, respectively, is simply
[] . Such restrictions certainly have certain disadvantages, but the idea is to transform a family of ordinary functions with an identical type of parameters, the last of which is a list, and various types of return, into a function that accepts a variable number of parameters (in addition to fixed ones that go to the list) .
Along the way, we automate the process of “implicit reduction” (in the terminology of other PLs) of specified types to the type of elements of the parameter list. Another restriction - “donor” functions must have “simple” types (non-polymorphic types without quantifiers and restrictions).
I will immediately begin again with examples of use, the idea will be clear, and only then I will briefly go through the implementation. So let's start with something simple:
{-# LANGUAGE TemplateHaskell, FlexibleInstances, ExtendedDefaultRules #-} import Data.Function.Vargs
In this example, we create a
tester wrapper function for the
tester ' function, which has the type:
tester' :: String -> [String] -> IO ()
Let's go through the text:
- (1) - we connect the module that implements a variable number of parameters
- (2) - we define the "experimental" function for the transformation
- (3) - a trick, for guaranteed reify work (for details, for example, here )
- (4) - we define a function with a variable number of parameters
Parameters starting from the 3rd - values of one of the types:
- (Name, ExpQ)
- (TypeQ, ExpQ)
they describe how you can convert values of a given type (Integer, (), etc.) into values of the type of the elements of the parameter list (String). The type is specified either by the name ((5), (6)) or by the expression ((7), (8)). Please note that the elements themselves are also passed as variable parameters!
- (9) - the actual function call with a variable number of parameters of different types (reducible to the string) in arbitrary order
Go ahead, or rather return to the example
with the reverse Polish notation :
{-# LANGUAGE TemplateHaskell, FlexibleInstances, ExtendedDefaultRules, GADTs #-}
In this example, everything is similar to the previous one, with the exception of one interesting point (1): here we use not just TypeQ, but some
Genz wrapper over it. This wrapper causes the generator to build an instance of the form:
instance a ~ Double => ArgSrc (a -> a -> a) where
instead of the standard
instance ArgSrc (Double -> Double -> Double) where
which in this case will not pass type checking.
Well, and the last example, the very function printf, or rather its schematic analog:
{-# LANGUAGE TemplateHaskell, FlexibleInstances, ExtendedDefaultRules, ExistentialQuantification #-} import Data.Function.Vargs type FmtRes = (String, String) class PfVal a where doFmt :: FmtRes -> a -> FmtRes instance PfVal Integer where doFmt (fmt, res) x = let (b, s) = span (/= '%') fmt in (res ++ (tail . tail $ s), b ++ show x) instance PfVal Double where doFmt (fmt, res) x = let (b, s) = span (/= '%') fmt in (res ++ (tail . tail $ s), b ++ show x) instance PfVal String where doFmt (fmt, res) x = let (b, s) = span (/= '%') fmt in (res ++ (tail . tail $ s), b ++ x) data PfValWrap = forall a. PfVal a => Val a
There are three new points to note here:
- using a wrapper type (1) for processing values of arbitrary types that support a PfVal class contract (able to output themselves to a string according to a specified format)
- the presence of two parameter handlers (2) - (3) for different types of result ( String and IO () )
- automatic code generation for converting the values of the specified types into the PfValWrap wrapper type (in fact, the only constructor of the type, Val, is simply pulled through reflection)
Now a few words about how it all works. Actually, all that
defVargsFun does
is that it creates several classes and instances, based on the information received from
reify , as well as the declaration and definition of the function itself with a variable number of parameters. All this "kitchen" corresponds to the general scheme previously discussed with examples. Again, it will be clearer and easier to demonstrate with an example what exactly is generated. Consider the code generated by the call:
defVargsFun "printf" ['printf_String, 'printf_IO] [''Integer, ''Double, ''String]
This code can be viewed if you run
ghc with the
-ddump-splices key . For clarity, I corrected the formatting and removed the extra brackets:
class ArgPrc_printf_aa3M a where
The monad Q provides us with the generation of unique names - hence the "intricate" endings in the names. Let's go through the text:
- the main class handler of a variable number of parameters (1) and its key method (2) are declared
- class (3) is declared for “implicit reduction” of values of given types to the type of parameter list element ( PfValWrap ) with a single method (4)
- “terminal” instances of our main class (1) are defined for the types String (5) and IO () (6), the implementation of the methods is the essence of a call to the specified function with the transfer of all fixed parameters and a list of accumulated “variables” parameters. Since if we accumulate parameters from the head of the list, then before calling the native function, the reverse is called
- the instance (7) of the main class (1) is defined for the functional type (a -> r) - here the value of the types belonging to the specially created class (3) is converted by calling the method (4) to the type of the parameter list elements ( PfValWrap ) , and, further, placing this value in the list
- below (8), instances of class (3) are determined for all the specified types + an instance for the PfValWrap type itself (such a “tautology” is necessary since method (4) is called for conversion)
- and finally the wrapper function itself is declared and defined with a variable number of parameters.
The source code of the Data.Function.Vargs module with comments, as well as the above examples of its use are
here , the documentation in the
haddoc format is available
here and as part of the package. At the moment the package is in the experimental stage from the word "absolutely";)
Perhaps with time I will bring to mind - at a minimum, it is necessary to do the analysis and handling of error situations (invalid or incompatible types), as a maximum:
- implement a generalized scheme and support for polymorphic types in the "parent" functions;
- allow meaningful naming of the created classes and methods, in particular, to enable the transfer of the wrapper function as a parameter to other functions;
- It is possible to consider alternative implementation schemes.
Then, I think, it would not be a shame to put it on
hackage (although there are already decent
HList- type
packages on similar topics).
Useful links on the topic:
- Varargs
- Polyvariadic functions
- Template hakell
- Existential type
- Hlist