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

questions for workshop (long message)



List of questions to be considered at the workshop.



----------------------------------------------------------------
		       Nil, t, and else...

Should (nil) be the same as (()) ?

Should () evaluate to the same thing as '() ?

Should nil evaluate to the same thing as () ?

Should nil evaluate to the same thing as '() ?

Should 'nil evaluate to the same thing as nil ?

Should nil be a symbol?

If nil should be a symbol, should its evaluation semantics be
those of a: 
    static constant
    lexical constant
    lexical variable

Should 't evaluate to the same thing as t ?

Should t be a symbol?

If t should be a symbol, should its evaluation semantics be those
of a:
    static constant
    lexical constant
    lexical variable

Should else be a:
    noise word recognized by certain special forms
    static constant
    lexical constant
    lexical variable

----------------------------------------------------------------
		     Lexical conventions...

Should the following characters be alphabetic?

	[ ] { }

If they are not alphabetic, what are they?

Should symbols be converted to upper case unless slashified?

Should slashification be indicated by backslash for single
characters, as in \" ?

And by enclosure in vertical bars for entire symbols, as in |"| ?

Should abc|def|g be the same symbol as abcdefg?

For the #\ character syntax, which of the following are the
correct choices?

	#\SP		#\SPACE		(ascii " ")
	#\DOT		#\PERIOD	(ascii ".")
	#\LF		#\NEWLINE	(ascii "
						")
	#\CR

	none of the above

Unreadable objects should be printed as
    #{...}
    #<...>
    something else

Is the #!... syntax a good idea for miscellaneous objects?

----------------------------------------------------------------
	  Scope rules for keywords of special forms...

Should the keywords of special forms have global or lexical scope?

Should the keywords of special forms be shadowed by lambda-binding?

Should the keywords of special forms be shadowed by local syntax
definitions?

Should the keyword of a special form be assigned using set! ?

What should happen when the keyword of a special form appears
other than in the car position of a form?

----------------------------------------------------------------
		    Names of special forms...

Should it be

	(lambda x ...)
or
	(mulambda x ...) ?

Should it be

	(lambda (a b . c) ...)
or
	(mumulambda (a b . c) ...)
or
	something else altogether?

For each of the following sets of names of special forms, choose
the better:

	{ labels, letrec }
	{ and, conjunction }			; also { disjunction, or }
	{ define, define!, defrec, defrec! }	; meaning IU's defrec
	{ define, define!, lset }		; for variables
	{ set, set! }
	{ do, step }
	{ begin, block, sequence }
	{ bind, fluid-let }

----------------------------------------------------------------
		    Semantics of constants...

Which of the following should evaluate to themselves?

	nothing
	numbers
	strings
	characters
	everything except symbols and conses

Side effects to quoted constants should
    be ok
    be an error
    signal an error

If side effects to quoted constants are ok, then should
structured constants be freshly consed?

----------------------------------------------------------------
		   Semantics of definitions...

For the define special form, should (define (foo ...) ...) be
equivalent to (define foo (lambda (...) ...)) ?

Should (define ((foo ...) ...) ...) be equivalent to
(define (foo ...) (lambda (...) ...)) ?  Et cetera?

Should

	(define (foo x)
	  (define (bar y) ...)
	  (define (baz z) ...)
	  ...)

be closer in its semantics to

	(define (foo x)
	  (letrec ((bar (lambda (y) ...))
	  	   (baz (lambda (z) ...)))
	    ...))

or to

	(define (foo x)
	  (set! bar (lambda (y) ...))
	  (set! baz (lambda (z) ...))
	  ...)

Assuming the first answer on the previous question, should
embedded definitions be required to come first in a definition,
or should

	(define (foo x)
	  (print (bar 3))
	  (define (bar y) ...)
	  (foo (+ x 1)))

be legal?

If embedded definitions are not required to come first in a
definition, what should their semantics be?

Assuming embedded definitions are required to come first in a
definition, should embedded definitions be allowed in a lambda?
In other words, should

	(mapcar (lambda (x)
		  (define (bar y) ...)
		  (define (baz z) ...)
		  ...)
		...)

be legal?

What value should be returned by a define form?

----------------------------------------------------------------
		 Semantics of fluid variables...

