I. Kernel Language for the Declarative Computation Model A. motivation (2) What does programming involve? ------------------------------------------ PARTS OF PROGRAMMING - a set of reasoning techniques - a programming model - a computation model ------------------------------------------ B. Defining languages (2.1) 1. how languages are defined ------------------------------------------ HOW LANGUAGES ARE DEFINED - syntax - semantics - static semantics (type checking, ...) - dynamic semantics (execution meanings) - pragmatics how expensive is it? ------------------------------------------ 2. syntax ------------------------------------------ EXTENDED BACKUS-NAUR FORM (EBNF) Example ::= { } ::= 0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 ------------------------------------------ ------------------------------------------ FOR YOU TO DO Give an EBNF grammar for phone numbers of the form 555-1212 or 441-1572 ------------------------------------------ 3. semantics (2.1.2) ------------------------------------------ SEMANTICS Goals: - simple - mathematical - reason about correctness - reason about efficiency Kernel Language Approach: [ Practical Language ] | | translation (desugaring) v [ Kernel Language ] E.g., fun {Sqr X} X * X end -translates-to-> proc {Sqr X Y} {Number.'*' X X Y} end ------------------------------------------ How to define the kernel language? What characteristics needed for kernel language? Why? Is C a kernel language? C++? a. linguistic abstractions What is a linguistic abstraction? ------------------------------------------ LINGUISTIC ABSTRACTIONS A named abstraction that adds to a language some feature e.g., for loops in C which abstract while loops for (int i=0; i < N; i++) { f(i) } --> int i = 0; while (i < N) { f(i); i++; } ------------------------------------------ What are some linguistic abstractions in C++ or Java? b. syntactic sugar What is a syntactic sugar? a syntactic abstracation, translation rule How is it different from a linguistic abstraction? it has no name ------------------------------------------ SYNTACTIC SUGARS In Java Integer x; x = 7; -> Integer x; x = new Integer(7); ------------------------------------------ What are some syntactic sugars in C++ and Java? c. Examples ------------------------------------------ EXAMPLES OF DESUGARING LINGUISTIC ABSTRACTIONS AND SUGARS fun {Discrim A B C} fun {Square N} N*N end in {Square A} + {Square B} - 4.0*A*C end {Browse {Discrim 5.0 4.0 3.0}} --> Discrim = proc {$ A B C Res} local Square in Square = proc {$ N R} {Number.'*' N N R} end local A2 in local B2 in {Square A A2} {Square B B2} local A2B2 in {Number.'+' A2 B2 A2B2} local A4 in local Four in Four=4.0 {Number.'*' A Four A4} local A4C in {Number.'*' A4 C A4C} {Number.'-' A2B2 A4C Res} end end end end end end end end local Temp in local Five in local Four in local Three in Five=5.0 Four=4.0 Three=3.0 {Discrim Five Four Three Temp} {Browse Temp} end end end end ------------------------------------------ ------------------------------------------ FOR YOU TO DO Desugar the following: fun {Inc N} N+1 end {Browse {Inc 3}} ------------------------------------------ C. declarative computation model details (2.2-2.5) 1. data and the store ------------------------------------------ VALUE CREATION: WHAT IS SHOWN? local X Y Z in %% Value creation X=3 Y=oh#kay Z=zrec(z1:99 32) %% atoms vs. identifiers {Browse x} {Browse X} {Browse Y} {Browse Z} end ------------------------------------------ ------------------------------------------ FOR YOU TO DO % What's shown by the following? local D in D=drec(3 feature: atom) {Show rec(feature:3)} {Show D} end Output is: rec(feature:3) drec(3 feature: atom) ------------------------------------------ 2. single-assignment store (2.2) ------------------------------------------ SINGLE-ASSIGNMENT STORE (2.2) Oz's = operation (tell) unifies the two sides making them identical if possible local X1 X2 X3 X4 X5 X6 in {Browse store(x1:X1 x2:X2 x3:X3 x4:X4 x5:X5 x6:X6)} {Delay 5000} X1=X2 {Delay 2000} X3=X2 {Delay 2000} X5=name(label:7) {Delay 2000} X6=name(label:X1) {Delay 2000} X1=X4 {Delay 2000} X5=X6 end ------------------------------------------ ------------------------------------------ FOR YOU TO DO % What's shown by the following? local Y1 Y2 Y3 Y4 Y5 Y6 Y7 in {Browse store(y1:Y1 y2:Y2 y3:Y3 y4:Y4 y5:Y5 y6:Y6 y7:Y7)} Y1=4020 Y2=Y3 Y4=aRecord(first:Y5 second: 1234) Y6=aRecord(second:Y7 first:999) Y4=Y6 Y4=Y2 end ------------------------------------------ How can we picture or model this? ------------------------------------------ NOTATION FOR SINGLE-ASSIGNMENT STORES Example 1: s = { x1, x2 = x3 } means s(x1) = {x1} // x1 is undetermined s(x2) = {x2, x3} s(x3) = {x2, x3} pictured as: x1 [ *-]--->[undetermined {x1}] x2 [ *-]--->[undetermined {x2, x3}] x3 [ *-]-/ Example 2: { x1 = 541, x2 = 3|4|nil, x3 = 3|4|nil, x4 } pictured as: x1 [541] x2 [ *-]--->[ 3|*-]->[ 4| *-]-> nil x3 [ *-]--/ x4 [ *-]--->[undetermined {x4}] ------------------------------------------ How would you implement this? What is a value store? a. environment (2.2.4-5) What does the following show? ------------------------------------------ ENVIRONMENT AND SCOPING EXAMPLES local X Y in X=4 Y=5 {Show 'first X = '#X} {Show 'first Y = '#Y} local X Y in X=11 Y=22 {Show 'inner X = '#X} {Show 'inner Y = '#Y} end {Show 'second X = '#X} {Show 'second Y = '#Y} end local X XVal Add AddPairs in X=4 XVal = proc {$ ?R} R=X end Add = fun {$ X Y} X+Y end fun {AddPairs X Y} case X of X1#X2 then case Y of Y1#Y2 then (X1+Y1)#(X2+Y2) end end end {Show '{XVal} = '#{XVal}} {Show '{Add X Y} = '#{Add 20 4000}} {Show '{AddPairs 50#21 40#20} = ' # {AddPairs 50#21 40#20}} end ------------------------------------------ ------------------------------------------ CASE AND SCOPING % What does the following do? local BadAddPairs in fun {BadAddPairs X Y} case X of X#Y then case Y of X#Y then (X+Y)#(X+Y) else canthappen end end end {Show '{BadAddPairs 50#21 40#20} = ' # {BadAddPairs 50#21 40#20}} end ------------------------------------------ How can we formally model these examples? ------------------------------------------ SUMMARY OF NOTATIONS AND MODEL Example: Y = 4020 Now have environment: E(Y) = x1 store: s(x1) = 4020 Pictured: E s Y [ *-]----> x1 [4020] Notation E = {Y --> x1} s = {x1 = 4020} ------------------------------------------ What is the value of Y? 4020 = s(E(Y)) What is dereferencing? b. partial values (2.2.6) ------------------------------------------ PARTIAL VALUES (2.2.6) def: A *partial value* is a data structure that may contain undetermined locations. Example: local X Y in X = person(name:"George" age: Y) end What environment and store does this produce? ------------------------------------------ What happens after the binding Y = "25" is done? ------------------------------------------ COMPATABILITY OF VALUES Program identifiers can be unified with (other) identifiers, which makes them the same (or checks that they are, fails if can't) if they are compatible: X = Y Pictured: X [ *-]-----> x1 [ *-]---> [undetermined {x1, x2}] / Y [ *-]-----> x2 [ *-]-/ Whenever one value is determined, the other variable identifier also sees it. local X Y in X = Y Y = 25 {Browse X} end ------------------------------------------ Can this work for more than 2 identifiers? c. dataflow execution (2.2.8) ------------------------------------------ DATAFLOW EXECUTION What if a location is used before it is determined? 1. Get garbage from memory C, C++, fast, insecure 2. Get default value for type (0) Java fields, slower, more secure, but still might not be what programmer wants 3. Give error message and stop, Prolog arithmetic, slower 4. Illegal, complain at compile time, Java locals 5. Wait until location's value is determined, Oz, slower ------------------------------------------ Why do these? What languages do these? What does Oz do? 3. Kernel Language (2.3) a. Syntax (2.3.1) ------------------------------------------ KERNEL LANGUAGE SYNTAX (TABLES 2.1, 2.2) ::= skip | | local in end | = | = | if then else end | case of then else end | '{' {} '}' ::= ::= | | ::= | ::= | ( {:} ) ::= proc '{' $ {} '}' end ::= | ::= | | ::= true | false ------------------------------------------ Why would you include all of these in the language? Why leave out some things, e.g., = ? What is a case statement like in C, C++, or Java? why records? b. Values and types (2.3.2) ------------------------------------------ TYPES def: a *type* is a set of values with a set of operations Types in the Oz's declarative model Value Number Int Char Float Record Tuple Literal Bool Atom ... List String ... Procedure ... ... ------------------------------------------ What does v has type T mean? What does a subtype mean in this interpretation of types? What is dynamic typing? Why do it? How does this type system compare to that of C, C++, and Java? i. Basic types (2.3.3) ii. Records (2.3.4-5) ------------------------------------------ RECORDS (2.3.4) Creation newrec(field1: Val1) Operations: Arity: Record -> Label : Record -> Literal '.' IsRecord: Value -> Bool ------------------------------------------ What's the operation for creating a record? What are the operations on records? What are these kinds of operations called in Java? How can records be used to make enumerations? variants? What does == do for records? compares label, arity, and all fields What is the difference between X = Y and X == Y ? iii. Procedures (2.3.4-5) ------------------------------------------ PROCEDURES Creation: proc { $ X Y } Y = X+X end Operations: { F ... } calls the procedure F ------------------------------------------ What are the operations on procedures? 4. Kernel Language Semantics (2.4) a. basic concepts (2.4.1) i. Static Scoping ------------------------------------------ DECLARATIONS def: In the declarative kernel, an identifier is declared by: 1. a local statement of form local in end e.g., Y is declared in: local Y in R=Y end 2. the identifiers in the of a case statments then where ::= ::= | ( {:} ) e.g., Y is declared in: case Z of foo(ab:Y) then R=Y else R=nil end 3. the formal parameter of a procedure value of form proc '{' $ {} '}' end e.g., Y and R are declared in: proc {$ Y ?R} R=Y end In each of the above, the *region* where such a declaration of may be referred to by uses of is the statement . ------------------------------------------ What other declaration sites are there in the sugared part of Oz? ------------------------------------------ DECLARATIONS IN SUGARED OZ SYNTAX local foo(ab: Y cd: Z) = Q in ... end case Q of foo(ab: Y) then ... [] bar(cd: Z) then... else ... end fun {Id X} X end sugar for Id = proc {$ X ?R} R=X end fun {Head X|_} X end sugar for Head = proc {$ L ?R} case L of X|_ then R=X else raise someException(...) end end end ------------------------------------------ ------------------------------------------ STATIC SCOPING def: In *static scoping*, each identifier, X, denotes the location for X declared in the closest textually surrounding declaration of X def: In *dynamic scoping*, each identifier, X, denotes the location for X declared in the most recent declaration of X that is still active. Example: local X F T in local X in X=2 F = proc {$ Y ?Z} Z=X+Y end end X=1 {F 10 T} {Browse T} end ------------------------------------------ What does the example give with each kind of scoping? ------------------------------------------ PICTURE WITH DYNAMIC SCOPING ------------------------------------------ In the example, does it matter if X=1 occurs after the declaration of F? What is the meaning of the procedure local X in X = 541 proc {$ Y Z} Z = X+Y end end with dynamic scoping? What kind of scoping is in C, C++, and Java? The Unix shell? ii. Free and bound identifier occurrences (p. 64) ------------------------------------------ FREE AND BOUND IDENTIFIER USES def: an identifier *occurs free* in a statement iff contains a use of that does not refer to a declaration of within def: an identifier *occurs bound* in a statment iff contains a use of that refers to a declaration of within . {proc {$ X ?Y} Y=X end F1 Z} {{{proc {$ X ?Y} Y=proc {$ X ?Y} Y={X F} end end} F Z} F1 Z1} {{{proc {$ X ?Y} Y=proc {$ F ?Y} Y={F F} end end} F Z} F1 Z1} ------------------------------------------ How would you define free and bound identifier uses in expressions? in the first expression, what does X refer to? ------------------------------------------ EXAMPLES F, F1 occur free in: F1 {F F1} proc {$ B ?Res} Res=F end B, B1 occur bound in: proc {$ B ?Res} Res = B end proc {$ B1 ?R1} R1= proc {$ B ?R} R={B1 B} end end There can be a mix: {proc {$ B R} R=B end F} ^ ^ bound-/ \-free occurrence occurrence The same identifier can occur both ways: {fun {$ N} N end N} ^ ^ bound-/ \-free occurrence occurrence Identifiers that are free in a subexpression may be bound in a larger expression fun {$ F} {fun {$ B} {B F1} end F} end Identifiers must be used to be bound proc {$ N R} proc {$ N R2} R2=3 end end fun {$ N} 3 end ------------------------------------------ So if N occurs free in an expression, does that mean it doesn't occur bound? ------------------------------------------ FOR YOU TO DO What are the (a) free, and (b) bound identifiers in ... fun {$ X} fun {$ Y} X end end (a): {} (b): {X} {G {Tail X}} free: {G, X, Tail} bound: {} fun {$ X} {G {Tail X}} end free: {Tail, G} bound: {X} fun {$ G} fun {$ X} {G {Tail X}} end end free: {Tail} bound: {G, X} ------------------------------------------ What's the difference between an identifier being bound in an expression and a location being bound in the store? Can an identifier that is free in an expression refer to a location that has a determined value in the store? ------------------------------------------ FORMAL DEFINITIONS FOR THE KERNEL % FV() is "the set of free identifiers in " FV(skip) = {} FV( ) = FV() U FV() FV(local in end) = FV() - {} FV( = ) = {, } FV( = ) = {} U FVE() FV(if then else end) = {} U FV() U FV() FV({ ... }) = {, , ..., } FV(case of then else end) = {} U FV() U (FV() - FVE()) % FVE() is "the set of free identifiers in " FVE() = {} FVE() = {} FVE((: ... )) = {, ..., } FVE(proc {$ ... } end) = FV() - {, ..., } % BV() is "the set of bound identifiers in " BV(skip) = {} BV( ) = BV() U BV() BV(local in end) = BV() U (FV() \intersect {}) BV( = ) = {} BV( = ) = BVE() BV(if then else end) = BV() U BV() FV({ ... }) = {} BV(case of then else end) = BV() U BV() U (FV() \intersect FVE()) % BVE() is "the set of bound identifiers in " BVE() = {} BVE() = {} BVE((: ... )) = {} BVE(proc {$ ... } end) = BV() U (FV() \intersect {,...}) ------------------------------------------ How would you generalize these to more complex expressions? iii. procedure values or closures (p. 65) ------------------------------------------ CURRYING function: Append3 = fun {$ LS1 LS2 LS3} {Append LS1 {Append LS2 LS3}} end curried form: CAppend3 = fun {$ LS1} fun {$ LS2} fun {$ LS3} {Append LS1 {Append LS2 LS3}} end end end Use of it: {{{CAppend3 [1 2]} [3 4]} [5 6]} FOR YOU TO DO Curry the following definition: Add = fun {$ X Y} X+Y end Use the curried version to add 2 and 3 ------------------------------------------ How is the binding of LS1 to [1 2] remembered? Can this be done in C++? ------------------------------------------ CURRYING IN C++? #include typedef int (*func)(int); int takes_y(int y) { return(x + y); } func cadd(int x) { return(&takes_y); } int main() { cout << (cadd(2))(3) << endl; } ------------------------------------------ does this work? ------------------------------------------ GRAVITATIONAL FORCE FIELDS AS CURRIED FUNCTIONS declare G = 6.670e~11 %% UNITS: N * m^2 / kg^2 fun {Square R} %% UNITS: m -> m^2 R*R end fun {GravForce M1 R M2} %% UNITS: kg x m x kg -> N if R == 0.0 then 0.0 else G * M1 * M2 / {Square R} end end fun {GravField M1} %% UNITS: kg -> m -> kg -> N fun {$ R} fun {$ M2} if R == 0.0 then 0.0 else G * M1 * M2 / {Square R} end end end end %%% USING IT MassOfEarth = 5.96e24 %% UNITS: kg RadiusOfEarth = 6.37e6 %% UNITS: m EarthsField %% UNITS: m -> kg -> N = {GravField MassOfEarth} ForceAtSurface %% UNITS: kg -> N = {EarthsField RadiusOfEarth} ------------------------------------------ ------------------------------------------ PROCEDURE VALUES ARE CLOSURES def: a *closure* is: code for a procedure and an environment (that remembers the free variables in the body) ------------------------------------------ So, in general, what in C++ is like a closure? b. The abstract machine (2.4.2) (offline, discuss reducer program) i. little step semantics in general ------------------------------------------ COMPUTATION (LITTLE STEP) SEMANTICS Meaning Programs <-------> Answers | ^ input | | output | | v -->* | State ------------> T def: a is in Meaning[[P]] iff ------------------------------------------ ii. terminal transition systems ------------------------------------------ TERMINAL TRANSITION SYSTEM (TTS) (State, -->, T) State: -->: T: -->* reflexive, transitive closure ------------------------------------------ What are the possible outcomes for a program? iii. TTS for Oz ------------------------------------------ TTS FOR OZ (MST,s) in State = state(MST x Store) + msg(String) MST = MultiSet(Thread) Thread = runnable(Stack) + suspended(Stack x Location) Stack = List( x Environment)) T = {({runnable(nil),...,runnable(nil)},s) | s in Store} + Message input[[S]] = ({runnable(S,{})|nil}, {}) output({runnable(nil),...,runnable(nil)}, s)) = s output(msg(Msg)) = Msg ------------------------------------------ What states are terminal? How should we define the transitions (-->)? ------------------------------------------ TRANSITIONS (-->) [skip] (runnable((skip,E) | Rest), s) --> (runnable(Rest), s) [sequence] (runnable((S1 S2, E) | Rest), s) --> (runnable((S1, E) | (S2, E) | Rest), s) [local] (runnable((local X in S end,E)|Rest), s) --> (runnable((S,E')|Rest), s') where E' = E+{X-->x} and x#s' = alloc(s) [var-var binding] (runnable((X=Y, E) | Rest), s) --> (runnable(Rest), s') where s' = unify(s)(E(X), E(Y)) and isStore(s') [var-var bindingerror] (runnable((X=Y, E) | Rest), s) --> (runnable((raise failure(Msg) end, E) | Rest), s') where (Msg,s') = unify(s)(E(X), E(Y)) [value-creation] (runnable((X=V, E) | Rest), s) --> (runnable(Rest), s3) if undetermined(s, E(X)) then v = MV[[V]](E) and s3 = bind(s)(E(X),v) else y#s' = alloc(s) and v = MV[[V]](E) and s'' = bind(s')({y},v) and s3 = unify(s'')(E(X),y) and isStore(s3) [value-creation error] (runnable((X=V, E) | Rest), s) --> (runnable((raise failure(Msg) end, E) | Rest), s3) where y#s' = alloc(s) and v = MV[[V]](E) and s'' = bind(s')({y},v) and (Msg, s3) = unify(s'')(E(X),y) [if-true] (runnable((if X then S1 else S2 end,E)|Rest), s) --> (runnable((S1, E)|Rest), s) where determined(s, E(X)) and s(E(X)) == true [if-false] (runnable((if X then S1 else S2 end, E)|Rest), s) --> (runnable((S2, E)|Rest), s) where determined(s, E(X)) and s(E(X)) == false [if-error] (runnable(if X then S1 else S2 end, E)|Rest), s) --> (runnable((raise error(...) end, E)|Rest), s) where determined(s, E(X)) and not(s(E(X)) == true) and not(s(E(X)) == false) [application] (runnable(({X Y1 ... Yn}, E)|Rest), s) --> (runnable((Body, E')|Rest), s) where determined(s,E(X)) and s(E(X)) in Closure and [Z1 ... Zn] = args(s(E(X))) and Body = body(s(E(X))) and E' = env(s(E(X))) + {Z1 -->E(Y1)} + ... + {Zn -->E(Yn)} [application-error] (runnable(({X Y1 ... Yn}, E)|Rest), s) --> (runnable((raise error(...) end,E) | Rest), s) where determined(s,E(X)) and not(s(E(X)) in Closure) or s(E(X)) does not have n arguments [case-match] (runnable((case X of L(F1: X1 ... Fn:Xn) then S1 else S2 end, E)|Rest), s) --> (runnable((S1, E') | Rest), s) where determined(s,E(X)) and isRecord(s(E(X))) and Label(s(E(X))) == L and Arity(s(E(X))) == [F1 ... Fn] and E' = E + {X1 -->s(E(X)).F1, ..., Xn -->s(E(X)).Fn} [case-else] (runnable((case X of L(F1: X1 ... Fn:Xn) then S1 else S2 end, E)|Rest), s) --> (runnable((S2, E) | Rest), s) where determined(s,E(X)) and not(isRecord(s(E(X)))) or not(Label(s(E(X))) == L) or not(Arity(s(E(X))) == [F1 ... Fn]) ------------------------------------------ What happens if one of the identifiers in var-var binding is not in the domain of the environment, E? What free identifiers are allowed in a program? What's the parameter passing mechanism? What happens to an if-statement when the condition's identifier denotes a location that is not determined? Can the matching case change the store? ------------------------------------------ MEANING OF VALUE EXPRESSIONS MV: ValueExpression -> Environment -> Value MV[[X]](E) = E(X), where X in MV[[N]](E) = N, where N in MV[[L]](E) = L, where L in MV[[L(F1:X1, ..., Fn:Xn)]](E) = L(F1: MV[[X1]](E), ..., Fn: MV[[Xn]](E)), where L(F1:X1, ..., Fn:Xn) in MV[[proc {$ F1 ... Fn} Body end]](E) = (proc {$ F1 ... Fn} Body end, E|FVP), where FVP = FV(Body) \ {F1 ... Fn} is the set of free identifiers in the procedure ------------------------------------------ iv. Examples (2.4.5) ------------------------------------------ EXAMPLES local R in local X in X = 2 R = X end end ({runnable((local R in local X in X = 2 R = X end end, {})|nil)}, {}) --> {by [local]} ({runnable((local X in X = 2 R = X end, {R-->x0})|nil)}, {x0}) --> {by [local]} ({runnable((X = 2 R = X, {R-->x0, X-->x1})|nil)}, {x0, x1}) --> {by [sequence]} ({runnable((X = 2, {R-->x0, X-->x1})|(R = X, {R-->x0, X-->x1})|nil)}, {x0, x1}) --> {by [value-creation]} ({runnable((R = X, {R-->x0, X-->x1})|nil)}, {x0, x1 = 2}) --> {by [var-var binding]} ({runnable(nil)}, {x0 = 2, x1 = 2}) ------------------------------------------ Is this final state terminal? ------------------------------------------ ANOTHER EXAMPLE local X in local Y in Y = proc {$ ?R} R=X end X=true local X in X=false local Z in {Y Z} if Z then skip else Z=X end end end end end We calculate as follows... ({runnable((local X in local Y in Y = proc {$ R} R = X end X = true local X in X = false local Z in {Y Z} if Z then skip else Z = X end end end end end, {})|nil)}, {}) --> {by [local]} ({runnable((local Y in Y = proc {$ R} R = X end X = true local X in X = false local Z in {Y Z} if Z then skip else Z = X end end end end, {X-->x0})|nil)}, {x0}) --> {by [local]} ({runnable((Y = proc {$ R} R = X end X = true local X in X = false local Z in {Y Z} if Z then skip else Z = X end end end, {X-->x0, Y-->x1})|nil)}, {x0, x1}) --> {by [sequence]} ({runnable((Y = proc {$ R} R = X end, {X-->x0, Y-->x1}) |(X = true, {X-->x0, Y-->x1}) |(local X in X = false local Z in {Y Z} if Z then skip else Z = X end end end, {X-->x0, Y-->x1})|nil)}, {x0, x1}) --> {by [value-creation]} ({runnable((X = true, {X-->x0, Y-->x1}) |(local X in X = false local Z in {Y Z} if Z then skip else Z = X end end end, {X-->x0, Y-->x1})|nil)}, {x0, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1})}) --> {by [value-creation]} ({runnable((local X in X = false local Z in {Y Z} if Z then skip else Z = X end end end, {X-->x0, Y-->x1})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1})}) --> {by [local]} ({runnable((X = false local Z in {Y Z} if Z then skip else Z = X end end, {X-->x2, Y-->x1})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2}) --> {by [sequence]} ({runnable((X = false, {X-->x2, Y-->x1}) |(local Z in {Y Z} if Z then skip else Z = X end end, {X-->x2, Y-->x1})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2}) --> {by [value-creation]} ({runnable((local Z in {Y Z} if Z then skip else Z = X end end, {X-->x2, Y-->x1})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2 = false}) --> {by [local]} ({runnable(({Y Z} if Z then skip else Z = X end, {X-->x2, Y-->x1, Z-->x3})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2 = false, x3}) --> {by [sequence]} ({runnable(({Y Z}, {X-->x2, Y-->x1, Z-->x3}) |(if Z then skip else Z = X end, {X-->x2, Y-->x1, Z-->x3})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2 = false, x3}) --> {by [application]} ({runnable((R = X, {X-->x0, Y-->x1, R-->x3}) |(if Z then skip else Z = X end, {X-->x2, Y-->x1, Z-->x3})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2 = false, x3}) --> {by [var-var binding]} ({runnable((if Z then skip else Z = X end, {X-->x2, Y-->x1, Z-->x3})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2 = false, x3 = true}) --> {by [if-true]} ({runnable((skip, {X-->x2, Y-->x1, Z-->x3})|nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2 = false, x3 = true}) --> {by [skip]} ({runnable(nil)}, {x0 = true, x1 = closure(proc {$ R} R = X end {X-->x0, Y-->x1}), x2 = false, x3 = true}) ------------------------------------------ c. Memory management (2.5) i. Memory organization (extra topic) How do we represent the environment and the store in a single address space on a conventional computer? ----------------- | Code | |---------------| | Static Data | | (constants) | |---------------| | run-time | ~ Environment | stack of ARs | | | | | | | v | \\\\\\\\\\\\\\\\| |\\\\\\\\\\\\\\\| | (heap) | ~ Store ----------------- Why is an activation record needed for every *call* of a procedure, instead of one for each procedure? How to access the values of local identifiers in the environment? --------------------- Aho and Ullman's design for Activation Record (using static links): __________________________ RET: | returned value | | (for functions) | |________________________| PAR: | | | actual parameters | | | |________________________| | DL: | dynamic link | | |________________________| | SL: | static link | fixed | | (or display) | size | |________________________| fields | IP: | saved machine status | <_________ EP (env pointer) | | (ip and other regs) | |________________________| VAR: | local data | | (storage for vars) | |________________________| | | TEMP:| temporaries | | | |\\\\\\\\\\\\\\\\\\\\\\\\\ <____ SP (stack pointer) --------------------- does saved part save information about caller or callee? How would this be used in making a call? How would this be used in a return? ii. Last call optimization (2.5.1) What is a last call optimization? ------------------------------------------ % Fully recursive fun {Length Lst} case Lst of _|T then 1+{Length T} else 0 end end Tracing this: {Length 1|2|3|4|nil} = 1+{Length 2|3|4|nil} = 1+(1+{Length 3|4|nil}) = 1+(1+(1+{Length 4|nil})) = 1+(1+(1+(1+{Length nil}))) = 1+(1+(1+(1+0))) = 1+(1+(1+(1))) = 1+(1+(2)) = 1+(3) = 4 Lst Acc 1|2|3|4|nil 0 2|3|4|nil 1 3|4|nil 2 4|nil 3 nil 4 fun {Length Lst} {LengthIter Lst 0} end % Tail recursive fun {LengthIter Lst N} case Lst of _|T then {LengthIter T N+1} else N end end Tracing this: {Length 1|2|3|4|nil} = {LengthIter 1|2|3|4|nil 0} = {LengthIter 2|3|4|nil 1} = {LengthIter 3|4|nil 2} = {LengthIter 4|nil 3} = {LengthIter nil 4} ------------------------------------------ What is it useful for? Does the semantics already to this? Do C, C++, and Java require this optimization? What does that say about using recursion in these languages? iii. Garbage collection (2.5.2-4) Why is garbage collection useful? Does C do garbage collection? C++? Java? What kinds of error does garbage collection prevent? ------------------------------------------ KINDS OF ERRORS GC PREVENTS? ------------------------------------------ Does garbage collection prevent memory leaks? II. Extensions for a Practical Language (2.6-2.8) Why not just program in the kernel language? ------------------------------------------ PICTURE OF SUGARS AND THE KERNEL |---------------------------------| | sugared language | | | | | | | | |------------| | | | kernel | | | | | | | | | | | |------------| | | | | | | | | | | | |---------------------------------| ------------------------------------------ A. Syntactic conventions (2.6.1) ------------------------------------------ SYNTACTIC SUGARS FOR VALUES, DECLARATIONS, AND PATTERNS Let E1, ..., En be expressions, lit, f1, ..., fn be literals, X1, ..., Xn be identifiers lit(f1:E1, ..., fn: En) % sugared ==> local X1 = E1 in % desugared ... local Xn = En in lit(f1:X1, ..., fn:Xn) end ... end local X = E in S end ==> local X in X = E S end R = (local X = E1 in E2 end) ==> local X in X=E1 R=E2 end local X1 ... Xn in S end ==> local X1 in ... local Xn in S end ... end {P E} ==> local X in X=E {P X} end e.g., R = {{CAdd 3} 5} ==> local Three in Three = 3 local C3 in {CAdd Three C3} local Five in Five = 5 {C3 5} end end end local = in end ==> local X1 ... Xn in local X in X = X = end end where {X1,...Xn}=FVE() and X not in (FV() U FVE()) e.g., local H|T = [7 99] in R=(H+1)|T end ==> local H T X0 in X0 = [7 99] X0 = '|'(1:H 2:T) local HP1 = H+1 in R='|'(1:HP1 2:T) end end e.g., [7 99] ==> local Seven=7 NN=99 Nil=nil in local Tail='|'(1:NN 2:Nil) in '|'(1:Seven 2:NN) end end ------------------------------------------ Any conditions on the new identifiers in the local = ... one? How does this get back to kernel syntax? Why do they preserve meaning? ------------------------------------------ PATTERNS IN FUNCTION DEFINITIONS In general: proc {P ... 1 ... n ...} S end ==> proc {P ... X1 ... Xn ...} case X1 of 1 then ... case Xn of n then S end ... end end where X1 ... Xn are fresh Example fun {First A#_} A end ==> fun {First X} case X of A#_ then A end end ==> First = proc {$ X R} case X of '#'(1:A 2:_) then R=A else raise error(kernel(noElse ...)...) end end end ------------------------------------------ How would you call First? How could you use this to define a Tail function for lists? fun {Tail _|T} T end What sugars would help with if statements? ------------------------------------------ IF-RELATED SUGARS if E1 then S1 elseif E2 then S2 else S3 end ==> if E1 then S1 else if E2 then S2 else S3 end end if E then S1 else S2 end ==> local Temp in Temp = E if Temp then S1 else S2 end end where Temp is fresh (Temp not in FV(S1) U FV(S2)) if X0 then X1 in S1 else X2 in S2 end ==> if X0 then local X1 in S1 end else local X2 in S2 end end X in S ==> local X in S end E1 andthen E2 % && ==> if E1 then E2 else false end E1 orelse E2 % || ==> if E1 then true else E2 end if E1 then S1 end ==> if E1 then S1 else skip end ------------------------------------------ How could you desugar the short-circuiting andthen and orelse? What sugars help with case statements? ------------------------------------------ CASE-RELATED SUGARS case X of P1 then S1 end ==> case X of P1 then S1 else raise error(kernel(noElse ...)...) end end case X of P1 then S1 [] P2 then S2 ... [] Pn then Sn else S0 end ==> case X of P1 then S1 else case X of P2 then S2 else ... else case X of Pn then Sn else S0 end end ... end end end case Y of L(F1:X1 ... Fn:Xn) andthen E(X1 ... Xn) then S1 else S2 end ==> case Y of L(F1:X1 ... Fn:Xn) then if E(X1 ... Xn) then S1 else S2 end else S2 end where none of {X1, ..., Xn} are in FV(S2) ------------------------------------------ ------------------------------------------ Q: How would you desugar the use of "andthen" in case clauses? case Y of L(F1:X1 ... Fn:Xn) andthen E(X1...Xn) then S1 else S2 end ==> ------------------------------------------ ------------------------------------------ Q: How would you desugar the use of constants in case clauses? case Y of L(F1:E1 ... Fn:En) then S1 else S2 end ==> case Y of L(F1:X1 ... Fn:Xn) andthen X1==E1 andthen ... andthen Xn==En then S1 else S2 end where none of X1,...,Xn are in FV(S1) or FV(S2) ------------------------------------------ What are these like in C, C++, and Java? ------------------------------------------ NESTING MARKERS Use '$' to turn a statement into an expression Examples: R = {Obj get($)} ==> {Obj get(R)} local X in {Obj get(X)} R = X end R = {P E1 ... Ej($) .. En} ==> {P E1 ... Ej(R) .. En} ------------------------------------------ What's the general rule for this? How would you translate proc {P X} X=Y end ? proc {P X} X=Y end ==> P = proc {$ X} X=Y end fun {Inc X} X+1 end ==> Inc = proc {$ X ?R} local One in One = 1 {Number.'+' X One R} end end Inc = proc {$ X ?R} local One in One = 1 R = {Number.'+' X One $} end end B. Expressions and Functions (2.6.2) ------------------------------------------ DESUGARING FUNCTION STATMENTS AND CALLS Desugaring rule for fun declarations fun {F X1 ... Xn} S E end ==> F = proc{$ X1 ... Xn R} S R=E end where R is fresh (R not in FV(S) U FV(E) U {X1...Xn}) Desugaring calls to functions Z = {F Y1 ... Yn} ==> {F Y1 ... Yn Z} ------------------------------------------ ------------------------------------------ EXPRESSIONS AND FUNCTIONS How to translate into kernel syntax: fun {Add1 X} X+3 end ==> Add1 = proc {$ X ?R} local Thre in Thre = 3 {Number.'+' X Thre R} end end R = {Add1 3} ==> local Three in Three = 3 {Add1 Three R} end R = {Add1 3 * 4} R = {Add1 {Add1 3 * 4}} ------------------------------------------ Can you use these rules in C or Java? C. Interactive Interface (2.6.3) How can you think of declare in terms of kernel syntax? ------------------------------------------ DECLARE EXAMPLE declare X X=1 % Feed the above lines first {Browse 'X='#X} declare X X=3 {Browse 'X='#X} % Vs. local declare Y Y=1 local Y in Y=2 {Browse 'Y='#Y} end {Browse 'Y='#Y} % Static scoping still declare X X=1 fun {F Z} X+Z end declare X X=3 % What does this do? {Browse '{F 4}='#{F 4}} ------------------------------------------ D. Exceptions (2.7) Why do we need exception handling? Why not just check return codes? ------------------------------------------ EXCEPTION HANDLING EXAMPLE proc {Assert B Msg} if B then skip else raise 'Assertion failed: ' # Msg end end end try {Assert false oops} {Browse skipped} catch S#M then {Browse S#M} end {Browse hi} ------------------------------------------ What happens in the above? What languages have exception handling? ------------------------------------------ TRANSITIONS FOR EXCEPTIONS [try] ((try S1 catch X then S2 end, E) | Rest, s) --> ((S1, E) | (catch X then S2 end, E) | Rest, s) [raise] ((raise X end, E) | Rest, s) --> ((Sc, Ec') | Rest', s) where (catch Y then Sc end, Ec) | Rest' = findHandler(Rest) and Ec' = Ec + {Y -->E(X)} [raise-error] ((raise X end, E) | Rest, s) --> "Uncaught exception" where nil = findHandler(Rest) [catch] ((catch X then S2 end, E) | Rest, s) --> (Rest, s) ------------------------------------------ Does the identifier in a raise have to be determined? How would you define findHandler? What's that statement catch X then S2 end added in [try]? Why is its semantics to do nothing? ------------------------------------------ SUGARS try S1 finally S2 end ==> try S1 catch X then S2 raise X end end S2 try S1 catch X then S2 finally S3 end ==> try try S1 catch X then S2 end finally S3 end ------------------------------------------ Do these sugars give the same semantics as in Java? How could we use pattern matching with try? try S1 catch then S2 end ==> try S1 catch X then case X of then S2 else raise X end end end How would you desugar that? What kind of data should be used for exceptions to help matching? E. Functional Languages (2.8.1) 1. foundational calculus (skip) ------------------------------------------ LAMBDA CALCULUS E ::= X | \X . E | E E | (E) parsing rules: scope of \X extends as far as possible application associates to the left example: \x . y z z means (\x . ((y z) z)) In Oz this is E ::= X | fun {$ X} E end | {E E} | (E) example: fun {$ X} {{Y Z} Z} end ------------------------------------------ In what way is this more primitive than the kernel language? How would you write a TTS for the lambda calculus? 2. functional programming on complete values How can we restrict the model to only work with complete values? F. Entailment and disentailment (2.8.2.4) ------------------------------------------ ENTAILMENT X == Y means X and Y are structurally equal blocks if some nodes are different but one is unbound What happens when we do: declare R1 R2 X R1 = pig(weight:100) R2 = pig(weight:X) {Browse R1 == R2} declare R1 R2 X R1 = pig(weight:X) R2 = pig(weight:X) {Browse R1 == R2} declare R1 R2 X R1 = horse(weight:X) R2 = pig(weight:X) {Browse R1 == R2} ------------------------------------------ What answers do these give? G. Static vs. Dynamic Typing (2.8.3) (skip, already covered) ------------------------------------------ STATIC VS. DYNAMIC TYPING def: A *type error* is an attempt to apply an operation outside its domain def: A language has a *static type system* iff all type errors can be discovered before running the program. def: A *dynamic type system* catches type errors at runtime (in general). ------------------------------------------ What kind of typing does Java have? Can a language have no type errors? Is calling a number as a procedure a type error? What are other examples? What about accessing an array outside its bounds? What about casting an object to a type it doesn't have in Java? Which is more general? Which makes separate compilation easier to implement? Which is better for exploratory programming? Which is better for safety critical systems? Which has faster compiled code? Which does Oz have? Is it possible to blend static and dynamic typing?