From: ············@mediaone.net
Subject: Re: Shelby has a good idea
Date: 
Message-ID: <367157bc.133056455@news.ne.mediaone.net>
Tim Bradshaw <···@aiai.ed.ac.uk> wrote:

>This is what we want!  Lisp for *children*.  Get them while they're
>young, and you've got them forever.

I've been teaching my 7-yr son lisp as well.  Lisp has been very nice as an
introductory language for him.  Along the vein of "so how do you suppose we ask
for the length of a list, why, we call the LENGTH function".  Makes for fairly
seamless instruction.  

I'm excited to see how excited he is, compared to all those teenagers and adults
who would look at the same thing and wonder why on earth anyone would want to
learn this stuff.  He likes the "power" of telling the computer what to do from
a REPloop. 

  Which brings me to my next question:

Any suggestions for program samples or texts for reaching young learners to
program?  Lisp-based would be nice, but I can translate the lesson if i have to.
It's interesting to observe the process.  Understanding zero-based indexing took
no time for him, 'parameters' are considerably harder to explain however.

By the way, my introductory program for him was the "Silly sentence" program,
where he just designs some lists of nouns, verbs, etc, and uses the random
function to paste together something fun.  Nothing like a problem domain which
engages the age group, and generated sentences like "Grandma farts slowly"
certainly achieved that!  Since he's studying some parts of speech in the 2nd
grade, it all fits nicely.

I'm not up on things like Turtle/logo, are there any good graphical instruction
environments which people recommend for Windows?  Any things which will run in
the Franz (ACLPC, ACL5) lisps?

D. Tenny
············@mediaone.net - no spam please

From: Scott Fahlman
Subject: Re: Shelby has a good idea
Date: 
Message-ID: <ydvhjiiizf.fsf@CLYDE.BOLTZ.CS.CMU.EDU>
············@mediaone.net writes:

> I've been teaching my 7-yr son lisp as well.  Lisp has been very
> nice as an introductory language for him...  Any suggestions for
> program samples or texts for reaching young learners to program?
> Lisp-based would be nice, but I can translate the lesson if i have
> to.

If you want to teach Common Lisp rather than Logo -- no need to change
to a more powerful language later, since CL is already the most
powerful language for hard, AI-flavored tasks -- I would recommend
Dave Touretzky's book, "Common Lisp: A Gentle Introduction".  It was
written to teach programming to computer-phobic college humanities
majors, so a bright computer-philic seven-year-old with soem parental
help should find it just about right.  :-)

Good luck,
Scott

===========================================================================
Scott E. Fahlman                        Internet:  ···@cs.cmu.edu
Principal Research Scientist            Phone:     412 268-2575
Department of Computer Science          Fax:       412 268-5576
Carnegie Mellon University              Latitude:  40:26:46 N
5000 Forbes Avenue                      Longitude: 79:56:55 W
Pittsburgh, PA 15213                    Mood:      :-)
===========================================================================
From: Wade Humeniuk
Subject: Re: Shelby has a good idea
Date: 
Message-ID: <36717689.0@news.cadvision.com>
>Any suggestions for program samples or texts for reaching young learners to
>program?  Lisp-based would be nice, but I can translate the lesson if i
have to.
>It's interesting to observe the process.  Understanding zero-based indexing
took
>no time for him, 'parameters' are considerably harder to explain however.
>
>I'm not up on things like Turtle/logo, are there any good graphical
instruction
>environments which people recommend for Windows?  Any things which will run
in
>the Franz (ACLPC, ACL5) lisps?
>

Here is something that runs on ACL for Windows.  Its a simple version of
Ladybug Graphics.  If you want the ladybug and aphid pixmaps send me mail
and I will attach them.  The ladybug graphic has a white border around it
so that a move will erase the previous drawing.

You will have to modify the code for your location and such.  But I think it
is
pretty straight forward.  You can do things like

(setf lady1 (create ladybug))
(move lady1 ahead 100)
(turn lady1 left)
(turn lady1 south)
(move lady1 right 20)

etc. etc.

You have type these commands in the top level listener.

