Skip to content

Commit

Permalink
version 4.0.7 more robust
Browse files Browse the repository at this point in the history
  • Loading branch information
ycaseau committed Jan 22, 2023
1 parent c400915 commit ab52a7b
Show file tree
Hide file tree
Showing 51 changed files with 1,558 additions and 1,243 deletions.
2 changes: 2 additions & 0 deletions compile/goexample.go.cl
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,8 @@ C_class = MakeClass("name",superclass,module) // module is where the class i
go_class(c) = ModClass, class_ident = <mod.>C_class
examples : ClaireClass OptimizeCallSpecial => Kernel.C_class, Optimize.C_Call_special

because of forward, we need NewClass("name",superclass,module) which looks for a class with that name first

// adding a slot
func (c *ClaireClass) AddSlot(p *ClaireProperty, r *ClaireType, def *ClaireAny) EID {
note that we do not handle the index
Expand Down
2 changes: 1 addition & 1 deletion compile/goexp.cl
Original file line number Diff line number Diff line change
Expand Up @@ -389,7 +389,7 @@ g_expression(self:Call_method,s:class) : void -> inline_exp(PRODUCER,self,s)
-> let m := self.arg, p := m.selector,
a1 := self.args[1], a2 := self.args[2], s1 := class!(c_type(a1)) in
( if (p = class! & a1 % symbol)
printf("~I = MakeClass(~S,~I,~I)", symbol_ident(a1),
printf("~I = NewClass(~S,~I,~I)", symbol_ident(a1),
string!(a1), // name
g_expression(a2,class), // superclass
g_expression(module!(a1),module)) // <yc> 7/98 safer (was current_module)
Expand Down
10 changes: 6 additions & 4 deletions compile/gogen.cl
Original file line number Diff line number Diff line change
Expand Up @@ -271,7 +271,8 @@ c_string(c:go_producer, self:symbol) : string
else if (m2.module! = m.module! & c ^ m2.domain[1] != {})
arg_match(go_signature(m2), %sig)
else true),
any defined(m.selector.name) = Kernel)))), // v4.0.6: mix of methods & slot are not supported with Go
any (defined(m.selector.name) = Kernel & // v4.0.6: mix of methods & slot are not supported with Go
module!(m2) = Kernel))))), // we make an exception for Kernel methods
any false)) ]


Expand Down Expand Up @@ -478,15 +479,16 @@ c_string(c:go_producer, self:symbol) : string
else if (s = integer) printf("INT(")
else if (s = float) printf("FLOAT(")
else if (s = char) printf("CHAR(")
else if (s = any | s = primitive) printf("ANY(")
else if (s = primitive) printf("ToPrimitive(ANY(")
else if (s = any) printf("ANY(")
else if (s <= object | s = array | s = string | s = port | s = function)
printf("~I(OBJ(",cast_class(s))
else if (s != any) error("what the fuck: eid prefix for ~S",s) ]

[eid_post(s:class) : void
-> if (s = EID | s = void) nil
else if (s = char | s = any | s = primitive) princ(")")
else if (s <= object | s = array | s = string | s = port | s = function) printf("))")
else if (s = char | s = any) princ(")")
else if (s <= object | s = array | s = string | s = port | s = function | s = primitive) printf("))")
else if (s != any) princ(")") ]