Should
	(let ((x 3))
	  (fluid-let ((x 4))
 	    x))

evaluate to 3 or to 4?

----------------------------------------------------------------
		    Ontology of variables...

Should lexical variables be the only kind of variable,
semantically speaking?

If there are semantically important variables other than lexical
variables, then which of the following kinds of variables should
there be:

	fluid variables
	locale variables
	global variables
	base variables
	other kinds of variables

----------------------------------------------------------------
		  Semantics of special forms...

Cond clauses should have:
    exactly two forms
    two or more forms
    one or more forms

If no cond clause is selected, then:
    the value of the cond expression should be nil
    it should be an error
    an error should be signalled

Each pattern of a case clause should consist of:
    a value (on which eq? is meaningfully defined)
    a value or list of values

If no case clause is selected, then:
    the case expression should return nil
    it should be an error
    an error should be signalled

In the following transcript, what should happen?

>>>(define foo (lambda (n) (if (0? n) t (foo (1- n)))))
foo
>>>(define bar foo)
bar
>>>(bar 3)
t
>>>(define foo (lambda (x) (list x)))
foo
>>>(bar 3)
???				; t or (2)?

Should set (set!) have the setf feature?

The do (step) special form should have:
    exactly one return form
    one or more return forms (all but the last are executed for effect)
    zero or more return forms (if zero, then the value of the
        test is returned)

Should it be permissible to omit update expressions for do (step)
variables?

(begin) should
    return nil
    be an error
    signal an error    

----------------------------------------------------------------
			    Macros...

Does anybody have a syntax and semantics for macros that is good
enough and stable enough that we should consider committing
ourselves to it for a period measured in years?

----------------------------------------------------------------
		       Input and output...

The following programs prompt for input, read input, print output
to a file, and then repeat the cycle.  These examples are
intended to illustrate incompatibilities between the various
implementations in the matter of input and output.

; T (fourth edition)