;;  Start of YBBIL.LSP.  Kid's Ladybug Graphics learning package.
;;  YBBIL is named after my daughter LIBBY.
;;  Written for Allegro Common Lisp for Windows (I think version 4.1)
;;  Wade Humeniuk
;;  ········@cadvision.com

(cl:defpackage "YBBIL" (:use "COMMON-LISP")
                       (:nicknames "YBB")
                       (:export "PAD" "CREATE" "YBBIL-PAD" "MAKE-YBBIL-PAD"
                                "BITMAP" "DRAW-IN-DEVICE" "MAKE-BITMAP"
                                "NORTH" "SOUTH" "EAST" "WEST" "UP" "DOWN"
                                "RIGHT" "LEFT" "FORWARD" "BACKWARD"
    "FORWARDS" "BACKWARDS" "AHEAD" "AFT"
    "PORT" "STARBOARD" "AROUND"
    "ANIMATRON" "CURRENT-POSITION"
    "CURRENT-DIRECTION"
    "PAD" "DRAW" "HIDE" "SHOW" "MOVE"
    "TURN" "PAUSE" "LADYBUG" "APHID" "REPEAT" "TEST"))

(cl:in-package :ybbil)

(defvar *ybbil-pad* nil)
(defconstant *ybbil-load-path* "d:\\user\\wade\\kidish\\")