// move from an integer to a EID or Object
Expand Down
1 change: 1 addition & 0 deletions compile/gomain.cl
Original file line number Diff line number Diff line change
Expand Up @@ -138,6 +138,7 @@
trace(0,"=== Light Module ~S:~S -> use ~S=== ", m, m.uses,claire_modules)),
claire_modules :add m,
load(get_value("Compile")), // load the compiler
jito?() := false, // turn just-in-time compiling off (sub optimal compared to compiler)
compiler.active? := true,
if (%out != "") external(m) := %out,
load(m), // load the module
Expand Down
21 changes: 15 additions & 6 deletions compile/gostat.cl
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,7 @@ unfold_use(ldef:list,x:any,s:class,v:string,err:boolean,loop:any) : void
[g_try(self:any,v:string,e:class,vglobal:string,loop:any) : void
-> let v2 := (if (e = EID) v else genvar("try_")) in
(if (e != EID) var_declaration(v2,EID,1),
if PRODUCER.debug? printf("/*g_try(v2:~S,loop:~S) */~I",v2,loop,breakline()),
if PRODUCER.debug? printf("/*g_try(v2:~S,loop:~S,e:~S) */~I",v2,loop,e,breakline()),
g_statement(self,EID,v2,true,loop),
// AUDACIEUX: if self is a Do, and we have a loop, break statements cover the error case
if (self % Do & loop % Tuple) printf("{~I",breakline())
Expand Down Expand Up @@ -205,20 +205,29 @@ unfold_eid(ldef:list,self:any,s:class, v:any,err:boolean,loop:any) : void
(if (length(x.args) >= 3) (princ(","), eid_expression(x.args[3],EID,lvar))),
(if (length(x.args) = 4) (princ(","), eid_expression(x.args[4],EID,lvar))))
else if (x.arg = *read_property*)
printf("~I.ReadEID(~I)",g_expression(x.args[1],property),
printf("~I.ReadEID(~I)",g_eid_expression(x.args[1],property,lvar),
eid_expression(x.args[2],EID,lvar))
else if (x.arg.selector = write_fast)
printf("~I.WriteEID(~I,~I)",g_expression(x.args[1],property),
g_expression(x.args[2],object),
g_eid_expression(x.args[2],object,lvar),
eid_expression(x.args[3],EID,lvar))
else if (x.arg.selector = nth_write)
printf("~I.WriteEID(~I,~I)",g_expression(x.args[1],list),
g_expression(x.args[2],integer),
printf("~I.WriteEID(~I,~I)",g_eid_expression(x.args[1],list),
g_eid_expression(x.args[2],integer,lvar),
eid_expression(x.args[3],EID,lvar))
else printf("~I.WriteEID(~I)",g_expression(x.args[1],Variable),
else printf("~I.WriteEID(~I)",g_eid_expression(x.args[1],Variable,lvar),
eid_expression(x.args[2],EID,lvar))),
any g_expression(x,s)) ]

// reverse from eid (the args of the call have been EIDed : represented by an EID var)
// hence when we need a regular object, we must check that the arg x is not in the var list
[g_eid_expression(x:any,s:class,lvar:list<Variable>) : void
-> case x
(Variable (if (x % lvar) (eid_prefix(s),
princ(c_string(PRODUCER,x)),
eid_post(s))
else g_expression(x,s)),
any g_expression(x,s)) ]

//**********************************************************************
//* Part 3: Basic control structures *
Expand Down
10 changes: 6 additions & 4 deletions compile/gosystem.cl
Original file line number Diff line number Diff line change
Expand Up @@ -659,10 +659,12 @@ parents(self:list) : list
// however is c_type(exp) is void we need to return CNULL
[function_body(self:any,s:class) : void
-> let %ret := (if (s != void) "return " else "") in
// (if (s = boolean) // this is an old optimization that is USELESS in CLAIRE4
// printf("if ~I {return CTRUE~I} else {return CFALSE}",bool_exp(self,true),breakline())
// else printf("~A ~I~I", %ret, g_expression(self,s),breakline())) ]
(if (c_type(self) = void & s != void)
(if (s = boolean & (case self (Call_method (let p := self.arg.selector in
(p = = | p = < | p = > | p = >= | p = <=) ))))
// this is an old optimization - there is a debate if this is still needed with CLAIRE4
// reintroduced in v4.0.7 for mSend, but only for direct comparisons
printf("if ~I {return CTRUE~I} else {return CFALSE}",bool_exp(self,true),breakline())
else if (c_type(self) = void & s != void)
printf("~I~Ireturn ~I~I",
g_expression(self,void), breakline(),
g_expression(unknown,s), breakline())
Expand Down
Loading

0 comments on commit ab52a7b

Please sign in to comment.