Common Lisp - 笔记整理 (草稿)

Table of Contents

1 准备

  • 实现
    • CCL
    • SBCL
  • 编辑器 : Emacs
    • Slime
    • lispy

2 开始

Live 活着的

  • 交互能力 实时修改 快速反馈
  • REPL : 读 求值 打印 循环

表示 和 操作

  • 表示
    • 数字 : 1 -1 3.14159 3/2 #b1001 #o777 #xAC53
      • 12345678901012345678902012345678903012345678901
    • 字符串 : "我们彼此看着对方" "Hello World"
      • 字符 : ##\云 (编码: ASCII Unicode UTF-8)
      • "Hello" == #(#####)
    • 真值 : t nil
      • 非nil 都为真
    • 名字(变量) : 关联一个对象
      • 比起使用变量这个术语 我更喜欢用名字或标签
      • 变量和常量 : 可不可以修改 名字与对象的关联 (是否可以把名字用到别的对象上)
      • 符号
    • 过程 : 函数
      • 匿名函数(深藏功与名) : lambda
      • 关联一个名字 : defun
      • 返回值
    • 控制流程 : 顺序 条件分支if cond 循环
    • 复杂对象 : list array hash-table structure class(CLOS)
  • 操作
    • 数学计算 : + - * / sin
    • 等等

3 自身

  • 语法 : S-表达式
    • 原子 (列表以外的)
    • 列表 (括号括起来的)
  • 求值
    • atom => self (自求值 : 返回自身)
      • Symbol => value (: 符号引用对象)
        • t nil :keyword => self
    • list (根据第一个元素)
      • function 函数 : 参数从左到右先求值 再传入函数求值
      • special 特殊形式 : 各自特定的规则
        • 不求值 : quote
      • macro 宏 : 参数不求值

3.1 Comment 注释

;;;; File header

;;; Paragraph
(defun foo (x)
  ;; Follow multiple lines
  (bar)
  (ted i)                             ; Current line
  (baz))

#| Multiple lines
    #|
       Nested
    |#
|#

3.2 Reader & Printer 读取器 和 打印器 :?:

3.3 Quote 引用

  • Homoiconicity 同象性 : 程序 & 数据
  • 引用 : quote (sugar: ')
    • 符号作为数据 : 'foo
    • 程序(列表)作为数据 : '(+ 1 2)
    • Ex.

      ;; (quote ...) == '(...)
      '(x y z)                  ;-> (X Y Z)
      (quote x)                 ;-> X
      (list 'quote 1)           ;-> '1  ;== (quote 1)
      (list 'quote 'y)          ;-> 'Y
      
  • 反引用
    • backquote (sugar: `)

      `(x (+ 3 3) y)  ;-> (X (+ 3 3) Y)
      `(x ,(+ 3 3) y) ;-> (X 6 Y)
      `(x (x y z))    ;-> (X (X Y Z))
      `(x ,@'(x y z)) ;-> (X X Y Z)
      `(x . ,'(x y z)) ;-> (X X Y Z)
      

3.4 Special 特殊操作符

  • 25个
  • 词法环境 : let let* setq progv
  • 函数 : function labels flet
  • 宏 : macrolet symbol-macrolet
  • 控制流
    • if
    • progn
    • block return-from return
    • tagbody go
    • catch throw
    • unwind-protect
  • 多值 : multiple-value-call multiple-value-prog1
  • 求值 : quote eval-when load-time-value
    • load-time-value : 若编译则只求值一次
  • 类型 : locally the

3.5 Type System 类型系统

  • 动态类型 : 运行时检测 名字 可关联 任何类型的对象
  • 强类型 : 所有的类型错误都会被检测
  • Class 可作为 Type 使用 (相反不可) : 定义 class 时 会自动定义一个同名的 Type
  • 名字(变量)没有类型 只有值才有类型

操作

  • Case : typecass ctypecase etypecase
  • Determining : type-of

    (type-of 'x)  ;-> SYMBOl
    (type-of '(+ 1)) ;-> CONS
    (type-of nil) ;-> NULL
    
  • Check : check-type typep

    (defun my-sqrt (x)
      (check-type x (real 0)) 
      (sqrt x))  
    (my-sqrt -9) ;; Error: TYPE-ERROR
    
    (defun my-sqrt (list)
      (check-type (first list) (real 0) "a non-negative real number")
      (sqrt (first list)))
    

3.5.1 Type Specifier 类型标识符 :?:

3.6 Symbol 符号

  • 符号的内部结构
    • name : symbol-name
    • package : symbol-package := home package | nil(uninterned)
    • value : symbol-value
    • function : symbol-function
    • plist : symbol-plist

      (setf (get 'a 'ss) 1)
      (symbol-plist 'a) ;;-> (SS 1)
      (get 'a 'ss) ;-> 1
      
  • 命名
    • 大小写不敏感 保持大小写使用"||"包围
    • 不能
      • 只有: 数字 或 "."
      • 含有: Whitespace [()"'`,:;\|]
    • 使用不被允许的字符
      • Escape : \
      • Surrounding : ||

        |lisp 3|
        | | 
        |abc|      
        

3.7 Name 名字

  • 基于: 符号
  • 约定
    • 全局变量 : name
    • 常量 : name
    • 特别低层的函数 : 前缀 %|%%
    • 分隔名字 : -
    • 谓词 : 后缀 p|-p
  • 函数和变量 使用不同 名称空间

    (defun fn () 2)
    (defparameter fn 1)
    fn ;-> 1
    (fn) ;-> 2
    #'fn ;-> #<Compiled-function FN #x3020033714EF>
    
    (symbol-value 'fn) ;-> 1
    (symbol-function 'fn) ;-> #<Compiled-function FN #x3020033714EF>
    

3.8 Package

  • 包 : 符号的集合 用于名称空间
  • 创建 : make-package defpackage

    ;; (make-package name &key nicknames use)
    (make-package :package-test) ;-> #<Package "PACKAGE-TEST">
    (make-package #:package-test) ;-> #<Package "PACKAGE-TEST">
    (make-package 'package-test) ;-> #<Package "PACKAGE-TEST">
    (make-package "package-test") ;-> #<Package "package-test">
    (make-package '|package-test|) ;-> #<Package "package-test">
    
    (make-package :my-package :nicknames '(:myp "myp"))
    (make-package "my-package" :use '(:cl))
    
    ;; (defpackage ...)
    (defpackage :my-package
      (:nicknames :myp "my-pkg")
      (:use :cl)
      (:shadow #:car #:cdr)
      (:shadowing-import-from :cl #:cons)
      (:import-from :pkgname #:bye)
      (:intern #:hi)
      (:export #:egg #:milk))
    
  • 删除 : delete-package

    (delete-package :my-pkg)
    
  • 改变当前包 : in-package

    (in-package :my-pkg)
    
  • 重命名 : rename-package

    ;; (rename-package :oldname :newname '(:nickname))
    (make-package :temp :nicknames '(:tp))
    (rename-package :temp :temps) ;->  #<PACKAGE "TEMPS">
    (package-name :temp)          ;-> There is no package named "TEMP" .
    (package-nicknames :temps) ;->  ()
    
  • Use | Import | Export

    ;; use-package : inherit all external symbol
    (use-package :cl)
    (use-package :cl :temp) ;; in TEMP use CL
    (unuse-package :cl)
    
    ;; import : add symbol to internal of package
    (import 'cl:car (make-package :temp))
    
    ;; shadowing-import
    (shadowing-import 'cl::car :temp) 
    
    ;; export | unexport
    (export 'temp::temp-sym :temp)
    (unexport 'temp::temp-sym :temp)
    
  • Intern : intern unintern

    ;; intern : enter symbol named string into package
    (intern "Never-Before") ;->  |Never-Before|, NIL
    (intern "Never-Before") ;->  |Never-Before|, :INTERNAL 
    (intern "NEVER-BEFORE" "KEYWORD") ;->  :NEVER-BEFORE, NIL
    (intern "NEVER-BEFORE" "KEYWORD") ;->  :NEVER-BEFORE, :EXTERNAL
    (intern "AAAA") ;-> AAAA
    (intern "aaa") ;-> |aaa|
    
    ;; unintern
    (unintern "Never-Before") ;-> T
    (find-symbol "Never-Before") ;-> NIL, NIL 
    
  • 屏蔽符号 : shadow

    ;; 屏蔽在当前包
    (shadow 'sym) 
    
    ;; 屏蔽其它包中导入的 
    (shadow 'pkg:sym)
    
    ;; 在:pkg包中屏蔽符号
    (shadow 'sym :pkg)  
    
  • 包信息 : package list-all-packages find-package package-[name nicknames]

    ;;; Packge
    ;; Name
    (package-name :cl) ;-> "COMMON-LISP"
    ;; Nickname 
    (package-nicknames :common-lisp) ;-> ("CL")
    
    ;; All registered package
    (list-all-packages)
    ;; Current-pkg 
    (print *package*)
    ;; find-package
    (find-package :cl) ;-> #<PACKAGE "COMMON-LISP">
    
  • 包与包关系 : package-[use used-by]-lisp

    ;; Use | Used package
    (make-package :new-pkg :use '(:my-pkg))
    (package-use-list :new-pkg) ;-> (#<Package "MY-PKG">)
    (package-used-by-list :my-pkg) ;-> (#<Package "NEW-PKG">)
    
  • 包内符号

    ;;; Symbol
    ;; (find-symbol string &optional package)
    (find-symbol "CAR" :cl-user) ;-> CAR, :INHERITED
    ;; find-all-symbols : searche every registered package
    (find-all-symbols '+) ;-> (:+ + XT3.OOP::+)
    ;; Symbol in package
    (symbol-package 'car) ;-> #<Package "COMMON-LISP">
    ;;; package-shadowing-symbols
    (package-shadowing-symbols (make-package :temp)) ;-> ()
    
  • 迭代包内符号 : loop do-[all external]-symbols

    ;;; List all Symbol in Package
    ;; loop
    (loop for s
       being each external-symbol|symbol|present-symbol of :cl
       count s)
    
    ;; do-symbols
    (do-symbols (s (find-package :cl-user))
      (print s))
    ;; do-external-symbols
    (do-external-symbols (s (find-package :cl-user))
      (print s))
    ;; do-all-symbols : iterates on every registered package
    (let ((lst ()))                                                     
      (do-all-symbols (s lst)
        (when (eq (find-package :temp) (symbol-package s))
          (push s lst)))
      lst)
    

3.9 Assignment 赋值

  • setf : (setf name|place value)

    (setf *x* (list 1 2 3))
    (let ((n 3))
      (setf n 33))
    
    ;; Place
    (setf (car *x*) 9)
    ;; *x* = (9 2 3)
    
    ;; 多个赋值
    (let ((a 1)
          (b 2))
      (setf a 5
            b a)
      (list a b))
    ;;-> (5 5)
    
  • setq psetq(平行) : (setq name value)

    (let ((a 1) (b 2))
      (setq a 3 b (+ a 1))
      (list a b))
    ;;-> (3 4)
    
    (let ((a 1) (b 2))
      (psetq a b b a)
      (list a b))
    ;;-> (2 1)
    
  • set : (set symbol value)

    (set 'x 1)
    x ;;-> 1
    
    (let ((a 3))
      (set 'a 1)
      a)
    ;;-> 3
    
  • multiple-value-setq

    (let (a b c)
      (multiple-value-setq (a b c) (values 1 2))
      (list a b c) ;-> (1 2 NIL)
      (multiple-value-setq (a b) (values 4 5 6))
      (list a b c) ;-> (4 5 NIL)
      )
    
  • rotatef shiftf (修改宏 参数只求值一次)

    (setf a 0)
    (setf b 1)
    (rotatef a b)
    a ;-> 1
    b ;-> 0
    
    (shiftf a b 10)
    a ;-> 0 
    b ;-> 10
    

3.9.1 Setf Place

  • 定义 : (setf name) | defsetf | define-setf-expander

    ;;; (setf name) 
    ;; 定义 : (defun (setf name) (new-val obj))
    ;;-| Can #'(setf name)
    ;; 调用 : (setf (name obj) new-val)
    

3.10 Macro 宏

  • 定义 : defmacro

    (defmacro name (parameter*)
      "Optional doc string"
      body-form*)
    
    ;; &body : 与&rest等价 但许多开发环境会根据其修改宏缩进
    ;; &whole
    (defmacro tfun (&whole form &rest body) `(list ',form ,@body))
    (tfun 1 2 3) ;-> ((TFUN 1 2 3) 1 2 3)
    
    ;; Destructuring parameter list 解构形参列表
    (defmacro macro (vars &body body) ...)
    (defmacro macro ((a b c) &body body) ...)
    
  • 展开 : macroexpand-1(一层) macroexpand
  • !! 注意
    • 多重求值问题
    • 变量定义顺序
    • 重名 (gensym)

3.11 Feature 特性

  • 用于区分运行环境
*features*

;; #+|- | #+|-(and|or|not ..)

;;; a in impl A, b in impl B
(cons #+a "more" #-b "little" x) 
;; in impl A ;-> (cons "more" x)
;; in impl B ;-> (cons "little" x)

3.12 Error :?:

3.13 Debug :?:

3.14 Help

  • apropos

    ;; opt second argument : limit search in particular package
    (apropos "MAP" :cl)
    ;;..-> MAPC, Def: FUNCTION
    
  • describe

    (describe 'length)
    ;;-> Symbol: LENGTH
    ;;-> Function
    ;;-> EXTERNAL in package: #<Package "COMMON-LISP">
    ;;-> Print name: "LENGTH"
    ;;-> Value: #<Unbound>
    ;;-> Function: #<Compiled-function LENGTH #x34C39B6>
    ;;-> Arglist: (SEQUENCE)
    ;;-> Plist: (:ANSI-CL-URL "fun_length.html")
    
    (describe "LENGTH")
    ;;-> "LENGTH"
    ;;-> Type: (SIMPLE-BASE-STRING 6)
    ;;-> Class: #<BUILT-IN-CLASS SIMPLE-BASE-STRING>
    ;;-> Length: 6
    ;;-> 0: #\L
    ;;-> 1: #\E
    ;;-> 2: #\N
    ;;-> 3: #\G
    ;;-> 4: #\T
    ;;-> 5: #\H
    
    (describe 3)
    ;;-> Fixnum: 3
    ;;-> Scientific: 3.00E+0
    ;;-> Log base 2: 1.5849625
    ;;-> Binary: #b11
    ;;-> Octal: #o3
    ;;-> Decimal: 3.
    ;;-> Hex: #x3
    ;;-> Roman: III
    ;;-> Character: #\ETX
    ;;-> Abbreviated: 3
    ;;-> As time: 8:00:03 Monday, 1 January, 1900
    ;;-> MOST-POSITIVE-FIXNUM: 1152921504606846975.
    ;;-> ; No value
    
  • inspect : 交互型describe

    (defparameter *thing*
                  (vector :lp (list 20 "Hotels") 1971))
    (inspect *thing*)
    ;;-:
    1 ;: go one level deeper
    (list $ $$) ;: $ $$ $$$ work like * 
    (setf (first $) 200)
    :s 0 #\M  ;: :s setf
    :q
    
  • documentation

    (documentation 'length 'function)
    ;;-> "returns the number of elements in sequence."
    
    (defun docstring ()
      "This is docstring."
      t)
    (documentation 'docstring 'function)
    ;;-> "This is docstring."
    
    • second argument
      • 'variable : defvar, defparameter, defconstant
      • 'function : defun, defmacro, special form
      • 'structure : defstruct
      • 'type : deftype
      • 'setf : defsetf
      • 'compiler-macro : define-compiler-macro
      • 'method-combination : define-method-combination
      • t : returned depends upon type of first argument.

4 表示

4.1 Number 数

4.1.1 Rational 有理数

  • Literal

    ;;; Integer
    123         ;-> 123
    -123        ;-> -123
    1.          ;-> 1
    15511210043330985984000000 ; probably a bignum
    
    #b100       ;-> 4
    #o777       ;-> 511
    #xD         ;-> 13
    ;; #nr : base 2~36
    #36rABC     ;-> 13368 
      
    
    ;;; Ratio
    3/7         ;-> 3/7
    4/6         ;-> 2/3
    6/3         ;-> 2
    #b1010/1011 ;-> 10/11  
    
  1. Integer 整数
    • 类型 : fixnum bignum

      (typep 1 'fixnum) ;-> t
      (typep (1+ most-positive-fixnum) 'bignum) ;-> t
      
    • 整数大小无限制 : 内部会自动在必要时分配存储 从而转换到大数表示
    • fixnum范围

      (list most-positive-fixnum
            most-negative-fixnum)
      ;; ( 1152921504606846975
      ;;  -1152921504606846976)
      
      (expt 2 60) ;-> 1152921504606846976
      (expt 2 61) ;-> 2305843009213693952
      
  2. Ratio 比值
    • Rational canonicalization 规约化 : 6/3 -> 2, 12/6 -> 4/3
    • GET : numerator denominator

      (numerator 3/5) ;-> 3
      (denominator 3/5) ;-> 5
      

4.1.2 Float 浮点数

  • 实现依赖 [CCL]
  • 类型 (precisions, sizes) : s(short) f(float) d(double) l(long)
  • Literal

    1.0      ;-> 1.0
    1e0 1s0 1f0      ;-> 1.0
    1d0      ;-> 1.0d0
    
    ;; float
    0.123    ;-> 0.123
    .123     ;-> 0.123
    123e-3   ;-> 0.123
    123E-3   ;-> 0.123
    0.123e20 ;-> 1.23e+19
    1.33232332329032 ;-> 1.3323233
    
    ;; doble
    123d23   ;-> 1.23d+25
    1.33232332329032d0 ;-> 1.33232332329032D0
    
    2.0/3    ; Error: 2.0/3 被当作一个 symbol name
    2/3.0    ;-> 0.6666667
    
  • 范围 (格式:m-s-f) : most-[positive|negative]-long-float

    (list most-negative-short-float
          most-positive-short-float
          most-negative-single-float
          most-positive-single-float
          most-negative-double-float
          most-positive-double-float
          most-negative-long-float
          most-positive-long-float)
    ;; (-3.4028235E+38 3.4028235E+38
    ;;  -3.4028235E+38 3.4028235E+38
    ;;  -1.7976931348623157D+308 1.7976931348623157D+308
    ;;  -1.7976931348623157D+308 1.7976931348623157D+308)
    

4.1.3 Complex 复数

  • Literal

    #c(2 1)       ;-> #c(2 1)
    #c(2/3 3/4)   ;-> #c(2/3 3/4)
    
    #c(2 1.0)     ;-> #c(2.0 1.0)
    #c(2.0 1.0d0) ;-> #c(2.0d0 1.0d0)
    #c(1/2 1.0)   ;-> #c(0.5 1.0)
    
    ;; complex canonicalization
    #c(3 0)       ;-> 3  
    #c(1/2 0)     ;-> 1/2
    #c(3.0 0.0)   ;-> #c(3.0 0.0)
    
  • GET : realpart imgpart

4.2 Character 字符

  • Literal

    #\x      ;-> #\x
    
    ;; #\char-name for no-printing (:imp-d)
    ;;-| Space, Newline, Tab, Page, Rubout, Linefeed, Return, Backspace  
    #\Space ;-> #\ 
    
    ;; Unicode (实现依赖)
    #\U4E91  ; [SBCL]
    #\U+4E91 ; [CCL]
    ;;
    #\云 ;-> #\U+4E91  
    
  • 转换 (实现依赖)
    • code-char char-code
    • char-name name-char

      (char-name #\return) ;-> "Return"
      (char-name #\U+0) ;-> "Null"
      (char-name #\U+123) ;-> "Latin_Small_Letter_G_With_Cedilla"
      
      (name-char "Return") ;-> #\Return
      (name-char "Null") ;-> #\Null
      (name-char "Latin_Small_Letter_G_With_Cedilla")
      ;;-> #\Latin_Small_Letter_G_With_Cedilla
      

4.3 String 字符串

  • 基于 : Vector-Char (字符向量)
  • 创建 : Literal make-string make-array(:e-t='character)

    "String"
    ;; \ : 用于转义 "" \ 
    "Str\"ing" ;-> "Str\"ing"
    "Str\\ing" ;-> "Str\\ing"
    
    ;; 不支持插值语法 和 \n(换行)等转义语法
    "Stri\ng"  ;-> "String" 
    
    ;; Make
    (make-string 3 :initial-element #\c) ;->  "ccc"
    (make-array 5 :fill-pointer 0 :adjustable :element-type 'character) ;-> ""
    
  • 字面值是否可变 ?: 实现依赖

    (eq "abc" "abc") ;-> NIL
    (setf s0 "abc")
    (setf s1 "abc")
    (setf (char s0 0) #\1)
    (list s0 s1) ;; ("1bc" "abc")
    
    (setf s0 "abc")
    (setf s1 s0)
    (setf (char s0 0) #\1)
    (list s0 s1) ;; ("1bc" "1bc")
    

4.3.1 GET

  • 单个元素 : char Vec.schar Arr.aref Seq.elt

    (char "abc" 1) ;-> #\b
    (char "云" 0) ;-> #\U+4E91
    
  • 子字符串 : Seq.subseq
  • 长度 : Seq.length

    (length "1234567") ;-> 7
    (length "一二三四五六七") ;-> 7
    (length "ÄÖÜ1") ;-> 4
    

4.3.2 Split & Concat & Join & Trim

  • 分隔 Split : cl-ppcre:split

    (split "" "hel lo") ;-> ("h" "e" "l" " " "l" "o")
    
    (split "\\s+" "foo   bar baz frob")
    ;;-> ("foo" "bar" "baz" "frob")
    (ppcre:split "(\\s+)" "foo   bar baz frob" :with-registers-p t)
    ;;-> ("foo" "   " "bar" " " "baz" " " "frob")
    
    (split "(,)|(;)" "foo,bar;baz" :with-registers-p t)
    ;;-> ("foo" "," NIL "bar" NIL ";" "baz") ;; ("," nil == mach(,) nomach(;))
    (split "(,)|(;)" "foo,bar;baz" :with-registers-p t :omit-unmatched-p t)
    ;;-> ("foo" "," "bar" ";" "baz")
    
    (split ":" "a:b:c:d:e:f:g::") ;-> ("a" "b" "c" "d" "e" "f" "g")
    (split ":" "a:b:c:d:e:f:g::" :limit 0)
    ;;-> ("a" "b" "c" "d" "e" "f" "g")
    (split ":" "a:b:c:d:e:f:g::" :limit 2)
    ;;-> ("a" "b:c:d:e:f:g::")
    (split ":" "a:b:c:d:e:f:g::" :limit 3)
    ;;-> ("a" "b" "c:d:e:f:g::") 
    
  • 连接 Concat : Imp.concat

    (defun concat (&rest s)
      (apply #'concatenate 'string s))
    
  • 加入 Join : Imp.join

    (defun join (strs &optional (separator " "))
      (reduce (lambda (acc next)
                (format nil "~a~a~a" acc separator next))
           strs))  
    
  • 修剪 Trim : string-trim-[left right]

    (string-trim "abc" "abcaakaaakabcaaa") ;->  "kaaak"
    (string-trim '(#\Space #\Tab #\Newline) " garbanzo beans") ;->  "garbanzo beans"
    (string-trim " (*)" " ( *three (silly) words* ) ") ;->  "three (silly) words"
    
    (string-left-trim " (*)" " ( *three (silly) words* ) ") ;->  "three (silly) words* ) "
    

4.3.3 Search & Replace

  • 匹配 : Seq.(find position) Seq.(search mismatch) cl-ppcre:(scan-[to-strings] all-matches-[as-strings])

    ;; 返回 项 或 NIL
    (find #\a "foobarbaz") ;-> #\a
    
    ;; 返回 位置 或 NIL
    (position #\a "foobarbaz") ;-> 4
    
    ;; 匹配的第一个位置
    (search "bar" "foobarbaz") ;-> 3
    (search "Bar" "foobarbaz" :test #'string=) ;-> NIL
    
    ;; 不匹配的第一个位置
    (mismatch "foobarbaz" "foom")            ;-> 3
    ;; 不匹配的第一个位置索引+1
    (mismatch "foobarbaz" "baz" :from-end t) ;-> 6
    
    ;; scan -> match:(start end) register-match:(start end)
    (scan "(a)*b" "xaaabd") ;-> 1 ;-> 5 ;-> #(3) ;-> #(4)
    (scan-to-strings "(([^b])*)b" "aaabd") ;-> "aaab" ;-> #("aaa" "a")
    
    ;; all-matches -> match:(start end)
    (all-matches "a" "foo bar baz") ;-> (5 6 9 10)
    (all-matches-as-strings "\\d" "bar 3 baz 5") ;-> ("3" "5")
    
  • 替代 : Seq.substitute cl-ppcre:regex-replace-[all] (破坏 : Seq.replace Seq.fill)

    (substitute #\c #\a "abababab") ;-> "cbcbcbcb"
    (substitute #\c #\A "abababab" :test 'string=) ;-> "abababab"
    
    (regex-replace "fo+" "foo bar" "frob")     ;-> "frob bar" ;-> T
    ;; 忽略大小写匹配
    (regex-replace "(?i)fo+" "FOO bar" "frob") ;-> "frob bar" ;-> T
    ;; 保留目标字符串大小写样式
    (regex-replace "(?i)fo+" "Foo bar" "frob" :preserve-case t)
    ;;-> "Frob bar" ;-> T
    (regex-replace-all "(?i)fo+" "foo Fooo FOOOO bar" 
                       "frob" :preserve-case t)
    ;;-> "frob Frob FROB bar" ;-> T
    

4.3.4 Compare

  • 大小写敏感 : string[= /= < > <= >=]
  • 不敏感 : string-[equal not-equal lessp greaterp not-greaterp not-lessp]
  • 前缀 和 后缀 : Imp.(prefixp suffixp)

    (defun prefixp (start s &key (test #'string=))
      (let ((m (mismatch start s :test test)))
        (or (null m) (= m (length start)))))
    
    
    (prefixp "foo" "foobarbaz" ) ;-> T
    (prefixp "foo" "foo" ) ;-> T
    (prefixp "foo" "barbaz" ) ;-> NIL
    
    (defun suffixp (end s &key (test #'string=))
      (case (mismatch end s :from-end t :test test)
        ((0 nil) t)
        (t nil)))
    
    (suffixp "baz" "foobaz" ) ;-> T
    
    

4.3.5 Regex

  • Lib:cl-ppcre

4.3.6 Coding

4.3.7 Other

  • string-[upcase downcase capitalize]

    (string-upcase "abcde") ;->  "ABCDE"
    (string-downcase "ABCDE") ;->  "abcde"
    (string-capitalize "hello Good MORING") ;-> "Hello Good Moring"
    (string-capitalize 'kludgy-hash-search) ;->  "Kludgy-Hash-Search"
    (string-capitalize "DON'T!") ;->  "Don'T!" ;: not "Don't!"  
    

4.4 Boolean Value 布尔值

  • 真|假(Ture|False) : t | nil (非空 == t)
  • t nil 是 符号常量 求值到自身

4.5 Empty(Nothing) 空

  • () == nil

4.6 CONS

  • 创建 : cons

    (cons 'a 'b)           ;-> (a . b)
    (cons 'a nil)          ;-> (a)
    (cons 'a '(b c))       ;-> (a b c)
    (cons 'a (cons b nil)) ;-> (a b)  
    (cons 1 2) ;-> (1 . 2) 
    (cons 1 (cons 2 3))   ;-> (1 2 . 3) 
    
  • 访问 : car|first cdr|rest
  • 修改 : (破坏 rplaca rplacd)

    (defparameter *some-list* (list* 'one 'two 'three 'four))
    
    (rplaca *some-list* 'uno) ;->  (UNO TWO THREE . FOUR)
    *some-list* ;->  (UNO TWO THREE . FOUR)
    
    (rplacd (last *some-list*) (list 'IV)) ;->  (THREE IV)
    *some-list* ;->  (UNO TWO THREE IV)    
    
    ;; (rplaca cons object) == (setf (car cons) object)
    ;; (rplacd cons object) == (setf (cdr cons) object)
    
    ;;; Create circular lists
    (let ((l (list 1)))
        (rplacd l l)  
        l) ; l=(1 . l)
    ;-> (1 1 1 1 1 1 1 1 ... ; Continues until interrupt or stack overflow 
    
    (let ((l (list 2))) 
        (rplaca l l)
        l) ; l=(l . nil)
    ;;-> (((((((((((((((( ... ; Continues until interrupt or stack overflow 
    

4.7 List 列表

  • 表示基于 : 4.6-Chain

    (1) == (1 . nil) == (cons 1 nil)            
    (1 2) == (cons 1 (cons 2 nil)) 
    (1 2 3) == (cons 1 (cons 2 (cons 3 nil)))
    (1 (2 3) 4) == (cons 1 
                         (cons (cons 2 
                                     (cons 3 nil)) 
                               (cons 4 nil)))
    
    ;; tail nil can ignore
    (1 . (2 . (3 . nil))) == (1 . (2 . (3))) == (1 2 3)
    
  • 创建 : Literal list|list* make-list cons

    ;;; Literal
    () ; 空列表 
    '(1 2 3)
    ;; !! (New Obj? 实现依赖)
    (eq '(1 2 3) '(1 2 3)) ;-> nil (Most imp)
    (eq (cdr '(1 2 3))
        (cdr '(1 2 3)))
    ;;-> nil (Most imp)
    
    ;;; Make
    ;; Proper list
    (cons 1 (cons 2 nil)) ;-> (1 2)
    (list 1 2 3)
    (list 'my (+ 2 1) "Sons") ;-> (MY 3 "Sons")
    (list* 'a 'b 'c '(d e f)) ;->  (A B C D E F)
    
    ;; Dotted list
    (cons 1 (cons 2 3)) ;-> (1 2 . 3)
    (list* 'a 'b 'c 'd) ;== (cons 'a (cons 'b (cons 'c 'd))) 
    ;;-> (A B C . D)
    
    ;; 重复列表
    (make-list 3) ;-> (nil nil nil)
    (make-list 3 :initial-element 3) ;-> (3 3 3)
    

4.7.1 种类

  • Proper list (true list) : NIL结尾
  • Dotted list : 非NIL结尾
  • Circular list 循环列表

    ;; Circular list
    #1=(1 2 3 . #1#) 
    ;! 求值导致无限循环
    ;! (length ..) (:imp-d, most: infinite loop)
    
    ;; 打印: *print-circle* = t ->  #1=(A B C . #1#)
    (setf *print-circle* t)
    (defparameter foo '(1 2 3))
    (setf (cdddr foo) foo)      ;-> #1=(1 2 3 . #1#)
    

4.7.2 GET

  • 长度 : Seq.length
  • 单个元素 : first~tenth ca*r nth(索引) Seq.elt

    (nth 0 '(a b c))    ;-> A
    
  • 子列表 : (共享: rest cd*r (索引: nthcdr) (范围: last butlast)) Seq.subseq

    (nthcdr 2 '(a b c)) ;-> (C)
    
    (last '(a b)) ;-> (B)
    (last '(1 2 3 4 5) 3) ;-> (3 4 5)
    
    ;; (butlast list n) == (ldiff list (last list n))
    (setf lst '(1 2 3))
    (butlast lst) ;->  (1 2)
    (butlast lst 2) ;->  (1)
    (butlast lst 5) ;->  NIL
    
    (subseq '(1 2 3 4 5) 0 2) ;-> (1 2)
    
  • 删除 : Seq.remove Seq.remove-duplicates (单个 索引: Imp.remove-at)

    ;;; Usa
    (remove-at '(a b c d) 2) ;-> (A B D)
    (remove-at '(a b c d) 10) ;-> (A B C D)
    
    ;;; Imp
    (defun remove-at (l loc)
      (loop for x in l and i from 0
         unless (= i loc)
         collect x))
    
  • 反转 : Seq.reverse

4.7.3 Concat

  • 追加 Append : append revappend

    (append (list 1 2) (list 3 5)) ;-> (1 2 3 5)
    (revappend (list 1 2) (list 3 6)) ;-> (2 1 3 6)
    

4.7.4 Search

  • member[-if[-not]] Seq.Search

    ;; (:test eql)
    (member a '(c a e)) ;-> (a e)
    

4.7.5 Destruct

  • destructuring-bind

    (destructuring-bind (x y z) (list 1 2 3) (list :x x :y y :z z))
    ;-> (:X 1 :Y 2 :Z 3)
    (destructuring-bind (x (y1 &optional y2) z) (list 1 (list 2) 3) (list :x ..))
    ;-> (:x 1 :y1 2 :y2 nil :z 3)
    (destructuring-bind (&key x y) (list :y 1 :x 2) ..)
    ;-> (:x 2 :y 1)
    (destructuring-bind (&whole whole &key x y) (list :y 2 :x 1) (list :x x :y y :whole whole))
    ;-> (:x 1 :y 2 :whole (:y 2 :x 1))
    

4.7.6 Map

  • mapcar maplist mapc mapl Seq.map

    (mapcar (lambda (x) x) '(1 2 3))  ;-> (1 2 3)
    (maplist (lambda (x) x) '(1 2 3)) ;-> ((1 2 3) (2 3) (3))
    
    ;; (only for side effect)
    (mapc '+ '(1 2 3)) ;-> (1 2 3)
    (mapc #'(lambda (x y) (format t "~a~a " x y)) '(a b c) '(e f d))
     ;;-> AE BF CD ;;-> (A B C)
     (mapl #'(lambda (x) (format t "~a " x)) '(a b c))
    ;;-> (A B C) (B C) (C) ;;-> (A B C)
    

4.7.7 Flatten

  • Imp.my-flatten

    ;;; Usa
    ;; 1
    (my-flatten '(a (b (c d) e))) ;-> (A B C D E)
    ;; 1+
    (my-flatten '((1 2 (3)) a (b (c (m (d e) f) d) e)) :floor 1)
    ;;-> (1 2 (3) A B (C (M (D E) F) D) E)
    (my-flatten '((1 2 (3)) a (b (c (m (d e) f) d) e)) :floor 2)
    ;;-> (1 2 3 A B C M (D E) F D E)
    
    ;;; Imp
    ;; A (1)
    (defun my-flatten (l)
      (cond ((null l) nil)
            ((atom l) (list l))
            (t (append (my-flatten (car l)) (my-flatten (cdr l))))))
    
    ;; B (1+)
    (defun my-flatten (l &key floor)
      (cond ((null l) nil)
            ((atom l) (list l))
            ((and (not (null floor)) (zerop floor)) l)
            (t (if (null floor)
                   (append (my-flatten (car l)) (my-flatten (cdr l)))
                   (append (my-flatten (car l) :floor (1- floor))
                           (my-flatten (cdr l) :floor floor))))))
    

4.7.8 Split

  • Imp.split-group

    ;;; Usa
    (split-group '(a b c d e f g h i k) '(2))
    (split-group '(a b c d e f g h i k) '(2 3 4)) 
    ;;-> ((A B) (C D E) (F G H I) (K)))  
    
    ;;; Imp
    (defun split-group (l g)
      (cond ((null l) nil)
            ((null g) (list l))
            (t (cons (subseq l 0 (car g))
                     (split-group (nthcdr (car g) l) (cdr g))))))  
    

4.7.9 Traversing

  • loop dolist dotimes

4.7.10 Replace

  • 替代元素 : (单个: subst[-if]) (多个: sublis) Seq.substitute

    (subst 10 1 '(1 2 (3 2 1) ((1 1) (2 2))))
    ;-> (10 2 (2 3 10) ((10 10) (2 2)))
    
    (sublis '((x . 100) (z . zprime))
             '(plus x (minus g z x p) 4 . x))
    ;;-> (PLUS 100 (MINUS G ZPRIME 100 P) 4 . 100)    
    

4.8 Tree 树

4.9 Stack 栈

  • 基于 : 4.7
  • 入栈 : (共享: cons) (破坏: push pushnew(使用:Set.adjoin))

    (let ((l (list 3 5)))
      (push 5 l)
      l)
    ;;-> (5 3 5)
    
    (let ((l (list 3 5)))
      (pushnew 3 l)
      (pushnew 6 l)
      l)
    ;;-> (6 3 5)
    
    (let ((l (list 3 5)))
      (cons 3 l)
      (cons 6 l)
      l)
    ;;-> (3 5)
    
  • 出栈 : (共享: car+cdr) (破坏: pop)

    (let ((l (list 1 2 3)))
      (pop l)                               ;-> 1
      l)
    ;;-> (2 3)
    
    (let ((l (list 1 2 3)))
      (car l)
      (setf l (cdr l))
      l)
    ;;-> (2 3)
    
    

4.10 Set 集合

  • 交并差补 属于 大小
  • 基于 : 4.7
  • 添加元素 : adjoin

    (adjoin 1 ()) ;-> (1)
    (adjoin 1 '(3 5 6)) ;-> (1 3 5 6)
    
    (let ((l (list 1 2 3)))
      (adjoin 5 l)
      (adjoin 1 l)
      l)
    ;;-> (1 2 3)
    
  • 操作 : intersection union set-difference set-exclusive-or

    (union '(1 2) '(3 5)) ;-> (2 1 3 5)
    (set-difference '(1 2 3 5 6) '(3 5)) ;-> (6 2 1)
    
  • 属于 : List.member
  • 大小 : Seq.length

4.11 alist 关联表

  • 基于 : 4.7
  • 创建 : List pairlis

    ;; ((k1 v1) (k2 v2) ... (kN vN))
    '((a . 1) (b . 2) (c . 3))
    '((a 1) (b 2) (c 3))
    
    (pairlis '(a b) '(1 2)) ;-> ((b . 2) (a . 1)) or ((a . 1) (b .2))
    
  • 访问 : assoc[-if] rassoc[-if]

    ;; Default(:key car :test #'eql) 
    (assoc 'a '((a . 1) (b . 2))) ;-> (a . 1)
    (assoc 'a '((a 1) (b 2)))     ;-> (a 1)
    (assoc "two" '((1 . a) ("two" . b) (three . c)) 
           :test #'equal)
    ;;-> ("two" . B)
    
    ;; Default(:key cdr)      
    (rassoc "two" '((1 . "one") (2 . "two") (3 . 3))
            :test 'equal)
    ;;-> (2 . "two")
    
  • 添加 : acons

    ;; (acons 'nk 'nv alist) == (cons (cons 'nk 'nv) alist)
    (acons 'd 4 '((a . 1) (b . 2) (c . 3)))
    ;;-> ((D . 4) (A . 1) (B . 2) (C . 3))
    

4.12 plist 属性表

  • 基于 : List 列表
  • 创建 : List

    ;; (k1 v1 k2 v2 ... kN vN)
    '(a 1 b 2 c 3)
    
  • 访问 : getf get-properties

    ;; 比较基于 : eq 
    (getf '(a 2 c 3 d c) 'a) ;-> 2
    (getf '(a 2 c 3 d c) 'd) ;-> c
    (getf '(1 2 4 5) 1)      ;-> 2
    (getf (list 1 :a 'two :b "three" :c) "three") ;-> NIL
    (getf '(1 2 3 4 5 nil) 6) ;-> NIL
    (getf '(1 2 3 4 5 nil) 6 "nothing") ;-> "nothing"
    
    (get-properties '(a 1 b 2 c 3 d 4) (list 'b))
    ;;-> B
    ;;-> 2
    ;;-> (B 2 C 3 D 4)
    
  • 移除 : (破坏: remf)

    (let ((pl (list :a 1 :b 2 :c 3)))
      (remf pl :b)
      pl)
    ;;-> (:A 1 :C 3) ;;-> T
    

4.13 Array 数组

  • 创建 : Literal make-array

    ;;; Literal
    #(2 3) ;-> #(2 3)
    ;; #n(..)
    #5(1 2 3) ;-> #(1 2 3 3 3)
    #3() ;-> Error (最少要有一个对象)
    #3(1) ;-> #(1 1 1)
    ;; 维度 : #nA(..)
    #0A()
    #1A(1 2 3) ;-> #(1 2 3)
    #2A((2) (3)) ;-> #2A((2) (3))
    #2A((1 2) (3 3))
    #3A(((1 2) (3 4)) ((5 6) (7 8)))
    
    ;;; Make
    (make-array 0)                      ;-> #()
    (make-array 3)                      ;-> #(0 0 0)
    (make-array '(2 3)) ;-> #2A((0 0 0) (0 0 0))
    
    (make-array 5 :element-type 'bit)   ;-> #*00000
    (make-array 3 :initial-element nil) ;-> #(NIL NIL NIL)
    (make-array '(2 4) :initial-contents '((0 1 2 3) (3 2 1 0)))
    ;;-> #2A((0 1 2 3) (3 2 1 0))
    
    (make-array 3 :fill-pointer 0) ;-> #()
    (make-array 3 :adjustable t) ;-> #()
    ;;; displaced-to, displaced-index-offset
    
  • 打印 : print-array
    • t : #nA(…)
    • nil : #<ARRAY NxM, simple>
  • CONSTANT
    • array-dimension-limit
    • array-rank-limit
    • array-total-size-limit

4.13.1 GET

  • 大小 : array-total-size Seq.length(1D, observe fill pointers)

    (let ((a (make-array 10 :fill-pointer 3)))
      (list (array-total-size a)
            (length a)))
    ;;-> (10 3)
    
  • 维度 : array-(dimension|dimensions)

    ;; 维数==括号层数
    ;; 返回列表的长度==秩 每个元素的值==每维的大小
    (array-dimensions #1A(1 2 3));-> (3)
    (array-dimensions (make-array 3));-> (3)
    
    (array-dimensions #2A((1 2 3) (1 2 3))) ;-> (2 3)
    (array-dimensions (make-array '(2 3))) ;-> (2 3)
    
    (array-dimensions #3A((((1 2 3)))));-> (1 1 1)
    (array-dimensions #3A((((1 2 3)) ((1 2 3))))) ;-> (1 2 1)
    (array-dimensions #3A((((1 2 3) (1 2 3)))
                          (((1 2 3) (1 2 3)))))
    ;; (2 1 2)
    
    
    ;; 某一维的大小 (从0起 0表示一维)
    (array-dimension (make-array 3) 0) ;-> 3
    (array-dimension (make-array '(2 3)) 1) ;-> 3
    
  • 秩 : array-rank

    (array-rank #0A())
    (array-rank (make-array '()))
    ;;->  0
    
    (array-rank #1A(1))
    (array-rank #1A(1 2 3))
    (array-rank (make-array '(3)))
    ;;-> 1
    
    (array-rank #2A((1)))
    (array-rank (make-array '(2 3)))
    ;;-> 2
    
  • 填充指针值 : fill-pointer
  • 成员类型 : array-element-type
  • array-displacement
  • 行列索引 -> 行主索引 : array-row-major-index

    ;; '(2 5)=(() ()) : [1, 2] : Index=1*5+2=7
    (array-row-major-index #2A((1 2 3 4 5) (3 4 5 6 7)) 1 2) ;-> 7
    
  • 索引元素 : aref row-major-aref

    (aref #(1 2 3) 1)           ;-> 2 
    (aref #2A((1 2) (3 4)) 0 1) ;-> 2
    
    ;; 行主索引 : 当作一行来索引
    (row-major-aref #(1 2) 1) ;-> 2
    (row-major-aref #2A((1 2) (3 4)) 3) ;-> 4
    
  • 子数组 : Seq.subseq

4.13.2 ADJUST

  • adjust-array upgraded-array-element-type

4.14 Vector 向量

  • 表示基于 : 1D-4.13
  • 创建 : Literal vector

    ;;; Literal
    #(1 2)
    
    ;;; 
    (vector)                            ;-> #()
    (vector 1 2)                        ;-> #(1 2)
    
  • 访问 : svref

    (svref #(1 2) 0) ;-> 1
    
  • 添加和删除元素 : vector-push vector-pop vector-push-extend

    ;; 向量需有填充指针
    (let ((v (make-array 3 :fill-pointer 0)))
      (vector-push 1 v)
      (vector-push 2 v)
      (vector-push 3 v)
      v)
    ;; #(1 2 3)
    (let ((v (make-array 3 :fill-pointer t :initial-contents '(1 2 3))))
      (vector-pop v)
      v)
    ;; #(1 2)
    
    ;; 向量需可调整
    (let ((v (make-array 3
                         :fill-pointer t
                         :adjustable t
                         :initial-contents '(1 2 3))))
      (vector-push 5 v)
      v                                     ;-> #(1 2 3)
      (vector-push-extend 5 v)
      v)
    ;;-> #(1 2 3 5)
    

4.15 Sequence 序列

  • 抽象从 (4.14 4.7)
  • 创建 : make-sequence

    (make-sequence 'list 0) ;->  ()
    (make-sequence 'string 3 :initial-element #\.) ;->  "..."
    (make-sequence '(vector double-float) 2 :initial-element 1d0) ;->  #(1.0d0 1.0d0)
    

4.15.1 函数名与参数 特定

  • Keyword Paramater
    • :key : 应用至每个元素的函数 ; identity
    • :test|:test-not : 用于比较的函数 ; eql
    • :start : 起始位置 ; 0
    • :end : 给定 或 结束位置 ; nil
    • :from-end : 若为真 则反向 ; nil
    • :count : 数字代表需要移除或替换的元素个数 nil代表全部 ; nil
    • :intial-value : for reduce
  • -if & -if-not (count position remove find substitute)
    • -if-not 不再使用 用 complement 替代

4.15.2 GET

  • 大小 : length

    (length (vector 1 2 3)) ;-> 3
    
  • 单个元素 : elt

    (elt (vector 1 2) 0)          ;-> 1
    (setf (elt (vector 1 2) 0) 2)
    
  • 子序列 : subseq remove remove-duplicates

    (subseq "foobarbaz" 3)   ;-> "barbaz"
    (subseq "foobarbaz" 3 5) ;-> "ba"
    
    (remove 1 #(1 2 3)) ;-> #(2 3)
    
    (remove-duplicates #(1 2 1 2 3 1 2 3 4)) ;-> #(1 2 3 4)
    
    
  • 反转 : reverse

    (reverse '(a b c)) ;-> (c b a)
    
  • 计数 : count[-if]

    (count 1 #(1 2 1)) ;-> 2
    (count-if #'evenp #(1 2 3)) ;-> 1
    

4.15.3 Replace

  • 替换单个元素 : substitute[-if]

    (substitute 10 1 #(1 3 1)) ;-> #(10 3 10)
    (substitute 10 1 '(1 2 1 3 1)) ;-> (10 2 10 3 10)
    (substitute #\c #\a "abababab") ;-> "cbcbcbcb"
    (substitute #\c #\A "abababab" :test 'string=) ;-> "abababab"
    

4.15.4 Sort

  • (破坏: sort stable-sort)

    (sort '(0 2 1 3 8) #'>)                     ;-> (8 3 2 1 0)
    (sort (vector "foo" "bar" "baz") #'string<) ;-> #("bar" "baz" "foo")
    ;; Vector-Char(String)
    (sort "cdba" #'char<) ;-> "abcd"
    

4.15.5 Concat & Merge

  • 连接 : concatenate

    (concatenate 'vector #(1 2) '(3 5))   ;-> #(1 2 3 5)
    (concatenate 'string "abc" "efg")     ;-> "abcefg"
    (concatenate 'string "aa" '(#\f #\s)) ;-> "aafs"
    
    (let* ((l1 (list 1 2))
           (l2 (list 3 4))
           (l3 (list 5 6))
           (nl (concatenate 'list l1 l2 l3)))
      (setf (second l1) 22)
      (setf (second l3) 66)
      (list l1 l2 l3 nl))
    ;; ((1 22)
    ;;  (3 4)
    ;;  (5 66)
    ;;  (1 2 3 4 5 6))
    
    
  • 合并 : merge

    (merge 'list #(1 2) #(3 4) #'<) ;-> (1 2 3 4)
    

4.15.6 Split

  • Lib:split-sequence

    (split-sequence #\Space "A stitch in time saves nine.")
    ;;-> ("A" "stitch" "in" "time" "saves" "nine.") ;;-> 28  
    
    ;; split-sequence-if | split-sequence-if-not
    

4.15.7 Map

  • 映射 Map : map map-into

    (map 'vector #'* #(1 2 3) #(2 2 2)) ;-> #(2 4 6)
    
    (map-into a #'+ a b c)
    (setf x #(0))                   ;-> #(1)
    (map-into x #'+ #(1) #(2) #(3)) ;-> #(6)
    
  • 累积 Reduce : reduce

    (reduce #'+ #(1 2 3))   ;-> 6
    (reduce #'max #(1 2 3)) ;-> 3
    (reduce #'+ #(1 2) :initial-value 3)
    (reduce (lambda (acc next)
              (format t "~a,~a " acc next) (+ acc next))
            (list 1 2 3 5))
    ;;-> 1,2 3,3 6,5 ;-> 11
    
  • 过滤 Filter : remove[-if]

    (remove 1 #(1 2 3)) ;-> #(2 3)
    (remove-if #'(lambda (x) (char/= (elt x 0) #\f))
               #("foo" "bar" "baz" "foom")) 
    ;;-> #("foo" "foom")
    

4.15.8 Search

  • 单元素 : find[-if] position[-if]

    ;; 返回 项或NIL
    (find 1 #(1 2 3)) ;-> 1
    
    ;;; 返回 位置
    (position 1 #(2 1 2)) ;-> 1
    
  • 子序列 : search mismatch

    ;;; 匹配的第一个位置
    (search "bar" "foobarbaz") ;-> 3
    
    ;;; 不匹配的第一个位置
    (mismatch "foobarbaz" "foom")            ;-> 3
    (mismatch "foobarbaz" "baz" :from-end t) ;-> 6
    

4.15.9 破坏

  • 修改元素 : (setf elt)

    (setf l0 (list 1 2 3))
    (setf (elt l0 1) 9) ;-> 9
    l0  ;-> (1 9 3)
    
  • 修改子序列 : (setf subseq) replace fill

    ;;; subseq
    ;; shorter length determines number of element that replaced
    (defparameter str "hello")
    (setf (subseq str 3) "1112") ; str == hel11
    
    ;;; replace
    (replace "abcdefghij" "0123456789" :start1 4 :end1 7 :start2 4) 
    ;;-> "abcd456hij"
    (setq lst "012345678")
    (replace lst lst :start1 2 :start2 0) ;->  "010123456"
    lst ;->  "010123456"
    
    ;;; fill
    (setf s0 "abcdefgh")
    (fill s0 #\f) ;-> "ffffffff"
    s0 ;-> "ffffffff"
    (fill s0 #\0 :start 1 :end 5) ;; 1..<5
    s0 ;-> "f0000fff"
    
  • 交换 Swap place : rotatef shiftf

    ;;; rotatef : 逆时针(向左)旋转
    (let ((l '(1 2 3)))
      (rotatef (first l) (second l))        ;; (a2 a1 a3)
      (rotatef (third l) (first l))         ;; (a3 a1 a2)
      l)
    ;; (3 1 2)
    (let ((l '(1 2 3)))
      ;; (a1=1 a2=2 a3=3)
      (rotatef (first l)  
               (second l) ;; a1<=a2 (a2 a2 a3)
               (third l)  ;; a2<=a3 (a2 a3 a3)
               (first l)  ;; a1=>a3 (a2 a3 a1)
               ;; a1=>a1 (a1 a3 a1)
               )
      l)
    ;; (1 3 1)
    
    ;;; shiftf : 左移
    (let ((l '(1 2 3)))
      (shiftf (first l) (second l)) ;; (2 2 3)
      (shiftf (first l) (second l) 5) ;; (2 5 3)
      (shiftf (first l)
              (second l)                    ;; (5 5 3)
              (third l)                     ;; (5 3 3)
              6)                            ;; (5 3 6)
      l)
    ;;-> (5 3 6)
    

4.16 Hash Table 哈希表

  • Key-Value
  • 创建 : make-hash-table

    ;; (&Key: test size rehash-size rehash-threshold)
    (make-hash-table)
    
    ;; hash-function
    (make-hash-table :test 'char-equal
                     :hash-function (lambda (char)
                                      (char-code
                                       (char-downcase char))))
    

4.16.1 GET

  • 键对应的值 : gethash

    (gethash 'foo h) ;-> NIL NIL
    
  • 键组 和 值组

    ;;; Keys
    (defun hash-keys (ht)
      (loop for key being the hash-keys of ht
         collect key))
    ;;; Values
    (defun hash-values (ht)
      (loop for value being the hash-valuess of ht
         collect value))
    
  • 遍历 : maphash loop Lib:iterate with-hash-table-iterator
    • maphash

      (let ((ht (make-hash-table)))
        (setf (gethash "a" ht) 1)
        (setf (gethash "b" ht) 1)
        (setf (gethash "c" ht) 1)
        (setf (gethash "d" ht) 1)
        (maphash #'(lambda (k v) (format nil "~a = ~a~%" k v)) ht))
      
    • loop

      ;; for key|value being each|the hash-keys|hash-key|hash-values|hash-value of
      (loop for key being the hash-keys of *my-hash*
         do (print key))
      ;;-> KEY
      
      (loop for key being the hash-keys of *my-hash*
         using (hash-value value)
         do (format t "The value associated with the key ~S is ~S~%" key value))
      ;;-> The value associated with the key KEY is VALUE 
      ;;-> NIL
      
      (loop for value being the hash-values of *my-hash*
         using (hash-key key)
         do (format t "~&~A -> ~A" key value))
      ;;-> KEY -> VAlUE
      ;;-> NIL
      
    • with-hash-table-iterator

        (with-hash-table-iterator (my-iterator *my-hash*)
          (loop
            (multiple-value-bind (entry-p key value)
                (my-iterator)
              (if entry-p
                  (print-hash-entry key value)
                  (return)))))
      
    • !! 迭代哈希表过程中修改哈希表 行为结果不确定 但是 setf(gethash) 和 remhash 可以安全使用
  • 信息 : hash-table-[count size rehash-size rehash-threshold test]

    (hash-table-count *my-hash*) ;-> 0
    (hash-table-test (make-hash-table)) ;-> EQL
    
  • 哈希编码 : sxhash(return hash code for object)

4.16.2 破坏

  • 键对应的值 : setf(gethash)

    ;;; gethash
    (setf (gethash 'foo ht) 'qc)
    (gethash 'foo h) ;-> qc
    
  • 移除 : remhash clrhash

    ;;; 移除项
    (remhash 'foo ht)
    
    ;;; 移除全部
    (clrhash ht)
    

4.17 Bits 位组

4.17.1 基于 Integer

#b111
  • 按位运算
    • 逻辑 : logand … | boole(前者的包装)
    • 移位 : ash

      (ash 11 1) ;-> 22
      (ash 11 -1) ;-> 5
      

4.17.2 基于 Bit-Vector

  • : 4.14-0|1
  • 创建 : Literal | make-array(:e-t='bit)

    ;;; Literal
    #*10110     ; 5 bit
    #*          ; empty
    
    ;;; 
    (make-array 5 :element-type 'bit) ;-> #*00000
    (make-array 5 :element-type 'bit :initial-contents '(1 0 1 1 1)) ;-> #*10111
    
  • 访问 : bit sbit

    (bit #*01101 0) ;-> 0
    
    ;; Simple-bit-vector : sbit
    (sbit #*100111 3)
    
  • 按位运算
    • 逻辑 : bit-..

      ;; 非 : bit-not
      (bit-not #*11010) ;-> #*00101
      
      ;; 与 : bit-and bit-andc1 bit-andc2
      ;; 或 : bit-ior bit-nor bit-orc1 bit-orc2
      ;; 异或 : bit-xor
      ;; 与非 : bit-nand
      ;; bit-eqv
      (bit-eqv #*11001 #*10011) ;-> #*10101
          
      
    • 移位

4.18 Byte 字节

  • 字节指示符 : byte byte-size byte-position

    ;; byte 位数 偏移
    (format nil "0b~B ~:*0x~X" (byte 8 0)) ;-> "0b11111111 0xFF"
    (format nil "0b~B ~:*0x~X" (byte 8 8)) ;-> "0b1111111100000000 0xFF00"
    (format nil "0b~B ~:*0x~X" (byte 16 8)) ;-> "0b111111111111111100000000 0xFFFF00"
    (format nil "0b~B ~:*0x~X" (byte 5 10)) ;-> "0b111110000000000 0x7C00"
    
    ;; 位数 : byte-size (1的个数)
    ;; (byte-size (byte j k)) == j
    (byte-size (byte 10 13)) ;-> 10
    (byte-size #b10011) ;-> 3
    
    ;; 偏移 : byte-position (0的个数)
    ;; (byte-position (byte j k)) == k
    (byte-position (byte 10 13)) ;-> 13
    (byte-position #b010010010)  ;-> 5  
    
  • 加载 : ldb

    ;; ldb
    (format nil "0x~X" (ldb (byte 8 0) #xABCD)) ;-> "#xCD"
    (format nil "0x~X" (ldb (byte 8 8) #xABCD)) ;-> "0xAB"
    
    ;; !!! Danger
    (let ((a (list 8)))
      (setf (ldb (byte 2 1) (car a)) 1)
      a)
    ;;-> (10)
    
    ;; ldb-test
    ;; 所指示位 任何一位为0 则 False
    (ldb-test (byte 3 0) #b1111010)
    (ldb-test (byte 3 0) #b1111000)
    
    
  • 放置 : dpb

    ;; dpb : 放置
    (format nil "0b~,,' ,8:B, ~:*0x~X" (dpb 0 (byte 8 0) #xABCD))
    ;;-> "0b10101011 00000000, 0xAB00"
    (format nil "0b~,,' ,8:B, ~:*0x~X" (dpb 1 (byte 8 8) #xABCD))
    ;;-> "0b1 11001101, 0x1CD"
    (format nil "0b~,,' ,8:B, ~:*0x~X" (dpb -2 (byte 8 8) #xABCD))
    ;;-> "0b11111110 11001101, 0xFECD"
    (format nil "0b~,,' ,8:B, ~:*0x~X" (dpb #b10101 (byte 8 8) #xABCD))
    ;;-> "0b10101 11001101, 0x15CD"
    
  • Field

    ;; mask-field
    (format nil "0x~X" (mask-field (byte 8 0) #xABCD)) ;-> "0xCD"
    (format nil "0x~X" (mask-field (byte 8 8) #xABCD)) ;-> "0xAB00"
    
    ;; deposit-field
    (format nil "0x~X" (deposit-field 0 (byte 8 0) #xABCD)) ;-> "0xAB00"  
    

5 基础

5.1 变量 和 常量

Variable 变量

  • Global (Dynamic) : defparameter defvar (命名约定: *name*)

    ;;; defparameter
    (defparameter *foo* 5)
    (defparameter *foo* (+ 1 2))            ; *foo* == 3
    
    ;;; defvar
    (defvar *bar* 5) ; *bar* = 5
    ;; 重定义不改变之前定义时的值
    (defvar *bar* 6) ; *bar* == 5
    ;; 定义时可以不设置值
    (defvar *bar*) ; *bar* == Unbound
    
  • Local : let let*(可引用变量列表中早先引入的变量)

    ;; let
    (let ((a 5) 􏰅
          (b 6))
      (+ a b))
    ;;-> 11
    
    ;; let*
    (let* ((a 5)
           (b (+ a 2)))
      b)
    ;;-> 7
    

Constant 常量

  • defconstant (命名约定: +name+)

    (defconstant +name+ initial-value-form (doucmentation-string))  
    

Dynamic (Special) Variable (!!! 注意命名)

  • all global variable are dynamic variable
  • Lexical scope & Dynamic extent variable 词法范围 和 动态作用域 变量

    ;; Lexical scope variable
    (let ((x 3))
      (defun test () x))
    (test)                ;-> 3
    (let ((x 5)) (test))  ;-> 3
    
    ;; Dynamic extent variable
    (defvar *special* 3)
    (defun test () *special*)
    (test) ;-> 3
    (let ((*special* 5)) (test)) ;-> 5
    
    
    ;; !!! 注意命名 : 否则难以分清 可导致使用错误
    (defparameter x 3)
    
    (defun test () x)
    (test) ;-> 3
    (let ((x 0)) (test))  ;-> 0
    
    (let ((x 1))
      (defun test () x))
    (test) ;-> 3
    (let ((x 0)) (test)) ;-> 0
    
  • Special: (declare (special ..))

    (let ((y 1))
      (defun test () y))
    (test) ;-> 1
    (let ((y 1))
      (defun test ()
        (declare (special y))
        y))
    (test)  ;-> Error: Unbound y
    (progn (defparameter y 3)
           (test))
    ;;-> 3
    

5.2 函数

  • Lambda : 匿名函数

    (lambda (n) (/ n 2))                   
    ;;-> #<Anonymous Function #x302000DB47EF>
    
    ;; Call
    (funcall #'(lambda (x y) (+ x y)) 2 3) ;-> 5
    ((lambda (x y) (+ x y)) 2 3)           ;-> 5
    ((lambda () 42))                       ;-> 42
    
  • Name 命名
    • Global: defun

      (defun name (arguments)
        "Optional document string"
        body-form)
      
      (defun six () (+ 3 3))
      (six) ;-> 6
      
    • Local: flet labels(call another|recursion)

      (flet ((f (n)
               (+ n 10))
             (g (n)
               (- n 3)))
        (g (f 5)))
      ;;-> 12
      
      (labels ((a (n)
                 (+ n 5))
               (b (n)
                 (+ (a n) 6)))
        (b 10))
      ;;-> 21
      
  • Function Object: function (sugar:#')

    ;; 引用 符号命名的函数 (通常为 defun全局定义的)
    (function car) ;-> #<Compiled-function CAR #x3000000FC18F>
    #'car          ;-> #<Compiled-function CAR #x3000000FC18F>
    
  • 函数 既可以作为 定义抽象的方式 来产生抽象 也可以 作为一个抽象来使用
    • Higher-Order (first-class fun) : as paramater or return-value

5.2.1 Call

  • apply | funcall

    ;; (最后一个参数需要是一个列表)
    (apply (function car) '((x y))) ;-> X
    (apply #'+ '(1 2 3 4 8))        ;-> 18
    (apply #'+ 1 2 '(3))            ;-> 6
    
    (funcall #'+ 1 3 5)    ;-> 9
    (funcall #'car '(x y)) ;-> X
    
  • 局部函数的调用问题 : 先 局部 若使用 符号 而不是 #' 则 全局

    (defun foo (x) (+ x 42))
    (foo 0) ;-> 42
    (funcall 'foo 0)                        ;-> 42
    (funcall #'foo 0) ;-> 42
    
    (flet ((foo (x) (1+ x)))
      (list (foo 0)                         ; Local
            (funcall 'foo 0)                ; Global
            (funcall #'foo 0)               ; Local
            ))
    ;;-> (1 42 1)
    

5.2.2 Paramater list

  • &optional 可选

    ;;; Optional
    (defun foo (a b &optional c d) (list a b c d))
    (foo 1 2)     ;-> (1 2 NIL NIL) 
    (foo 1 2 3)   ;-> (1 2 3 NIL)
    (foo 1 2 3 4) ;-> (1 2 3 4)  
    
  • &key 关键字

    ;;; Keyword 
    (defun foo (&key a b (c 3)) (list a b c))
    (foo)                ;-> (NIL NIL 3)
    (foo :b 1)           ;-> (NIL 1 3)
    (foo :a 1 :b 2 :c 3) ;-> (1 2 3)
    
    ;; 区分外部和内部调用名
    (defun foo (&key ((:apple a)) ((:box b) 0)) (list a b))
    (foo :apple 1 :box 2)  
    
    ;; 关键字名 可不为 关键字
    (defun baz (&key ((foo bar) 42))
               (list bar))
    (baz 'foo 23) ;-> (23)
    
  • Default value 默认值

    ;;; Default Value
    (defun foo (a &optional (b 10)) (list a b))
    (foo 1 2) ;-> (1 2)
    (foo 1) ;-> (1 10)
    
    ;; value 可以是任何 lisp 表达式
    
    ;; 可依赖前面的参数
    (defun foo (a &optional (b a)) (list a b))
    (foo 1 2) ;-> (1 2)
    (foo 1) ;-> (1 1)
    
  • supplied-p : 用于判断是否提供了实参

    ;;; supplied-p
    (defun foo (a &optional (c 3 c-supplied-p)) 
      (list a c c-supplied-p))
    (foo 1)   ;-> (1 3 NIL)
    (foo 1 3) ;-> (1 3 T)  
    
  • &rest

    ;;; rest 
    (defun my+ (&rest nums)
      (apply #'+ nums))  
    
  • &aux : define auxiliary local variables

    ;;; auxiliary
    (defun average (&rest args
                    &aux (len (length args)))
      (/ (reduce #'+ args) len 1.0))
    (average 1 2 3) ;-> 2.0
    
  • &allow-other-keys : 允许未定义的关键字参数 并收集于此

参数数量上限

  • call-arguments-limit
  • lambda-parameters-limit

组合使用问题

  • Order: required &optional &rest &key
    • &rest and &key

        ;;; &rest + &key : 只能使用key
      (defun foo (&rest rest &key a b c) (list rest a b c))
      (foo :a 1 :b 2 :c 3) ;-> ((:A 1 :B 2 :C 3) 1 2 3)
      (foo :a 1) ;-> ((:A 1) 1 NIL NIL)
      (foo 1 2) ;-> Error
      (foo 1 2 :a 1) ;-> Error
      (foo :a 2 1 2) ;-> Error
      
  • Avoid
    • &optional + &key

      (defun foo (x &optional y &key z) (list x y z))
      (foo 1 2 :z 3) ;-> (1 2 3)
      (foo 1)        ;-> (1 nil nil) 
      (foo 1 :z 3)   ;-> Error: Incorrect keyword arguments in (3) .
      (foo 1 :z :z 3) ;-> (1 :Z 3)
      

5.2.3 Return Value

  • 返回值 Return value : 默认返回最后一个表达式的值
  • 返回多值 Return Multi-Values : values values-list

    ;;; Return Multi-Values
    (values 'a nil (+ 1 2));;-> a ;-> nil ;-> 3
    ;; 列表作为参数
    (values-list '(1 2))
    ;;-> 1 ;-> 2
    
    ;; 返回值 传递
    ((lambda () 
       ((lambda () (values 1 2))))) ;;-> 1 ;-> 2
    ;; 多返回值作为参数 只有第一个被使用
    ((lambda (x) x)
      (values 1 2)) ;-> 1
    
    ;; 若不需要使用返回值
    ((lambda () (format t "~a" 1)))
    ;;-> 1 ;-> NIL
    ((lambda ()
       (format t "~a" 1)
       (values)))
    ;;-> 1 ;-> ; No value
    
    ;; (values) 不是 不返回值
    (+) ;->0
    (+ (values)) ; Error: The value NIL is not of the expected type NUMBER.
    (null (values)) ;-> T
    
  • 处理多返回值
    • 多值绑定 : multipel-value-bind

      (multiple-value-bind (a b) (values 2 3)
        (* a b))   ;-> 6
      (multiple-value-bind (a b) (values 2 3 2)
        (* a b)) ;-> 6
      (multiple-value-bind (a b c) (values 2 3)
        c)       ;-> nil
      
    • 多值作为函数参数 : multiple-value-call

      (funcall #'+ (values 1 2 3)) ;->1
      (multiple-value-call #'+ (values 1 2 3)) ;-> 6
      
      (funcall #'+ (values 1 2 3) (values 4 5 6)) ;-> 5
      (multiple-value-call #'+ (values 1 2 3) (values 4 5 6)) ;-> 21
      
    • 多值->列表 : multiple-value-list

      (multiple-value-list (values 'a 'b 'c)) ;-> (A B C)
      

5.2.4 Closures

  • 闭包 Closures : 捕捉创建时的环境信息 : 捕获的是变量 不是值

    (setf fn (let ((i 3)) #'(lambda (x) (+ x i))))
    (funcall *fn*) ;-> 1
    (funcall *fn*) ;-> 2
    (funcall *fn*) ;-> 3
    
    (let ((count 0))
      (list
       #'(lambda () (incf count))
       #'(lambda () (decf count))
       #'(lambda () count)))
    

5.3 控制流

5.3.1 Flow 顺序流程

  • progn prog1 multiple-value-prog1 prog2

    ;;; 返回最后值
    (progn
      (format t "a")
      (format t "b")
      (+ 3 3))
    ;;-> ab
    ;;-> 6
    
    ;;; 返回第一个形式的值
    (prog1 1 2 3) ;-> 1
    (prog1 (values 1 2) 3) ;-> 1
    ;; 返回多值
    (multiple-value-prog1 (values 1 2) 3) ;-> 1 ;-> 2
    
    ;;; 返回第二个形式的值 == (progn a (prog1 b c ... z))
    (prog2 (open-a-file) (process-the-file) (close-the-file)) 
    

5.3.2 Conditional 条件

  • if

    (if (= (+ 1 2) 3)
        'yes
        'no)
    ;;-> yes
    
  • when | unless

    (when (oddp 5) (prin1 "a") (prin1 "b")) ;-> "a""b"
    (unless (oddp 4) (prin1 "a") (prin1 "b")) ;-> "a""b"
    
  • cond

    (cond ((= 3 5) '=)
          ((> 3 3) '>)
          (t))
    ;;-> T
    
    ;;; 没有表达式则会返回条件式的值
    (cond (99)) ;-> 99
    

5.3.3 Case 匹配

  • case ccase ecase

    ;; 键值 被视为常量 不被求值 需要则使用 "#."
    ;; Compare : eql
    ;; 缺省子句的键值可以 : t|otherwise
    (defun month-length (mon)
      (case mon
        ((jan mar may jul aug oct dec) 31)
        ((apr jun sep nov) 30)
        (feb (if (leap-year) 29 28))
        (otherwise "unknown month")))
    (month-length 'mar) ;-> 31
    
    ;;; 如果没有子句符合时 | 子句只包含键值时 , 返回 nil
    (case 99 (99)) ;-> NIL 
    
    ;; ecase : 没有匹配时报错 (e: error|exhaustive)
    
  • typecase ctypecase etypecase

    ;;; typecase
    ;; 每个子句中的键值 : 类型修饰符(type specifiers)
    ;; 键值比较 : typep
    (typecase x
      (number #'+)
      (list #'append)
      (t #'list))
    

5.3.4 Block 区块

  • block

      (block name ...)
      ;; name 是词法解析的 定义时被绑定 返回时不会被其它同名块劫持
    
  • Return from block : return-from return

    ;;; return-from
    (block test
      (return-from test "end")
      "see me")
    ;;-> "end"
    
    ;;; return : (return-from nil ..) 的语法糖 
    (block nil (return 3)) ;-> 3
    
  • 隐式包裹在块中

    ;;; defun : 块名同函数名
    (defun return-from-func ()
      (return-from return-from-func "R")
      "NR")
    (return-from-func) ;-> "R"
    
    (defun foo (n)
      (dotimes (i 10)
        (dotimes (j 10)
          (when (> (* i j) n)
            (return-from foo (list i j))))))
    
    ;;; loop dotimes : 块名NIL 
    (let ((i 0))
      (loop
         (when (> i 5)
           (return))
         (incf i))
      i)
    ;;-> 6
    (dotimes (i 10)
      (when (>= i 3)
        (return i)))
    ;;-> 3
    

5.3.5 Goto 跳转

  • tagbody go

    ;; Label 必须在顶层
    ;; go : to labels
    (tagbody
     top ;: Label
       (if (< (random 20) 10) (go top))
     s1 (if (> (random 3) 1) (go s2))
     s2 (if (> (random 3) 2) (go s3))
     s3 (list "End"))
    ;;-> NIL
    

5.3.6 Loop 循环 :?:

  • All are macro built on TAGBODY and GO
  • do | do*

    (do (var-def*)
        (end-test-form result-form*)
     statement*)
    (var init-form step-form) ; var-def
    
    (do ((n 0 (1+ n))
         (cur 0 next)
         (next 1 (+ cur next)))
        ((= 10 n) cur))
    
  • dolist

    (dolist (x '(1 2 3) 'done) (print x))
    ;;-> 1 ;;-> 2 ;;-> 3 ;;-> Done
    
  • dotimes

    (dotimes (i 3) (print "a"))
    ;;-> a ;;-> a ;;-> a ;;-> NIL
    
  • loop
    • Basic

      (loop) ;-> Infinite Loop   
      
      ;; do
      (loop for x from 0 to 3 
         do (princ x)) ;-> 0123
      
      ;; collect -> (list ... )
      (loop for x from 0 to 3 collect x) ;-> (0 1 2 3)
      
      ;; repeat
      (loop repeat 10 collect 1) ;-> (1 1 1 1 1 1 1 1 1 1)
      
      ;; named
      (loop named a for i below 2
         do (loop named b for j below 2
               do (print j)
               when (= j 1) do (return-from a 'done)))
      ;;-> 0 ;;-> 1 ;;-> done
      
      ;; initially 
      (loop initially (print 'begin)
         for x below 3 collect x)
      ;;-> begin ;;-> (0 1 2)
      
      ;; finally
      (loop for x below 3 do (print x)
         finally (print 'end))
      ;;-> 0 ;;-> 1 ;;-> 2 ;;-> end ;;-> nil
      (loop for x below 3 collect x
         finally (print 'end))
      ;;-> end ;;-> (0 1 2)
      
      ;; end
      (loop for i below 5 when (oddp i) collect i
         end collect " ")
      ;;-> (" " 1 " " " " 3 " " " ")
      
      
    • For-in

      ;;; for|as
      ;; from|upfrom|downfrom to|upto|downto by 
      (loop for x from 0 to 3 collect x) ;-> (0 1 2 3)
      (loop for x from 0 to 5 by 2 collect x) ;-> (0 2 4)
      ;; below
      (loop for i below 3 collect i) ;-> (0 1 2)
      ;; then
      (loop for i = 0 then (1+ i)
         when (= i 3) return 'done
         do (print i)) ;;-> 0 ;;-> 1 ;;-> 2 ;;-> done
      (loop repeat 3 for x = 0 then (1+ x) collect x) ;-> (0 1 2)
      ;; in|on  always|never|thereis  (List)
      (loop for x in '(1 2 3) collect (+ x 1)) ;-> (2 3 4)
      (loop for x in '(0 2 4) always (evenp x)) ;-> t
      (loop for x in '(0 2 4) never (oddp x)) ;-> t
      (loop for x in '(1 2 3) thereis (evenp x)) ;-> t
      ;; across (Array)
      (loop for x across #(1 2 3) collect (+ x 1)) ;; (2 3 4)
      ;; and
      (loop
         for x from 1 to 3
         for y from 1 to 3
         collect (list x y))
      (loop for x from 1 to 3 and y from 1 to 3 collect (list x y))
      ;;-> ((1 1) (2 2) (3 3))
      ;; count
      (loop for i in '(1 2 3) count i) ;-> 3
      ;; sum
      (loop for i in '(1 2 3) sum i) ;-> 6
      (loop for i from 1 to 3 sum i) ;-> 6
      ;; minimize|maximize
      (loop for i in '(1 2 3) maximize i) ;-> 3
      ;; append|nconc
      (loop for i in '(1 2 3) append (list 0 i)) ;-> (0 1 0 2 0 3)
      ;; destructure
      (loop for (a b) in '((x 1) (y 2) (z 3))
         collect (list b a) )
      ;;-> ((1 X) (2 Y) (3 Z))
      (loop for (x . y) in '((1 . 1) (2 . 4) (3 . 9)) collect y)
      ;;-> (1 4 9)
      (loop for (key value) on args by #'cddr
         collect (list (intern (symbol-name key)) value))
      
    • Condition: when unless while until if-else

        ;; when 
        (loop for i below 5
           when (= i 3) return 'done
           do (print i))
        ;;-> 0 ;;-> 1 ;;-> 2 ;;-> done
        (loop for i below 5
           when (= i 3) do (print i)
           collect i)
        ;;-> 3 ;;-> (0 1 2 3 4)
        (loop for i in '(0 1 2 3)
           when (evenp i) collect i)
        ;;-> (0 2)
      
        ;; unless
        (loop for i in '(0 1 2 3)
           unless (evenp i) collect i)
        ;;-> (1 3)
      
        ;; while
        (loop for i in '(0 1 2 3)
           while (evenp i) return 'done)
        ;;-> done
        (loop for i in '(0 1 2 3)
           while (evenp i) do (print i) collect i)
        ;;-> 0 ;;-> (0)
        (loop for i in '(0 1 2 3)
           while (evenp i) collect i)
        ;;-> (0)
      
        ;; until
        (loop for i from 0 collect i until (> i 3))
        ;;-> (0 1 2 3 4)
      
        ;; if else
        (loop for i below 3
           if (oddp i) collect i
           do (print i))
        ;;-> 0 ;;-> 1 ;;-> 2 ;;-> (1)
        (loop for i below 3
           if (oddp i) collect i
           else do (print i)
           do (print "done"))
        ;;-> 0 ;;-> "done" ;;-> "done" ;;-> 2 ;;-> "done" ;;-> (1)
        
      
    • Variable

        ;;; with
        (loop with x = (+ 1 1) repeat 3 collect x)
        ;;-> (2 2 2)
      
        ;;; Into
        (loop for i in '(1 2 3)
           minimize i into lowest
           maximize i into biggest
           finally (return (cons lowest biggest)))  
      
    • Hash Table

        ;; being each|the hash-keys|hash-key|hash-values|hash-value of
        (defparameter ht (make-hash-table))
        (setf (gethash 'a ht) 1)
        (setf (gethash 'b ht) 2)
        (loop for key being the hash-keys of ht
           collect key)
        ;;-> (B A)
        
      
    • Return: loop-finish return

      (loop for i in ’(3 7 8 1)
         do (print i)
         when (evenp i)
         do (loop-finish)
         finally (print :done))
      ;;-> 3 ;-> 7 ;-> 8 ;-> :DONE ;-> NIL
          
      
  • Lib:Iterate : similar to built in loop

5.3.7 Break 中断

  • catch, throw : escape from anywhere
  • 中断保护(打断时 剩下的表达式仍会被求值) : unwind-protect

    (setf x 1) ;-> 1
    (catch 'abort
      (unwind-protect
           (throw 'abort 99)
        (setf x 2)))
    ;;-> 99,  x = 2
    

5.4 Compare 比较

5.4.1 GENERAL : eq eql equal equalp

  • eq : compare memory addresse of object (最好只用来比较符号)
  • eql : retain eq, extend to identical number and character
  • equal : true for print same
  • equalp : ignore number type and character case
    • true : if element are EQUALP(ture)
      • Array
      • Structure
      • Hash Table
;;; eq
(eq 'h 'h)          ;-> T
(eq "h" "h")        ;-> NIL
(eq '(1 2) '(1 2))  ;-> NIL
;; by implementation
(eq 3 3)            ;-> T
(eq 3.0 3)          ;-> NIL
(eq #\a #\a)        ;-> T

;;; eql
;; retain eq
(eq 'h 'h)          ;-> T
(eq "h" "h")        ;-> NIL
(eq '(1 2) '(1 2))  ;-> NIL
;; extend eq
(eql 3 3.0)         ;-> NIL 
(eql 3.3 3.3)       ;-> T
(eql #\a #\a)       ;-> T

;;; equal
(equal 'apple 'apple) ;-> T
(equal '(a b) '(a b)) ;-> T
(equal 5 5)           ;-> T
(equal 2.5 2.5)       ;-> T
(equal 3 3.0)         ;-> NIL
(equal "foo" "foo")   ;-> T
(equal #\a #\a)       ;-> T

;;; equalp
;; diff equal
(equalp "Bob Smith" "bob smith") ;-> T
(equalp 0 0.0)                   ;-> T

5.4.2 Number

  • = /= < > <= >=

    (= 1 1)                       ;-> T
    (= 10 20/2)                   ;-> T
    (= 1 1.0 #c(1.0 0.0) #c(1 0)) ;-> T
    
    (/= 1 1)                      ;-> NIL
    (/= 1 2)                      ;-> T
    (/= 1 2 1)                    ;-> NIL
    
  • max min

    (max 1 2 3) ;-> 3
    (min 1 2 3) ;-> 1
    
  • 复数

    (eql 3 #c(3 0)) ;-> T
    (eql 3.0 #c(3.0 0.0)) ;-> NIL
    (equalp 3.0 #c(3.0 0.0)) ;-> T
    

5.4.3 Character

  • 大小写敏感 : char[= /= < > <= >=]
  • 不敏感 : char-[equal not-equal lessp greaterp not-greaterp not-lessp]
  • 范围 : 如 (char<= #\0 CHAR #\9)

5.4.4 String

  • 大小写敏感 : string[= /= < > <= >=]
  • 不敏感 : string-[equal not-equal lessp greaterp not-greaterp not-lessp]

5.4.5 List

  • tree-equal ldiff(差集)

    (defparameter *a* '(42 "3" 5.3 :x #\u :a 23/12))
    (ldiff *a* (member-if 'symbolp *a*)) ;-> (42 "3" 5.3)   
    
  • Set : Imp:set-equal | Lib:ALEXANDRIA{set-equal}

    (defun set-equal (a b)
        (null (set-exclusive-or a b)))
    
    (set-equal '(1 2 2 3) '(3 3 1 1 2)) ;-> t  
    

6 概念

6.1 Scope & Extent 作用域 和 生命周期

  • Scope (space) & Extent (time) : Visibility & Lifetime
    • lexical 词法
    • dynamic 动态
  • Shadowing
    • 同名 : 后者可能屏蔽前者