(define main
  (labels ((get-list
            (lambda ()
              (display "Please give me a list to reverse: " (standard-output))
              (read (standard-input)))))
    (lambda (filename)
      (let ((output (open filename '(out))))
        (do ((list (get-list) (get-list)))
            ((null? list) (close output))
            (print (reverse list) output)
            (newline output))))))

; MIT Scheme (seventh edition)

(define (main filename)
  (define (get-list)
    (princ "Please give me a list to reverse: ")
    (read))
  (define output (open-printer-channel filename))
  (define (loop list)
    (if (null? list)
        (close-channel output)
	(sequence (print (reverse (list)) output))
		  (loop (get-list)))))
  (loop (get-list)))

; Scheme 312 Version -3.00

(define main
  (letrec ((get-list
            (lambda ()
              (printstring "Please give me a list to reverse: ")
              (read))))
    (lambda (filename)
      (let ((output (outfile filename)))
        (do ((list (get-list) (get-list)))
            ((null? list) (close output))
            (print (reverse list) output)
            (newline output))))))

; Scheme 84 Version 0.5

(define main
  (letrec ((get-list
            (lambda ()
              (print "Please give me a list to reverse: ")
              (read))))
    (lambda (filename)
      (let ((output (open filename 'write)))
        (do ((list (get-list) (get-list)))
            ((null? list) (close output))
	    (fluid-let ((output-port output))
              (display (reverse list))
              (newline)))))))

Is the Scheme 84 idea of routing all I/O through fluid
identifiers a good one?

How should the following basic I/O operations be done?

Read an object from the standard input:

	(read (standard-input))
	(read)

Print an object to the standard output, with slashification:

	(print object (standard-output))	; T
	(prin1 object)				; MIT Scheme
	(display object)			; Scheme 84

Print an object to the standard output, without slashification:

	(display object (standard-output))	; T
	(princ object)				; MIT Scheme
	(print object)				; Scheme 84

Print a string to the standard output, without the double quotes.

	(write-string (standard-output) object)	; T
	(princ object)				; MIT Scheme
	(printstring string)			; Scheme 312
	(print object)				; Scheme 84

Write an end of line to the standard output:

	(newline (standard-output))
	(newline)

Read a character from the standard input:

	(read-char (standard-input))		; T
	(tyi)					; MIT Scheme
	(tyi %conin)				; Scheme 312
	(read-char)				; Scheme 84

Peek at a character from the standard input:

	(block0 (read-char (standard-input))
		(unread-char (standard-input)))
	(peekch)
	(tyipeek)

Write a character to the standard output:

	(write-char (standard-output) char)	; T
	(tyo char)				; MIT Scheme
	(tyo char %conout)			; Scheme 312

Open a file for input:

	(open filename '(in))			; T
	(open-reader-channel filename)		; MIT Scheme
	(infile filename)			; Scheme 312
	(open filename 'read)			; Scheme 84

Open a file for output:

	(open filename '(out))			; T
	(open-printer-channel filename)		; MIT Scheme
	(outfile filename)			; Scheme 312
	(open filename 'write)			; Scheme 84

Close an open file:

	(close object)
	(close-channel channel)

Test for end of file on an open input file:

	(block0 (eof? (read-char stream))
		(unread-char stream))
	(let ((eof '(eof)))
	  (eq? (peekch channel eof) eof))
	(=? (tyipeek port) -1)

Test if an object that has been read is the end of file:

	(eof? object)
	(eq? object EOF)

Pretty print an object on the standard output:

	(pretty-print object (standard-output))	; T
	(pp object)				; MIT Scheme
	(pretty-print object)			; Scheme 312

Pretty print (some approximation to) the definition of a
procedure on the standard output:

	(pp name-of-procedure)			; T
	(pp procedure)				; MIT Scheme
	(pretty '(name-of-procedure))		; Scheme 312, Scheme 84

Generate wallpaper:

	(transcript-on filename)		; T, Scheme 84
	(photo filename)			; MIT Scheme

Stop generating wallpaper:

	(transcript-off)			; T, Scheme 84
	(tofu)					; MIT Scheme

----------------------------------------------------------------
		      Naming conventions...

Are the T naming conventions for procedures acceptable?

Should the names of variables whose values are not procedures or
whose value is intended to change begin and end with asterisks,
with t and nil as exceptions to the rule?

----------------------------------------------------------------
			  Procedures...

Should various sorts of procedures be distinguishable at run
time?  (E.g. primitives, system functions, continuations,
fluid-closures, closures, engines.)

Which is the better name?

	{ procedure?, proc?, applicable? }

----------------------------------------------------------------
			   Numbers...

Should various sorts of numbers be distinguishable at run time?
(E.g. fixnums, bignums, ratios, floats, complexes.)

Which is the better name?

	{ integer?, fix? }
	{ -1+, 1- }
	{ subtract1, sub1 }
	{ div, quotient, / }
	{ =, =? }
	{ <, <? }
	{ >, >? }
	{ >=, >=? }
	{ <=, <=? }
	{ =0?, 0?, =0 }
	{ <0?, <0 }
	{ >0?, >0 }
	{ N=0?, <>0?, <>0, !=0?, !=0, not=0?, nonzero? }
	{ atan, arctan }
	{ atan2, atan }		; two arguments
	{ ->integer, fix }
	{ ->float, float, floor, ceiling, truncate, round }

Should trigonometric functions take their arguments in radians?

----------------------------------------------------------------
			   Symbols...

Which is the better name?

	{ symbol->string, pname }
	{ concatenate-symbol, concat }
	{ alphaless?, alpha< }
	{ generate-symbol, generate-uninterned-symbol, gensym }
	
----------------------------------------------------------------
			    Lists...

Which is the better name?

	{ pair?, cons? }
	{ proper-list?, list? }		; true if cdr of last cons is nil
	{ alikev?, equal? }
	{ nth, list-ref }
	{ nthcdr, list-tail }
	{ lastcdr, last, last-pair }
	{ map, mapcar }
	{ walk, mapc }

Taking the car or cdr of nil should:
    yield nil
    be an error
    signal an error

atom? is true of what things?

----------------------------------------------------------------
			   Strings...

Which is the better name?

	{ list->string, list-to-string }
	{ string->list, string-to-list }

----------------------------------------------------------------
			   Vectors...

Which is the better name?

	{ list->vector, list-to-vector }
	{ vector->list, vector-to-list }
	{ vector-elt, vector-ref }
	{ vset, vector-set! }
	{ vector-length, vector-size }