[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

New Issue: SYNTACTIC-ENVIRONMENT-ACCESS



Issue:          SYNTACTIC-ENVIRONMENT-ACCESS
References:     CLtL Chapter 8: Macros,
		Issue MACRO-FUNCTION-ENVIRONMENT,
		Issue GET-SETF-METHOD-ENVIRONMENT,
		Issue COMPILE-FILE-ENVIRONMENT,
		Issue LOAD-TIME-EVAL
Category:       ADDITION
Edit history:	Version 1, 2-Oct-88, Eric Benson
Status:         For internal discussion

Problem description:

 When macro forms are expanded, the expansion function is called with
 two arguments: the form to be expanded, and the environment in which
 the form was found.  The environment argument is of limited utility.
 The only use sanctioned currently is as an argument to MACROEXPAND or
 MACROEXPAND-1 or passed directly as an argument to another macro
 expansion function.  Recent cleanup issues propose to allow it as an
 argument to MACRO-FUNCTION and to GET-SETF-METHOD.

 Implementing the FIND-CLASS and ENSURE-GENERIC-FUNCTION functions of
 CLOS requires the ability to distinguish between environments used
 for compiling to a file from those used for processing in-core, such
 as by EVAL or COMPILE.  Resolution of the LOAD-TIME-EVAL issue may
 also require this information.  This problem has been addressed by
 the recent cleanup issue COMPILE-FILE-ENVIRONMENT.  Also, it has
 proven impossible to write a portable code walker in Common Lisp, due
 to insufficient access to the information contained in environments
 and the inability to augment environments with local function
 definitions.

Proposal (SYNACTIC-ENVIRONMENT-ACCESS:ADD-FUNCTIONAL-INTERFACE):

 The following functions provide information about syntactic
 environment objects.  In all of the functions the argument named ENV
 is a environment, of the sort received by the &ENVIRONMENT argument
 to a macro.  In all cases it is an error to supply an argument which
 is not a syntactic environment.

 Note that we have used the term "syntactic environment" here.  This
 is to distinguish these environments from the environment arguments
 of EVALHOOK and APPLYHOOK.  EVALHOOK-type environments must include a
 mapping from names to values (run-time) as well as the simple
 presence-or-absence information (compile-time) needed for
 MACROEXPAND-type environments.  We consider these to be two entirely
 different kinds of objects and will not deal with EVALHOOK-type
 environments at all in this proposal.

 ENVIRONMENT-TARGET env				[Function]

  This function returns one of the three symbols EVAL, COMPILE or
  COMPILE-FILE, depending on whether the environment is from the
  interpreter, the in-core compiler, or the file compiler.  If
  MACROEXPAND or MACROEXPAND-1 is called directly without supplying
  the environment argument, the environment passed to any expander
  functions will have target EVAL.

 ENVIRONMENT-VARIABLE-KIND variable env		[Function]

  VARIABLE is a symbol.  This function returns one of the following
  values:
	NIL, if the symbol has no visible definition, declaration or
	  binding as a variable.
	PROCLAIM, if the symbol has been proclaimed special.
	DECLARE, if the symbol has been declared special.
	SYMBOL-MACROLET, if the symbol names a symbol macro.
	T, if the symbol has an ordinary lexical binding.

 [Note: these alternatives may have to be changed depending on the
 outcome of the PROCLAIM-LEXICAL issue.]

 Example:

  (DEFMACRO KIND-OF-VARIABLE (VAR &ENVIRONMENT ENV)
    `',(ENVIRONMENT-VARIABLE-KIND VAR ENV))

  (DEFVAR A)

  (DEFUN TEST ()
    (LET (B)
      (LET (C)
	(DECLARE (SPECIAL C))
	(SYMBOL-MACROLET ((D ANYTHING))
	  (LIST (KIND-OF-VARIABLE A)
		(KIND-OF-VARIABLE B)
		(KIND-OF-VARIABLE C)
		(KIND-OF-VARIABLE D)
		(KIND-OF-VARIABLE E))))))

  (TEST) -> (PROCLAIM T DECLARE SYMBOL-MACROLET NIL)
      

 ENVIRONMENT-FUNCTION-KIND function env		[Function]

  FUNCTION is a symbol.  This function returns one of the following
  values:
	NIL, if the symbol has no visible function definition or
	  function binding.
	DEFUN, if the symbol names a global function not overridden by a
	  local binding.
	DEFMACRO, if the symbol names a global macro not overridden by a
	  local binding.
	SPECIAL-FORM-P, if the symbol names a special form.
	FLET, if the symbol has a local function binding, such as
	  created by FLET or LABELS.
	MACROLET, if the symbol has a local macro binding, such as
	  created by MACROLET.

 Example:

  (DEFMACRO KIND-OF-FUNCTION (FUNCTION-NAME &ENVIRONMENT ENV)
    `',(ENVIRONMENT-FUNCTION-KIND FUNCTION-NAME ENV))

  (DEFUN A ())

  (DEFMACRO B ())

  (DEFUN TEST ()
    (FLET ((C ()))
      (MACROLET ((D ()))
	(LIST (KIND-OF-FUNCTION A)
	      (KIND-OF-FUNCTION B)
	      (KIND-OF-FUNCTION QUOTE)
	      (KIND-OF-FUNCTION C)
	      (KIND-OF-FUNCTION D)
	      (KIND-OF-FUNCTION E)))))

  (TEST) -> (DEFUN DEFMACRO SPECIAL-FORM-P FLET MACROLET NIL)

 ENVIRONMENT-BLOCK-P block-name env		[Function]

  BLOCK-NAME is a symbol.  This function returns T if there is a block
  with that name in the environment, otherwise it returns NIL.

 Example:

  (DEFMACRO IS-A-BLOCK (NAME &ENVIRONMENT ENV)
    `',(ENVIRONMENT-BLOCK-P NAME ENV))

  (DEFUN TEST ()
    (LOOP (RETURN (LIST (IS-A-BLOCK TEST)
			(IS-A-BLOCK NIL)
			(IS-A-BLOCK NOT-HERE)))))

  (TEST) -> (T T NIL)
	
 ENVIRONMENT-TAG-P tag-name env		[Function]

  TAG-NAME is a symbol or an integer.  This function returns T if
  there is a tag with that name in the environment, otherwise it
  returns NIL.

 Example:

  (DEFMACRO IS-A-TAG (TAG-NAME &ENVIRONMENT ENV)
    `',(ENVIRONMENT-TAG-P TAG-NAME ENV))

  (DEFUN TEST ()
    (PROG ()
      A
      (RETURN (LIST (IS-A-TAG A)
		    (IS-A-TAG I-HOPE-NOT)))))

  (TEST) -> (T NIL)

 ENVIRONMENT-VARIABLE-TYPE variable env		[Function]

  VARIABLE is a symbol.  This function returns the type specifier
  associated with the variable named by the symbol in the environment,
  or NIL if there is none.  (This is in spite of the fact that NIL is
  a legal type specifier, since NIL has no meaning as a type specifier
  for a variable.)

 Example:

  (DEFMACRO VARTYPE (VAR &ENVIRONMENT ENV)
    `',(ENVIRONMENT-VARIABLE-TYPE VAR ENV))

  (DEFVAR A 1)

  (PROCLAIM '(FIXNUM A))

  (DEFUN TEST ()
    (LET ((B (AREF "X" 0))
	  (C 3))
      (DECLARE (STRING-CHAR B))
      (LIST (VARTYPE A) (VARTYPE B) (VARTYPE C))))

  (TEST) -> (FIXNUM STRING-CHAR NIL)

 ENVIRONMENT-FTYPE function env			[Function]

  FUNCTION is a symbol.  This function returns the type specifier
  associated with the function named by the symbol in the environment,
  or NIL if there is none.

 Example:

  (DEFMACRO FUNTYPE (FUN &ENVIRONMENT ENV)
    `',(ENVIRONMENT-FTYPE FUN ENV))

  (DEFUN A-FUNCTION (X)
    (+ X 3))

  (PROCLAIM '(FTYPE (FUNCTION (FIXNUM) FIXNUM) A-FUNCTION))

  (DEFUN TEST ()
    (FLET ((ANOTHER-FUNCTION (X)
	     (+ X 2)))
      (DECLARE (FTYPE (FUNCTION (INTEGER) INTEGER) ANOTHER-FUNCTION))
      (LIST (FUNTYPE A-FUNCTION) (FUNTYPE ANOTHER-FUNCTION))))

  (TEST) -> ((FUNCTION (FIXNUM) FIXNUM) (FUNCTION (INTEGER) INTEGER))

 ENVIRONMENT-INLINE function env		[Function]

  FUNCTION is a symbol.  This function returns INLINE, NOTINLINE or
  NIL, depending on whether the function named by FUNCTION is declared
  or proclaimed INLINE, declared or proclaimed NOTINLINE, or if no
  such declaration or proclamation has been made.

 Example:

  (DEFMACRO INLINENESS (FUN &ENVIRONMENT ENV)
    `',(ENVIRONMENT-INLINE FUN ENV))

  (PROCLAIM '(INLINE A-SHORT-FUNCTION))
  (DEFUN A-SHORT-FUNCTION () 'SHORT)

  (PROCLAIM '(NOTINLINE Y))
  (DEFUN Y (F)
    ((LAMBDA (G)
       #'(LAMBDA (X)
	   (FUNCALL (FUNCALL F
			     (FUNCALL G G))
		    X)))
     #'(LAMBDA (H)
         #'(LAMBDA (Z)
	     (FUNCALL (FUNCALL F
			       (FUNCALL H H))
		      Z)))))

  (DEFUN A-FUNCTION ())

  (DEFUN TEST ()
    (FLET ((A-LOCAL-FUNCTION ()))
      (DECLARE (INLINE A-LOCAL-FUNCTION)
	       (NOTINLINE A-SHORT-FUNCTION))
      (LIST (INLINENESS A-SHORT-FUNCTION)
	    (INLINENESS Y)
	    (INLINENESS A-LOCAL-FUNCTION)
	    (INLINENESS A-FUNCTION)))

  (TEST) -> (NOTINLINE NOTINLINE INLINE NIL)

 ENVIRONMENT-OPTIMIZE-LEVEL attribute env	[Function]

  ATTRIBUTE is one of the symbols SPEED, SPACE, SAFETY or
  COMPILATION-SPEED.  This function returns an integer between 0 and
  3, which reflects the current settings of the OPTIMIZE proclamation
  or declaration.

 Example:

  (DEFMACRO OPTIMIZE-LEVEL (PROPERTY &ENVIRONMENT ENV)
    `',(ENVIRONMENT-OPTIMIZE PROPERTY ENV))

  (PROCLAIM '(OPTIMIZE (SPEED 3)
		       (SAFETY 0)
		       (SPACE 0)
		       (COMPILATION-SPEED 0)))

  (DEFUN TEST ()
    (LIST (LIST (OPTIMIZE-LEVEL SPEED)
		(OPTIMIZE-LEVEL SAFETY)
		(OPTIMIZE-LEVEL SPACE)
		(OPTIMIZE-LEVEL COMPILATION-SPEED))
	  (LOCALLY (DECLARE (OPTIMIZE (SAFETY 3)
				      (SPEED 0)
				      (COMPILATION-SPEED 3)
				      (SPACE 3)))
	    (LIST (OPTIMIZE-LEVEL SPEED)
		  (OPTIMIZE-LEVEL SAFETY)
		  (OPTIMIZE-LEVEL SPACE)
		  (OPTIMIZE-LEVEL COMPILATION-SPEED)))))

  (TEST) -> ((3 0 0 0) (0 3 3 3))

 The following function provides the ability to create a new
 syntactic environment based on an existing environment:

 AUGMENT-ENVIRONMENT env &KEY variables
			      specials
			      functions
			      macros
			      blocks
			      tags
			      types
			      ftypes
			      inlines
			      optimize		[Function]

  This function returns a new environment augmented with the
  information provided by the keyword arguments.  The arguments are
  supplied as follows:
	VARIABLES is a list of symbols, which shall be visible as
  ordinary lexical variables in the new environment.
	SPECIALS is a list of symbols, which shall be visible as
  special declarations in the new environment.
	FUNCTIONS is a list of symbols, which shall be visible as
  local function bindings in the new environment.
	MACROS is an a-list of symbols and macroexpansion functions.
  The new environment will have local macro bindings of each symbol to
  the corresponding expander function, so that MACRO-FUNCTION or
  MACROEXPAND when given that symbol will use the new expander
  function.
	BLOCKS is a list of symbols, which shall be visible as block
  names in the new environment.
	TAGS is a list of symbols and integers, which shall be visible
  as TAGBODY tags in the new environment.
	TYPES is an a-list of symbols and type specifiers.  The new
  environment will have the type specifier associated with the
  corresponding symbol, as if a type declaration were visible.
	FTYPES is an a-list of symbols and function type specifiers.
  This is analogous to TYPES, except operating in the function
  namespace.
	INLINES is a a-list of symbols and either the symbol INLINE or
  NOTINLINE.  This causes an INLINE or NOTINLINE declaration to be
  visible in the new environment.
	OPTIMIZE is an a-list of any of the symbols SPEED, SAFETY,
  SPACE or COMPILATION-SPEED with integers between 0 and 3.  These
  settings will be returned by the ENVIRONMENT-OPTIMIZE-LEVEL
  function for the new environment.

Rationale:

 This proposal provides a portable interface to environment
 information which must otherwise be obtained by
 implementation-dependent means.  The ENSURE-GENERIC-FUNCTION and
 FIND-CLASS functions of CLOS require the ENVIRONMENT-TARGET function.  A
 useful code walker requires the capability of adding local function
 definitions to an environment.

Cost to Implementors:

 Most implementations already store this information in some form.
 Providing these functions should not be too difficult, but it is a
 more than trivial amount of work.

Cost to Users:

 This change is upward compatible with user code.

Current practice:

 No implementation provides this interface currently.  Portable Common
 Loops defines a subset of this functionality for its code walker and
 implements it on a number of diffent versions of Common Lisp.