Implement step 6
authorVasilij Schneidermann <mail@vasilij.de>
Fri, 7 Jul 2017 16:36:48 +0000 (18:36 +0200)
committerVasilij Schneidermann <mail@vasilij.de>
Fri, 7 Jul 2017 16:36:48 +0000 (18:36 +0200)
gst/core.st
gst/func.st
gst/printer.st
gst/step6_file.st [new file with mode: 0644]
gst/types.st

index f4f397f..c8b699d 100644 (file)
@@ -1,5 +1,6 @@
 FileStream fileIn: 'types.st'.
 FileStream fileIn: 'printer.st'.
+FileStream fileIn: 'reader.st'.
 
 Object subclass: Core [
     Ns := Dictionary new.
@@ -57,3 +58,29 @@ Core Ns at: #> put:
     [ :args | Core coerce: [ args first value > args second value ] ].
 Core Ns at: #>= put:
     [ :args | Core coerce: [ args first value >= args second value ] ].
+
+Core Ns at: #'read-string' put:
+    [ :args | Reader readStr: args first value ].
+Core Ns at: #slurp put:
+    [ :args | MALString new: (File path: args first value) contents ].
+
+Core Ns at: #atom put:
+    [ :args | MALAtom new: args first ].
+Core Ns at: #'atom?' put:
+    [ :args | Core coerce: [ args first type = #atom ] ].
+Core Ns at: #deref put:
+    [ :args | args first value ].
+Core Ns at: #'reset!' put:
+    [ :args | args first value: args second. args second ].
+Core Ns at: #'swap!' put:
+    [ :args |
+        | a f x xs result |
+        a := args first.
+        f := args second.
+        f class = Func ifTrue: [ f := f fn ].
+        x := a value.
+        xs := args allButFirst: 2.
+        result := f value: (xs copyWithFirst: x).
+        a value: result.
+        result
+    ].
index 90ecd62..ccff241 100644 (file)
@@ -1,10 +1,15 @@
 Object subclass: Func [
-    | ast params env fn |
+    | ast params env fn meta |
 
     ast [ ^ast ]
     params [ ^params ]
     env [ ^env ]
     fn [ ^fn ]
+    meta [ ^meta ]
+
+    meta: aMeta [
+        meta := aMeta
+    ]
 
     Func class >> new: ast params: params env: env fn: fn [
         | func |
@@ -19,4 +24,11 @@ Object subclass: Func [
         env := anEnv.
         fn := aFn.
     ]
+
+    withMeta: meta [
+        | func |
+        func := self deepCopy.
+        func meta: meta.
+        ^func
+    ]
 ]
index 5543892..7079a49 100644 (file)
@@ -32,6 +32,10 @@ Object subclass: Printer [
             ^self prMap: sexp printReadably: printReadably
         ].
 
+        sexp type = #atom ifTrue: [
+            ^'(atom ', (self prStr: sexp value printReadably: printReadably), ')'
+        ].
+
         Error halt: 'unimplemented type'
     ]
 
diff --git a/gst/step6_file.st b/gst/step6_file.st
new file mode 100644 (file)
index 0000000..f7d6edb
--- /dev/null
@@ -0,0 +1,185 @@
+FileStream fileIn: 'readline.st'.
+FileStream fileIn: 'reader.st'.
+FileStream fileIn: 'printer.st'.
+FileStream fileIn: 'env.st'.
+FileStream fileIn: 'func.st'.
+FileStream fileIn: 'core.st'.
+
+Object subclass: MAL [
+    MAL class >> READ: input [
+        ^Reader readStr: input
+    ]
+
+    MAL class >> evalAst: sexp env: env [
+        sexp class = BlockClosure ifTrue: [^sexp ].
+
+        sexp type = #symbol ifTrue: [
+            ^env get: sexp value
+        ].
+
+        sexp type = #list ifTrue: [
+            ^self evalList: sexp env: env class: MALList
+        ].
+        sexp type = #vector ifTrue: [
+            ^self evalList: sexp env: env class: MALVector
+        ].
+        sexp type = #map ifTrue: [
+            ^self evalList: sexp env: env class: MALMap
+        ].
+
+        ^sexp
+    ]
+
+    MAL class >> evalList: sexp env: env class: aClass [
+        | items |
+        items := sexp value collect:
+            [ :item | self EVAL: item env: env ].
+        ^aClass new: items
+    ]
+
+    MAL class >> EVAL: aSexp env: anEnv [
+        | sexp env ast a0 a0_ a1 a1_ a2 a3 an forms function args |
+
+        "NOTE: redefinition of method arguments is not allowed"
+        sexp := aSexp.
+        env := anEnv.
+
+        [
+            [ :continue |
+                (sexp class = BlockClosure or: [ sexp type ~= #list ]) ifTrue: [
+                    ^self evalAst: sexp env: env
+                ].
+                sexp value isEmpty ifTrue: [
+                    ^sexp
+                ].
+
+                ast := sexp value.
+                a0 := ast first.
+
+                a0 class ~= BlockClosure ifTrue: [
+                    a0_ := ast first value.
+                    a0_ = #'def!' ifTrue: [
+                        | result |
+                        a1_ := ast second value.
+                        a2 := ast third.
+                        result := self EVAL: a2 env: env.
+                        env set: a1_ value: result.
+                        ^result
+                    ].
+
+                    a0_ = #'let*' ifTrue: [
+                        | env_ |
+                            env_ := Env new: env.
+                        a1_ := ast second value.
+                        a2 := ast third.
+                        1 to: a1_ size by: 2 do:
+                            [ :i | env_ set: (a1_ at: i) value
+                                        value: (self EVAL: (a1_ at: i + 1)
+                                                     env: env_) ].
+                        env := env_.
+                        sexp := a2.
+                        continue value "TCO"
+                    ].
+
+                    a0_ = #do ifTrue: [
+                        | forms last |
+                        ast size < 2 ifTrue: [
+                            forms := {}.
+                            last := MALObject Nil.
+                        ] ifFalse: [
+                            forms := ast copyFrom: 2 to: ast size - 1.
+                            last := ast last.
+                        ].
+
+                        forms do: [ :form | self EVAL: form env: env ].
+                        sexp := last.
+                        continue value "TCO"
+                    ].
+
+                    a0_ = #if ifTrue: [
+                        | condition |
+                        a1 := ast second.
+                        a2 := ast third.
+                        a3 := ast at: 4 ifAbsent: [ MALObject Nil ].
+                        condition := self EVAL: a1 env: env.
+
+                        (condition type = #false or:
+                             [ condition type = #nil ]) ifTrue: [
+                                 sexp := a3
+                             ] ifFalse: [
+                                 sexp := a2
+                             ].
+                        continue value "TCO"
+                    ].
+
+                    a0_ = #'fn*' ifTrue: [
+                        | binds env_ fn |
+                            a1_ := ast second value.
+                        binds := a1_ collect: [ :item | item value ].
+                        a2 := ast third.
+                        fn := [ :args |
+                            self EVAL: a2 env:
+                                (Env new: env binds: binds exprs: args) ].
+                        ^Func new: a2 params: binds env: env fn: fn
+                    ]
+                ].
+
+                forms := (self evalAst: sexp env: env) value.
+                function := forms first.
+                args := forms allButFirst asArray.
+
+                function class = BlockClosure ifTrue: [ ^function value: args ].
+                function class = Func ifTrue: [
+                    | env_ |
+                    sexp := function ast.
+                    env_ := Env new: function env binds: function params
+                                exprs: args.
+                    env := env_.
+                    continue value "TCO"
+                ]
+            ] valueWithExit
+        ] repeat.
+    ]
+
+    MAL class >> PRINT: sexp [
+        ^Printer prStr: sexp printReadably: true
+    ]
+
+    MAL class >> rep: input env: env [
+        ^self PRINT: (self EVAL: (self READ: input) env: env)
+    ]
+]
+
+| input historyFile replEnv argv |
+
+historyFile := '.mal_history'.
+ReadLine readHistory: historyFile.
+replEnv := Env new: nil.
+
+argv := Smalltalk arguments.
+argv notEmpty ifTrue: [ argv := argv allButFirst ].
+argv := OrderedCollection from: (argv collect: [ :arg | MALString new: arg ]).
+
+Core Ns keysAndValuesDo: [ :op :block | replEnv set: op value: block ].
+replEnv set: #eval value: [ :args | MAL EVAL: args first env: replEnv ].
+replEnv set: #'*ARGV*' value: (MALList new: argv).
+
+MAL rep: '(def! not (fn* (a) (if a false true)))' env: replEnv.
+MAL rep: '(def! load-file (fn* (f) (eval (read-string (str "(do " (slurp f) ")")))))' env: replEnv.
+
+Smalltalk arguments notEmpty ifTrue: [
+    MAL rep: '(load-file "', Smalltalk arguments first, '")' env: replEnv
+] ifFalse: [
+    [ input := ReadLine readLine: 'user> '. input isNil ] whileFalse: [
+        input isEmpty ifFalse: [
+            ReadLine addHistory: input.
+            ReadLine writeHistory: historyFile.
+            [ (MAL rep: input env: replEnv) displayNl ]
+                on: MALEmptyInput do: [ #return ]
+                on: MALError do:
+                    [ :err | ('error: ', err messageText) displayNl. #return ].
+        ]
+    ].
+
+    '' displayNl.
+]
index d9015e8..4938b1b 100644 (file)
@@ -5,11 +5,11 @@ Object subclass: MALObject [
     value [ ^value ]
     meta [ ^meta ]
 
-    setValue: aValue [
+    value: aValue [
         value := aValue.
     ]
 
-    setMeta: aMeta [
+    meta: aMeta [
         meta := aMeta.
     ]
 
@@ -29,7 +29,7 @@ Object subclass: MALObject [
     withMeta: meta [
         | object |
         object := self deepCopy.
-        object setMeta: meta.
+        object meta: meta.
         ^object
     ]