Multiple ways of doing things

Discussion of Common Lisp
Post Reply
Jasper
Posts: 209
Joined: Fri Oct 10, 2008 8:22 am
Location: Eindhoven, The Netherlands
Contact:

Multiple ways of doing things

Post by Jasper » Fri May 07, 2010 8:20 pm

For some things i noticed multiple ways of doing things:

Allowing the user to define 'a type of function' this might be some kind of macro that allows for things inside to be defined you have various approaches:

Via methods.

Code: Select all

(defgeneric keyword-macro-gen (name form))
(defmacro def-keyword-macro (name args &body body)
   (with-gensyms (namevar)
     `(defmethod keyword-macro-gen ((,namevar (eql ,name)) (,args list))
         ,@body)))
(defmacro keyword-macro (name &rest form)
   (keyword-macro-gen name form))
Via hash table, or other type of dictionary.(Advantage of being special variable)

Code: Select all

(defvar *keyword-macros* (make-hash-table))
(defmacro def-keyword-macro (name args &body body)
  `(setf (gethash ',name *keyword-macros*) (lambda ,args ,@body)))
(defmacro keyword-macro (name &rest form)
  (apply (gethash name *keyword-macros*) form))
And via renamed function which is a bad idea, because you might accidentally collide with it, a variant is to make a special package for these functions.

Higher order functions vs methods. Lets say you have some thing, and you want to do it in different ways. You could use

Code: Select all

(defgeneric do-something (way args))
(defvar *way*)
(defun do-something-* (args) (do-something *way* args))
And then provide different ways. Or you could pass a function, and pass a different function if you want to do it another way, you could pass this function via special variable. You could pass the way with special var *way*. Which is what the GIL project does to determine the language.

Methods have the nice quality that you can incrementally add onto them. But if you want to alter one of them for one use without changing existing methods, you need a new way, and an rather arbitrary name for it. The higher order function doesn't have this problem, but that is then not extensible. I guess the combination, used like this is the answer i am looking for:

Code: Select all

(lambda (args)
  (if (condition args) (use-own-thing) (use-existing-methods)))
And there is the Functions vs objects thing, and the functions vs macros.

Code: Select all

(defun do-something-before-fun (fun)
  (do-something) (funcall fun))
(defmacro do-something-before (&body body) ;;These are very straight forward enough
  `(do-something-before-fun (lambda () ,@body)))
Macros act like a LAMBDA-without-arguments like that sometimes. Sometimes you want to store something intermediately and 'run' it later, then the superiority from the user perspective of LAMBDA shows. And the question if and when you can trust LAMBDA to inline if you're not using this function. A LAMBDA without arguments can also be stored with a object storing the objects being used, combined with a function that emulates funcall.(you need garbage collection on the objects) Often handy, if you don't have a lib to store functions.

Functions via objects is a much deeper thing, though.

Not sure if this is worth posting. But it's too quiet ;) Anyway, know any other similar things that can be done in a different way? Would it be suitable to have stuff like this in the CLiki?

gugamilare
Posts: 406
Joined: Sat Mar 07, 2009 6:17 pm
Location: Brazil
Contact:

Re: Multiple ways of doing things

Post by gugamilare » Sat May 08, 2010 6:37 am

About the functions versus methods, weblocks has a nice approach in one of those cases. It's been a long time since I saw it, so I don't remember the exact use, but it is something more or less along this way: you define a class with a callback:

Code: Select all

CL-USER> (defclass foo ()
           ((callback :accessor foo-callback :initarg :callback :initform (constantly nil))))
#<STANDARD-CLASS FOO>
CL-USER> (defun call-callback (foo)
           (funcall (foo-callback foo)))
CALL-CALLBACK
This way you can create a callback per-instance, and even change it later. If you want, you can create a subclass of foo and "pretend" the callback is a method using the method created as the accessor:

Code: Select all

CL-USER> (defclass bar (foo)
           ())
#<STANDARD-CLASS BAR>
CL-USER> (defmethod foo-callback ((obj bar))
           (let ((std-callback (call-next-method)))
             (lambda ()
               (format t "Executing callback of ~a~%" obj)
               (funcall std-callback)
               (format t "Execution finished.~%"))))
#<STANDARD-METHOD FOO-CALLBACK (BAR) {24863BC1}>
Example of use:

Code: Select all

CL-USER> (make-instance 'foo :callback (lambda () (print "Hello World!")))
#<FOO {248AE889}>
CL-USER> (call-callback *)

"Hello World!" 
"Hello World!"
CL-USER> (make-instance 'bar :callback (lambda () (print "Hello World!")))
#<BAR {24C21789}>
CL-USER> (call-callback *)
Executing callback of #<BAR {24C21789}>

"Hello World!" Execution finished.
NIL
In general choosing the best approach will depend on the problem you are dealing with at the moment.

dlweinreb
Posts: 41
Joined: Tue Jul 01, 2008 5:11 am
Location: Lexington, MA
Contact:

Re: Multiple ways of doing things

Post by dlweinreb » Sat May 08, 2010 9:17 am

Frankly, I'm having trouble understanding your examples; I don't understand what they're trying to do. I think you need to expand them more, give some examples of USES of the functions and macros you're defining.

However, if your point is just that there are a lot of ways to do things in Common Lisp, yes, absolutely. Common Lisp is put together from several dialects, many of which started as laboratories to try new language ideas. It's by no means minimal.

That saie, there are often ways that are a lot better than others.

One very important principle is to never use a macro when all you need is a function.

-- Dan

Jasper
Posts: 209
Joined: Fri Oct 10, 2008 8:22 am
Location: Eindhoven, The Netherlands
Contact:

Re: Multiple ways of doing things

Post by Jasper » Sat May 08, 2010 1:43 pm

keyword-macro, should at least be fairly obvious, it does exactly what defmacro does, but binds it after (keyword-macro bound-to ....) (it is useless, it's point it to show how it can vary, there are less useless variations) I didn't specify how the last way, going via a renamed function, works, but it is straightforward; you just mess with the symbol-name and re-intern it.
dlweinreb wrote:One very important principle is to never use a macro when all you need is a function.
Easily said; you can do just about everything with functions, but it isn't always readily apparent. And sometimes macros can clean it up a little. Like do-something-before-fun vs do-something-before. I doubt though, that many people would write the first.

LML2 certainly spits in the face of this principle. (Not sure about LML, i don't get how LML2 claims to be able to be faster than LML, i don't see an issue) GIL doesn't, it is all-functions, but not sure if this might slow it down.(I should see if i can get GIL served in the macro-sense too, though perhaps i can use existing definitions)I still haven't written a LML2 vs GIL comparison yet, i probably should.

LML2 could do the 'same thing', without macros. What i will tell you here is similar to how GIL works, but applied to LML. There, I, B, P and such could be functions.(you only have to funcall them after) You can make those return a function from, say P, and calling that function will then write the input. The arguments might be functions, like from B, or strings, which it will just print.

The only real disadvantage to this is that you have to depend on the compile to expand (funcall (lambda ()..)) that effectively ensues. Of course, the compile being able to not expand it could be space saver. And in principle the (funcall (lambda()..))s should be inlinable, just like the macro. (And perhaps one could do optimizations with def-compiler-macro too)

At this point i can't really argue you cannot store intermediate results if they were macros; you could still use the macros inside a lambda. However what if you want to be able to output different results from combine it with the *way* thing, you cannot; the macros can't use that special variable, but the function approach can. In the case of GIL, this is *lang*, the output language, with values like :info(gathers info on text, links, sections, indexing of words), :txt, :html, :latex(undertested, latex can be such a pain in ass), :clg(under development). But i am not entirely satisfied my approach is well-enough thought out, and if it is, it is pointless if people won't use it. (Hence, as i said, i should be writing that comparison, i guess what i wrote here goes part of the way.)

I guess you could do your example the following way:

Code: Select all

;foo is just a function, call-callback is just funcall.
(defun bars-way (a-foo)
  (lambda ()
    (format t "Executing callback of ~a~%" obj)
    (funcall a-foo)
    (format t "Execution finished.~%"))))
And then your example goes:

Code: Select all

(let ((a-foo (lambda () (print "Hello world!"))))
  (funcall a-foo) => first result
  (funcall (bars-way a-foo)) => second result
So an sich i don't really see the point there. However, it is nice to have (type)names on stuff. Guess a named-lambda might do that, if CLOS could see that name. (minding that limitations of clos shouldn't be internalized :) ) Hmm, one could make a macro(this one a bit ugly, name isn't thought out)

Code: Select all

(defmacro clos-identifyable-lambda (name args &body body)
  (let ((class-name (intern (symbol-name name) (find-package :package-just-for-this-purpose))))
     (unless (find-class class-name)
        (defclass ,class-name () ((fun :initarg :fun :type function))))
    `(make-instance ',class-name :fun (lambda ,args ,@body))))
And then define caller-functions.

I should really be trying weblocks, btw. Presumably it does also divide things into pages, and then pages have standard elements. Since this is about different ways of doing things, i can give one for that too. In GIL there are SECTIONs, somewhat like Latex sections. These have a level. (according to header level in HTML, not sure if that is wise :) ) You can set a level to determine if a section should have it's own page, like an html file, so if this level is 'triggered' you have a function/object from the SECTION function, which will be put into a function *handle-page*, which can attach whatever it wants to the page, like a sidebar with menu. (hmm *page-hook* might be better name) (Now am looking at it, the function that is supposed to be stored in *handle-page* should have different arguments though.)

Wow this post seems almost excessively coherent. I mean it goes from dlweinrebs comment about macros to LML2 to how LML implemented with functions is similar to GIL, to how gil:*lang* is an example of *way* and macros don't seem to be able to use special variables like that, to another way of doing gugamilares example, to how the same two different ways may be occuring in weblocks vs gil.(And how i made my little websites.)

gugamilare
Posts: 406
Joined: Sat Mar 07, 2009 6:17 pm
Location: Brazil
Contact:

Re: Multiple ways of doing things

Post by gugamilare » Sat May 08, 2010 6:43 pm

Jasper wrote:I guess you could do your example the following way:

Code: Select all

;foo is just a function, call-callback is just funcall.
(defun bars-way (a-foo)
  (lambda ()
    (format t "Executing callback of ~a~%" obj)
    (funcall a-foo)
    (format t "Execution finished.~%"))))
And then your example goes:

Code: Select all

(let ((a-foo (lambda () (print "Hello world!"))))
  (funcall a-foo) => first result
  (funcall (bars-way a-foo)) => second result
So an sich i don't really see the point there.
That would function in a very different way. You defined one function named bars-way, so all calls to bars-way would do the same thing in every situation. You would need to choose the behavior during compile-time, not runtime. The way I defined things, you can create methods while still having the convenience of dynamic functions. You would need to choose between methods or per-instance functions during compile-time, you can choose that on runtime depending on the object you are working with.

In the end, it works like if you could define per-object methods (instead of just per-class methods). This way you can have both the flexibility of dynamic functions and extendability of methods.

And, yes, you are right, there is another way to do this: define call-callback as a generic function. The only reason weblocks did the thing the way I showed was because in most cases you would call the instance's function, while defining methods would be rare. And in weblocks the objects themselves were not mere function-holders like in my example, they were widgets with many information, and one of the slots holding a function that was called on certain circumstances.

Post Reply