;; Local Macros
(defmacro repeat (times . forms)
  (let ((count (gensym)))
    `(cl:do ((,count 1 (+ ,count 1)))
     ((>= ,count ,times))
     ,@ forms)))

(defclass ybbil-pad (cg:bitmap-window)
    ())

(defun make-ybbil-pad ()
   (if (cg:windowp *ybbil-pad*)
      *ybbil-pad*
      (setq *ybbil-pad*
        (cg:open-stream 'ybbil-pad cg:*lisp-main-window* :io
         :title "Ybbil"
         :user-scrollable nil
         :window-interior (cg:make-box 350 40 750 440)
         :user-movable t
         :user-resizable t
         :user-closable t
         :user-shrinkable nil
         :background-color cg:white))))

(defun clear ()
  (if (cg:windowp *ybbil-pad*)
      (acl:clear-page *ybbil-pad*)))

;; LADYBUG GRAPHICS

(defclass bitmap ()
  ((pixmap :accessor pixmap
    :initarg :pixmap
    :initform nil)
   (texture-info :accessor texture-info
                 :initarg :texture-info
          :initform nil)
   (bitmap-file-type :reader file-type
       :initarg :file-type :initform :bitmap)
   (bitmap-file :reader file :initarg :file :initform nil)))

(defmethod bounding-box ((bm bitmap))
  (cg:make-box-relative 0 0 (cg:texture-info-width (texture-info bm))
       (cg:texture-info-height (texture-info bm))))

(defmethod draw-in-device ((device cg:drawing-and-filling-device)
      (bm bitmap) (pos position))
  (cg:copy-pixels-to-stream device
       (pixmap bm) (texture-info bm)
       (cg:box-move (bounding-box bm) pos)
       (bounding-box bm)
       cg:po-replace))

(defmethod initialize-instance :after ((bm bitmap) &rest initargs)
  (if (file bm)
      (let ((pm nil)
     (ti nil))
 (cl:multiple-value-setq
  (pm ti)
  (case (file-type bm)
        ((:lisp) (cg:load-lisp-pixmap (file bm)))
        ((:bitmap) (cg:load-pixmap (file bm)))))
 (setf (pixmap bm) pm)
 (setf (texture-info bm) ti))))

(defun make-bitmap (file)
   (make-instance 'bitmap :file file))

;; Absolute directions expressed as, hopefully, unit vectors
(defconstant east (cg:make-position 1 0))
(defconstant north (cg:make-position 0 -1))
(defconstant west (cg:make-position -1 0))
(defconstant south (cg:make-position 0 1))
(defconstant up north)
(defconstant down south)

;; Relative directions expressed in angle of rotation from
;; current position
(defconstant right 90)
(defconstant left -90)
(defconstant forward 0)
(defconstant backward 180)
(defconstant forwards 0)
(defconstant backwards 180)
(defconstant ahead forwards)
(defconstant aft backwards)
(defconstant port left)
(defconstant starboard right)
(defconstant around backward)

(defclass animatron ()
    ((animatron-position-current :accessor animatron-position
     :initarg :initial-position
                                 :reader current-position
                                 :writer set-current-position
     :initform (cg:make-position 0 0)
     :type position)
     (animatron-direction-current :accessor animatron-direction
      :initarg :initial-direction
                                  :writer set-current-direction
                                  :reader current-direction
      :initform east
      :type position)
     (pad :accessor pad
   :initarg :pad
   :initform *ybbil-pad*)
     (bitmap-alist :accessor bitmap-alist
     :initarg :bitmap-alist :initform nil)))

(defmethod current-bitmap ((tron animatron))
  (let ((bitmap-for-direction
  (assoc (animatron-direction tron)
  (bitmap-alist tron) :test #'cg:position=)))
    (if bitmap-for-direction
 (cdr bitmap-for-direction)
      nil)))

(defmethod draw-at ((tron animatron) (pos position))
   (draw-in-device (pad tron) (current-bitmap tron) pos))

(defmethod draw ((tron animatron))
  (draw-at tron (current-position tron)))

(defmethod hide ((tron animatron))
   (cg:set-fill-texture (pad tron) cg:white-texture)
   (cg:fill-box (pad tron)
     (cg:box-move (bounding-box (current-bitmap tron))
    (current-position tron))))

(defmethod show ((tron animatron))
   (draw tron))

(defmethod initialize-instance :after ((tron animatron) &rest initargs)
  (draw tron))

(defmethod move ((tron animatron) (direction position) steps)
   (repeat steps
     (cg:nposition+ (animatron-position tron) direction)
     (draw tron)))

(defmethod move ((tron animatron) (direction integer) steps)
   (move tron (cg:position-rotate (current-direction tron) direction)
steps))

(defmethod turn ((tron animatron) (new-direction position))
   (hide tron)
   (set-current-direction new-direction tron)
   (draw tron))

(defmethod turn ((tron animatron) (new-direction integer))
   (turn tron (cg:position-rotate (current-direction tron) new-direction)))

;; I am unaware of a better way to pause.
(defun pause (msec)
  (let ((start (get-internal-real-time)))
    (acl:while (< (- (get-internal-real-time) start) msec)
      (cg:process-pending-events))))

(defconstant ladybug0 (make-bitmap "d:\\user\\wade\\kidish\\lady0.bmp"))
(defconstant ladybug90 (make-bitmap "d:\\user\\wade\\kidish\\lady90.bmp"))
(defconstant ladybug180 (make-bitmap "d:\\user\\wade\\kidish\\lady180.bmp"))
(defconstant ladybug270 (make-bitmap "d:\\user\\wade\\kidish\\lady270.bmp"))

(defclass ladybug (animatron)
  ((bitmap-alist :initform
   `((,east . ,ladybug0)
     (,north . ,ladybug90)
     (,west . ,ladybug180)
     (,south . ,ladybug270)))))

(defconstant aphid0 (make-bitmap "d:\\user\\wade\\kidish\\aphid0.bmp"))
(defconstant aphid90 (make-bitmap "d:\\user\\wade\\kidish\\aphid90.bmp"))
(defconstant aphid180 (make-bitmap "d:\\user\\wade\\kidish\\aphid180.bmp"))
(defconstant aphid270 (make-bitmap "d:\\user\\wade\\kidish\\aphid270.bmp"))

(defclass aphid (animatron)
    ((bitmap-alist :initform
       `((,east . ,aphid0)
         (,north . ,aphid90)
         (,west . ,aphid180)
         (,south . ,aphid270)))))

(defmacro create (name animatron-class . initargs)
   `(defparameter ,name (apply #'make-instance (list ',animatron-class
,@initargs))))

(defun test ()
   (let ((lady (make-instance 'ladybug
         :initial-position (cg:make-position 50 50)
         :initial-direction south))
         (kady (make-instance 'ladybug
         :initial-position (cg:make-position 300 300)
         :initial-direction north)))
      (clear)
      (repeat 100
       (repeat 10
        (move lady forward 20)
        (move kady forward 20))
       (pause 500)
       (turn lady left)
       (turn kady left))
      (hide lady)
      (hide kady)))