diff options
author | dos-reis <gdr@axiomatics.org> | 2010-07-12 16:33:55 +0000 |
---|---|---|
committer | dos-reis <gdr@axiomatics.org> | 2010-07-12 16:33:55 +0000 |
commit | e5f701265114472fd307faff46539a5c619faf2a (patch) | |
tree | 6a2615b95dce683802fed0c3d7c2deef410b6040 /src | |
parent | e15a618f184aeb8cfd29128e610c336ccd4a984b (diff) | |
download | open-axiom-e5f701265114472fd307faff46539a5c619faf2a.tar.gz |
cleanups
Diffstat (limited to 'src')
46 files changed, 127 insertions, 127 deletions
diff --git a/src/interp/br-con.boot b/src/interp/br-con.boot index bf412deb..f8413bfa 100644 --- a/src/interp/br-con.boot +++ b/src/interp/br-con.boot @@ -49,7 +49,7 @@ namespace BOOT -- atom a => b -- a := conform2OutputForm a -- [mathform2HtString x for x in rest a] --- if not atom a then a := first a +-- if cons? a then a := first a -- da := DOWNCASE a -- pageName := LASSQ(da,'((type . CategoryType)(union . DomainUnion)(record . DomainRecord)(mapping . DomainMapping))) => -- downlink pageName --special jump out for primitive domains @@ -65,7 +65,7 @@ conPage(a,:b) == atom a => [a,:b] a $conArgstrings: local := [form2HtString x for x in KDR a] - if not atom a then a := first a + if cons? a then a := first a da := DOWNCASE a pageName := LASSQ(da,'((type . CategoryType)(union . DomainUnion)(record . DomainRecord)(mapping . DomainMapping)(enumeration . DomainEnumeration))) => downlink pageName --special jump out for primitive domains @@ -743,7 +743,7 @@ conOpPage1(conform,:options) == MEMQ(conname,$DomainNames) => dbSpecialOperations conname domname := --> !!note!! <-- - null atom conform => conform + cons? conform => conform nil line := conPageFastPath conname [kind,name,nargs,xflag,sig,args,abbrev,comments]:=parts:= dbXParts(line,7,1) diff --git a/src/interp/br-data.boot b/src/interp/br-data.boot index 0518b21a..0ff40dcd 100644 --- a/src/interp/br-data.boot +++ b/src/interp/br-data.boot @@ -740,7 +740,7 @@ sublisFormal(args,exp,:options) == main where x is [.,:.] => acc := nil y := x - while null atom y repeat + while cons? y repeat acc := [sublisFormal1(args,first y,n),:acc] y := rest y r := nreverse acc diff --git a/src/interp/br-op1.boot b/src/interp/br-op1.boot index 169175ba..a7520da8 100644 --- a/src/interp/br-op1.boot +++ b/src/interp/br-op1.boot @@ -818,12 +818,12 @@ dbExpandOpAlistIfNecessary(htPage,opAlist,which,needOrigins?,condition?) == --Case 1: Already expanded; just cons it onto ACC null string? line => --already expanded if condition? then --this could have been expanded at a lower level - if null atom (pred := second line) then value := pred + if cons? (pred := second line) then value := pred acc := [line,:acc] --this one is already expanded; record it anyway --Case 2: unexpanded; expand it then cons it onto ACC [name,nargs,xflag,sigs,conname,pred,comments] := dbParts(line,7,1) predicate := ncParseFromString pred - if condition? and null atom predicate then value := predicate + if condition? and cons? predicate then value := predicate sig := ncParseFromString sigs --is (Mapping,:.) if which = '"operation" then if sig isnt ['Mapping,:.] @@ -853,7 +853,7 @@ dbExpandOpAlistIfNecessary(htPage,opAlist,which,needOrigins?,condition?) == for [op,:alist] in opAlist repeat for [sig,:tail] in alist repeat condition? => --the only purpose here is to find a non-trivial pred - null atom (pred := first tail) => return ($value := pred) + cons? (pred := first tail) => return ($value := pred) 'skip u := tail is [.,origin,:.] and origin => @@ -864,7 +864,7 @@ dbExpandOpAlistIfNecessary(htPage,opAlist,which,needOrigins?,condition?) == dbGetDocTable(op,sig,docTable,which,nil) origin := IFCAR u or origin docCode := IFCDR u --> (doc . code) --- if null FIXP rest docCode then harhar(op) --> +-- if not FIXP rest docCode then harhar(op) --> if null doc and which = '"attribute" then doc := getRegistry(op,sig) tail.rest := [origin,isExposedConstructor opOf origin,:docCode] $value => return $value @@ -949,14 +949,14 @@ getDomainOpTable(dom,fromIfTrue,:options) == info := null predValue => 1 -- signifies not exported - null fromIfTrue => nil + not fromIfTrue => nil cell := compiledLookup(op,sig1,dom) => [f,:r] := cell f = 'nowhere => 'nowhere --see replaceGoGetSlot f = 'makeSpadConstant => 'constant f = function IDENTITY => 'constant f = 'newGoGet => substitute('_$,domname,devaluate first r) - null VECP r => systemError devaluateList r + not VECP r => systemError devaluateList r substitute('_$,domname,devaluate r) 'nowhere [sig1,:info] diff --git a/src/interp/br-prof.boot b/src/interp/br-prof.boot index a154127a..4f4983c8 100644 --- a/src/interp/br-prof.boot +++ b/src/interp/br-prof.boot @@ -248,7 +248,7 @@ hasNewInfoAlist conname == hasNewInfoText u == and/[atom op and "and"/[item is [sig,:alist] and - null sig or null atom sig and null atom alist for item in items] for [op,:items] in u] + null sig or cons? sig and cons? alist for item in items] for [op,:items] in u] getInfoAlist conname == cat? := getConstructorKindFromDB conname = "category" diff --git a/src/interp/br-saturn.boot b/src/interp/br-saturn.boot index c7972406..d5daf12b 100644 --- a/src/interp/br-saturn.boot +++ b/src/interp/br-saturn.boot @@ -1012,7 +1012,7 @@ dbGatherThenShow(htPage,opAlist,which,data,constructorIfTrue,word,fn) == atom thing => '"unconditional" '"" htSay '"}" - if null atom thing then + if cons? thing then if constructorIfTrue then htSay('" {\em ",dbShowKind thing,'"}") htSay '" " FUNCALL(fn,thing) diff --git a/src/interp/c-doc.boot b/src/interp/c-doc.boot index 90bf1925..5364f38f 100644 --- a/src/interp/c-doc.boot +++ b/src/interp/c-doc.boot @@ -44,7 +44,7 @@ batchExecute() == getDoc(conName,op,modemap) == [dc,target,sl,pred,D] := simplifyModemap modemap sig := [target,:sl] - null atom dc => + cons? dc => sig := MSUSBT('$,dc,sig) sig := SUBLISLIS($FormalMapVariableList,rest dc,sig) getDocForDomain(conName,op,sig) @@ -280,7 +280,7 @@ transformAndRecheckComments(name,lines) == $exposeFlagHeading : local := atom name => ['" -- ",name] concat('" --",formatOpSignature(name.0, escapePercent name.1)) - if null $exposeFlag then sayBrightly $exposeFlagHeading + if not $exposeFlag then sayBrightly $exposeFlagHeading u := checkComments(name,lines) $recheckingFlag := true checkRewrite(name,[u]) @@ -315,7 +315,7 @@ checkRewrite(name,lines) == main where --similar to checkComments from c-doc u := checkAddMacros u u := checkTexht u -- checkBalance u - okBefore := null $checkErrorFlag + okBefore := not $checkErrorFlag checkArguments u if $checkErrorFlag then u := checkFixCommonProblem u checkRecordHash u @@ -1302,10 +1302,10 @@ checkDecorateForHt u == if $checkingXmptex? then checkDocError ["Symbol ",x,'" appearing outside \spad{}"] x = '"$" or x = '"%" => checkDocError ['"Unescaped ",x] --- null spadflag and string? x and (member(x,$argl) or #x = 1 +-- not spadflag and string? x and (member(x,$argl) or #x = 1 -- and alphabetic? x.0) and not member(x,'("a" "A")) => -- checkDocError1 ['"Naked ",x] --- null spadflag and string? x and (not x.0 = $charBack and not digit?(x.0) and digit?(x.(MAXINDEX x))or member(x,'("true" "false"))) +-- not spadflag and string? x and (not x.0 = $charBack and not digit?(x.0) and digit?(x.(MAXINDEX x))or member(x,'("true" "false"))) -- => checkDocError1 ["Naked ",x] u := rest u u diff --git a/src/interp/cattable.boot b/src/interp/cattable.boot index 5366ee32..ff4066a4 100644 --- a/src/interp/cattable.boot +++ b/src/interp/cattable.boot @@ -359,7 +359,7 @@ makeCatPred(zz, cats, thePred) == if zz is ['IF,curPred := ["has",z1,z2],ats,.] then ats := if ats is ['PROGN,:atl] then atl else [ats] for at in ats repeat - if at is ['ATTRIBUTE,z3] and not atom z3 and + if at is ['ATTRIBUTE,z3] and cons? z3 and constructor? first z3 then cats:= [['IF,quickAnd(["has",z1,z2], thePred),z3,'%noBranch],:cats] at is ['IF, pred, :.] => diff --git a/src/interp/clam.boot b/src/interp/clam.boot index e23456be..5b1eed1d 100644 --- a/src/interp/clam.boot +++ b/src/interp/clam.boot @@ -610,18 +610,18 @@ hputNewProp(ht,op,argList,val) == listTruncate(l,n) == u:= l n:= QSSUB1 n - while n ~= 0 and null atom u repeat + while n ~= 0 and cons? u repeat n:= QSSUB1 n u:= rest u - if null atom u then - if null atom rest u and $reportInstantiations = true then + if cons? u then + if cons? rest u and $reportInstantiations = true then recordInstantiation($op,CAADR u,true) u.rest := nil l lassocShift(x,l) == y:= l - while not atom y repeat + while cons? y repeat EQUAL(x,first first y) => return (result := first y) y:= rest y result => @@ -633,7 +633,7 @@ lassocShift(x,l) == lassocShiftWithFunction(x,l,fn) == y:= l - while not atom y repeat + while cons? y repeat FUNCALL(fn,x,first first y) => return (result := first y) y:= rest y result => @@ -645,7 +645,7 @@ lassocShiftWithFunction(x,l,fn) == lassocShiftQ(x,l) == y:= l - while not atom y repeat + while cons? y repeat EQ(x,first first y) => return (result := first y) y:= rest y result => @@ -657,7 +657,7 @@ lassocShiftQ(x,l) == -- rassocShiftQ(x,l) == -- y:= l --- while not atom y repeat +-- while cons? y repeat -- EQ(x,rest first y) => return (result := first y) -- y:= rest y -- result => diff --git a/src/interp/clammed.boot b/src/interp/clammed.boot index 18632214..e19e03ba 100644 --- a/src/interp/clammed.boot +++ b/src/interp/clammed.boot @@ -123,7 +123,7 @@ isValidType form == -- Arguments to constructors are general expressions. Below -- domain constructors are not considered valid arguments (yet). x' := opOf x - not atom x' or not IDENTP x' => true -- surely not constructors + cons? x' or not IDENTP x' => true -- surely not constructors getConstructorKindFromDB x' ~= "domain" selectMms1(op,tar,args1,args2,$Coerce) == diff --git a/src/interp/compiler.boot b/src/interp/compiler.boot index 77212ee9..4999b870 100644 --- a/src/interp/compiler.boot +++ b/src/interp/compiler.boot @@ -170,7 +170,7 @@ compNoStacking1(x,m,e,$compStack) == comp2(x,m,e) == [y,m',e]:= comp3(x,m,e) or return nil - --if null atom y and isDomainForm(y,e) then e := addDomain(x,e) + --if cons? y and isDomainForm(y,e) then e := addDomain(x,e) --line commented out to prevent adding derived domain forms m~=m' and ($bootStrapMode or isDomainForm(m',e))=>[y,m',addDomain(m',e)] --isDomainForm test needed to prevent error while compiling Ring @@ -639,7 +639,7 @@ compFormWithModemap(form,m,e,modemap) == getFormModemaps(form is [op,:argl],e) == op is ["elt",domain,op1] => [x for x in getFormModemaps([op1,:argl],e) | x is [[ =domain,:.],:.]] - not atom op => nil + cons? op => nil modemapList:= get(op,"modemap",e) -- Within default implementations, modemaps cannot mention the -- current domain. diff --git a/src/interp/define.boot b/src/interp/define.boot index 350a5eb9..ca7d8386 100644 --- a/src/interp/define.boot +++ b/src/interp/define.boot @@ -795,7 +795,7 @@ displayMissingFunctions() == null $CheckVectorList => nil loc := nil -- list of local operation signatures exp := nil -- list of exported operation signatures - for [[op,sig,:.],:pred] in $CheckVectorList | null pred repeat + for [[op,sig,:.],:pred] in $CheckVectorList | not pred repeat not member(op,$formalArgList) and getmode(op,$e) is ['Mapping,:.] => loc := [[op,sig],:loc] exp := [[op,sig],:exp] @@ -872,7 +872,7 @@ genDomainView(viewName,originalName,c,viewSelector) == c $e:= augModemapsFromCategory(originalName,viewName,nil,c,$e) cd:= ["%LET",viewName,[viewSelector,originalName,mkTypeForm code]] - if null member(cd,$getDomainCode) then + if not member(cd,$getDomainCode) then $getDomainCode:= [cd,:$getDomainCode] viewName @@ -1034,7 +1034,7 @@ compDefineCapsuleFunction(df is ['DEF,form,signature,specialCases,body], rettype:= resolve(signature'.target,$returnMode) localOrExported := - null member($op,$formalArgList) and + not member($op,$formalArgList) and getmode($op,e) is ['Mapping,:.] => 'local 'exported @@ -1241,7 +1241,7 @@ compile u == $savableItems := [unew, :$saveableItems] -- tested by embedded RWRITE optimizedBody:= optimizeFunctionDef u stuffToCompile:= - if null $insideCapsuleFunctionIfTrue + if not $insideCapsuleFunctionIfTrue then optimizedBody else putInLocalDomainReferences optimizedBody $doNotCompileJustPrint=true => (PRETTYPRINT stuffToCompile; op') @@ -1692,7 +1692,7 @@ DomainSubstitutionFunction(parameters,body) == ++ environment `env'. compSignature(opsig,pred,env) == [op,:sig] := opsig - not atom op => + cons? op => for y in op repeat compSignature([y,:sig],pred,env) op in '(per rep) => diff --git a/src/interp/functor.boot b/src/interp/functor.boot index 1449309a..c4b4b411 100644 --- a/src/interp/functor.boot +++ b/src/interp/functor.boot @@ -193,7 +193,7 @@ CategoriesFromGDC x == compCategories u == atom u => u - not atom first u => + cons? first u => error ['"compCategories: need an atom in operator position", first u] first u = "Record" => -- There is no modemap property for these guys so do it by hand. @@ -455,7 +455,7 @@ DescendCodeAdd1(base,flag,target,formalArgs,formalArgModes) == n:=MAXINDEX cat code:= [u - for i in 6..n | not atom cat.i and not atom (sig:= first cat.i) + for i in 6..n | cons? cat.i and cons? (sig:= first cat.i) and (u:= SetFunctionSlots(SUBLIS(slist,sig),['ELT,instantiatedBase,i],flag, diff --git a/src/interp/g-cndata.boot b/src/interp/g-cndata.boot index 80c26f33..0aaa9f30 100644 --- a/src/interp/g-cndata.boot +++ b/src/interp/g-cndata.boot @@ -105,7 +105,7 @@ getConstructorUnabbreviation op == abbreviation?(op) or throwKeyedMsg("S2IL0019",[op]) mkUserConstructorAbbreviation(c,a,type) == - if not atom c then c := first c -- Existing constructors will be wrapped + if cons? c then c := first c -- Existing constructors will be wrapped constructorAbbreviationErrorCheck(c,a,type,'abbreviationError) clearClams() clearConstructorCache(c) diff --git a/src/interp/g-opt.boot b/src/interp/g-opt.boot index 1670e994..a11855ff 100644 --- a/src/interp/g-opt.boot +++ b/src/interp/g-opt.boot @@ -218,7 +218,7 @@ optCatch (x is ["CATCH",g,a]) == x optSPADCALL(form is ['SPADCALL,:argl]) == - null $InteractiveMode => form + not $InteractiveMode => form -- last arg is function/env, but may be a form argl is [:argl,fun] and fun is ["ELT",dom,slot] => optCall ['%call,['ELT,dom,slot],:argl] diff --git a/src/interp/g-timer.boot b/src/interp/g-timer.boot index 85bce196..edd7020d 100644 --- a/src/interp/g-timer.boot +++ b/src/interp/g-timer.boot @@ -140,7 +140,7 @@ startTimingProcess name == if EQ(name, 'load) then statRecordLoadEvent() stopTimingProcess name == - (name ~= peekTimedName()) and null $InteractiveMode => + (name ~= peekTimedName()) and not $InteractiveMode => keyedSystemError("S2GL0015",[name,peekTimedName()]) updateTimedName peekTimedName() popTimedName() diff --git a/src/interp/g-util.boot b/src/interp/g-util.boot index 267df900..cf7da6ce 100644 --- a/src/interp/g-util.boot +++ b/src/interp/g-util.boot @@ -459,7 +459,7 @@ isSharpVar x == IDENTP x and SCHAR(SYMBOL_-NAME x,0) = char "#" isSharpVarWithNum x == - null isSharpVar x => nil + not isSharpVar x => nil (n := QCSIZE(p := PNAME x)) < 2 => nil ok := true c := 0 @@ -583,7 +583,7 @@ get(x,prop,e) == get1(x,prop,e) get0(x,prop,e) == - not atom x => get(x.op,prop,e) + cons? x => get(x.op,prop,e) u:= QLASSQ(x,first first e) => QLASSQ(prop,u) (tail:= rest first e) and (u:= fastSearchCurrentEnv(x,tail)) => QLASSQ(prop,u) @@ -591,7 +591,7 @@ get0(x,prop,e) == get1(x,prop,e) == --this is the old get - not atom x => get(x.op,prop,e) + cons? x => get(x.op,prop,e) prop="modemap" and $insideCapsuleFunctionIfTrue=true => LASSOC("modemap",getProplist(x,$CapsuleModemapFrame)) or get2(x,prop) @@ -617,7 +617,7 @@ put(x,prop,val,e) == $InteractiveMode and not EQ(e,$CategoryFrame) => putIntSymTab(x,prop,val,e) --e must never be $CapsuleModemapFrame - not atom x => put(first x,prop,val,e) + cons? x => put(first x,prop,val,e) newProplist := augProplistOf(x,prop,val,e) prop="modemap" and $insideCapsuleFunctionIfTrue=true => SAY ["**** modemap PUT on CapsuleModemapFrame: ",val] @@ -628,7 +628,7 @@ put(x,prop,val,e) == addBinding(x,newProplist,e) putIntSymTab(x,prop,val,e) == - null atom x => putIntSymTab(first x,prop,val,e) + cons? x => putIntSymTab(first x,prop,val,e) pl0 := pl := search(x,e) pl := null pl => [[prop,:val]] @@ -836,7 +836,7 @@ centerString(text,width,fillchar) == stringPrefix?(pref,str) == -- sees if the first #pref letters of str are pref -- replaces STRINGPREFIXP - null (string?(pref) and string?(str)) => NIL + not (string?(pref) and string?(str)) => NIL (lp := QCSIZE pref) = 0 => true lp > QCSIZE str => NIL ok := true @@ -851,7 +851,7 @@ stringChar2Integer(str,pos) == -- returns small integer represented by character in position pos -- in string str. Returns NIL if not a digit or other error. if IDENTP str then str := PNAME str - null (string?(str) and + not (string?(str) and integer?(pos) and (pos >= 0) and (pos < QCSIZE(str))) => NIL not digit?(d := SCHAR(str,pos)) => NIL DIG2FIX d @@ -1085,7 +1085,7 @@ searchCurrentEnv: (%Thing,%List) -> %List searchTailEnv: (%Thing,%Env) -> %List getProplist(x,E) == - not atom x => getProplist(first x,E) + cons? x => getProplist(first x,E) u:= search(x,E) => u --$InteractiveMode => nil --$InteractiveMode and (u:= search(x,$InteractiveFrame)) => u diff --git a/src/interp/ht-util.boot b/src/interp/ht-util.boot index a6907b8c..a4781e09 100644 --- a/src/interp/ht-util.boot +++ b/src/interp/ht-util.boot @@ -397,7 +397,7 @@ pvarCondList1(pvarList, activeConds, condList) == pvarCondList1(pvarList, activeConds, restConds) pvarsOfPattern pattern == - null LISTP pattern => nil + not LISTP pattern => nil [pvar for pvar in rest pattern | pvar in $PatternVariableList] htMakeTemplates(templateList, numLabels) == diff --git a/src/interp/htcheck.boot b/src/interp/htcheck.boot index 70ac5d43..48f8f07f 100644 --- a/src/interp/htcheck.boot +++ b/src/interp/htcheck.boot @@ -98,7 +98,7 @@ buildHtMacroTable() == $htMacroTable getHtMacroItem line == - null stringPrefix?('"\newcommand{",line) => nil + not stringPrefix?('"\newcommand{",line) => nil k := charPosition(char '_},line,11) command := SUBSTRING(line,12,k - 12) numOfArgs := diff --git a/src/interp/i-analy.boot b/src/interp/i-analy.boot index 4cb9bbe5..c43236f3 100644 --- a/src/interp/i-analy.boot +++ b/src/interp/i-analy.boot @@ -511,7 +511,7 @@ bottomUpForm3(t,op,opName,argl,argModeSetList) == bottomUpForm2(t,op,opName,argl,argModeSetList) bottomUpForm2(t,op,opName,argl,argModeSetList) == - not atom t and opName="%%" => bottomUpPercent t + cons? t and opName="%%" => bottomUpPercent t opVal := getValue op -- for things with objects in operator position, be careful before @@ -568,7 +568,7 @@ removeUnionsAtStart(argl,modeSets) == m := objMode(v) m isnt ['Union,:.] => nil val := objVal(v) - null isWrapped val => nil + not isWrapped val => nil val' := retract v m' := objMode val' putValue(arg,val') diff --git a/src/interp/i-coerce.boot b/src/interp/i-coerce.boot index 1bf238fd..a7b879da 100644 --- a/src/interp/i-coerce.boot +++ b/src/interp/i-coerce.boot @@ -948,7 +948,7 @@ compareTypeLists(tl1,tl2) == -- returns true if every type in tl1 is = or is a subdomain of -- the corresponding type in tl2 for t1 in tl1 for t2 in tl2 repeat - null isEqualOrSubDomain(t1,t2) => return NIL + not isEqualOrSubDomain(t1,t2) => return NIL true coerceIntAlgebraicConstant(object,t2) == diff --git a/src/interp/i-coerfn.boot b/src/interp/i-coerfn.boot index ce8d47a2..bc5d05cc 100644 --- a/src/interp/i-coerfn.boot +++ b/src/interp/i-coerfn.boot @@ -1284,7 +1284,7 @@ Sm2PolyType(u,source is [sm,n,S], target is [pol,vl,T]) == -- first want to check case S is Polynomial S is ['Polynomial,S'] => -- check to see if variable occurs in any of the terms - if ATOM vl + if atom vl then vl' := [vl] else vl' := vl novars := true diff --git a/src/interp/i-funsel.boot b/src/interp/i-funsel.boot index 51b3ccde..5bf952e7 100644 --- a/src/interp/i-funsel.boot +++ b/src/interp/i-funsel.boot @@ -1335,7 +1335,7 @@ evalMmCat(op,sig,stack,SL) == S='failed and $hope => stack:= [mmC,:stack] S = 'failed => return S - not atom S => + cons? S => makingProgress:= 'T SL:= mergeSubs(S,SL) if stack or S='failed then 'failed else SL @@ -1613,11 +1613,11 @@ hasAtt(dom,att,SL) == --UGH! New world has attributes stored as pairs not as lists!! for [x,:cond] in atts until not (S='failed) repeat S:= unifyStruct(x,att,copy SL) - not atom cond and not (S='failed) => S := hasCatExpression(cond,S) + cons? cond and not (S='failed) => S := hasCatExpression(cond,S) S for [x,cond] in atts until not (S='failed) repeat S:= unifyStruct(x,att,copy SL) - not atom cond and not (S='failed) => S := hasCatExpression(cond,S) + cons? cond and not (S='failed) => S := hasCatExpression(cond,S) S 'failed 'failed @@ -1637,8 +1637,8 @@ unifyStruct(s1,s2,SL) == s1=s2 => SL if s1 is [":",x,.] then s1:= x if s2 is [":",x,.] then s2:= x - if not atom s1 and first s1 = '_# then s1:= # second s1 - if not atom s2 and first s2 = '_# then s2:= # second s2 + if cons? s1 and first s1 = '_# then s1:= # second s1 + if cons? s2 and first s2 = '_# then s2:= # second s2 s1=s2 => SL isPatternVar s1 => unifyStructVar(s1,s2,SL) isPatternVar s2 => unifyStructVar(s2,s1,SL) @@ -1659,7 +1659,7 @@ unifyStructVar(v,s,SL) == (s0 := LASSOC(v, SL)) or (s0 := LASSOC(v,$Subst)) => S:= unifyStruct(s0,s1,copy SL) S='failed => - $Coerce and not atom s0 and constructor? first s0 => + $Coerce and cons? s0 and constructor? first s0 => containsVars s0 or containsVars s1 => ns0 := subCopy(s0, SL) ns1 := subCopy(s1, SL) diff --git a/src/interp/i-map.boot b/src/interp/i-map.boot index ed313aca..f2512ced 100644 --- a/src/interp/i-map.boot +++ b/src/interp/i-map.boot @@ -60,7 +60,7 @@ isInternalMapName name == (not IDENTP(name)) or (name = "*") or (name = "**") => false sz := SIZE (name' := PNAME name) (sz < 7) or (char("*") ~= name'.0) => false - null digit? name'.1 => false + not digit? name'.1 => false null STRPOS('"_;",name',1,NIL) => false -- good enough true diff --git a/src/interp/i-object.boot b/src/interp/i-object.boot index ea3ddff7..86fbe547 100644 --- a/src/interp/i-object.boot +++ b/src/interp/i-object.boot @@ -249,7 +249,7 @@ getMode x == ++ sets the mode for the VAT node x to y. putMode(x,y) == x is [op,:.] => putMode(op,y) - null VECP x => keyedSystemError("S2II0001",[x]) + not VECP x => keyedSystemError("S2II0001",[x]) x.1 := y ++ returns an interpreter object that represents the value of node x. @@ -265,7 +265,7 @@ getValue x == ++ sets the value of VAT node x to interpreter object y. putValue(x,y) == x is [op,:.] => putValue(op,y) - null VECP x => keyedSystemError("S2II0001",[x]) + not VECP x => keyedSystemError("S2II0001",[x]) x.2 := y ++ same as putValue(vec, val), except that vec is returned instead of val. @@ -289,7 +289,7 @@ getUnname x == ++ Subroutine of getUnname. getUnname1 x == VECP x => x.0 - null atom x => keyedSystemError("S2II0001",[x]) + cons? x => keyedSystemError("S2II0001",[x]) x ++ returns the mode-set of VAT node x. @@ -302,7 +302,7 @@ getModeSet x == y keyedSystemError("S2GE0016",['"getModeSet",'"no mode set"]) m:= getBasicMode x => [m] - not atom x => getModeSet first x + cons? x => getModeSet first x keyedSystemError("S2GE0016",['"getModeSet", '"not an attributed tree"]) @@ -348,7 +348,7 @@ getModeSetUseSubdomain x == keyedSystemError("S2GE0016", ['"getModeSetUseSubomain",'"no mode set"]) m := getBasicMode0(x,true) => [m] - null atom x => getModeSetUseSubdomain first x + cons? x => getModeSetUseSubdomain first x keyedSystemError("S2GE0016", ['"getModeSetUseSubomain",'"not an attributed tree"]) @@ -371,7 +371,7 @@ putAtree(x,prop,val) == -- otherwise will be pushing to deeply into calling structure if VECP op then putAtree(op,prop,val) x - null VECP x => x -- just ignore it + not VECP x => x -- just ignore it n := QLASSQ(prop,'((mode . 1) (value . 2) (modeSet . 3))) => x.n := val x.4 := insertShortAlist(prop,val,x.4) @@ -383,7 +383,7 @@ getAtree(x,prop) == -- otherwise will be pushing to deeply into calling structure VECP op => getAtree(op,prop) NIL - null VECP x => NIL -- just ignore it + not VECP x => NIL -- just ignore it n:= QLASSQ(prop,'((mode . 1) (value . 2) (modeSet . 3))) => x.n QLASSQ(prop,x.4) diff --git a/src/interp/i-output.boot b/src/interp/i-output.boot index 881d0b22..31242154 100644 --- a/src/interp/i-output.boot +++ b/src/interp/i-output.boot @@ -1858,7 +1858,7 @@ keyp(u) == absym x == (NUMBERP x) and (MINUSP x) => -x - not (atom x) and (keyp(x) = '_-) => second x + cons? x and (keyp(x) = '_-) => second x x agg(n,u) == @@ -1875,7 +1875,7 @@ argsapp(u,x,y,d) == appargs(rest u,x,y,d) subspan u == atom u => 0 NUMBERP rest u => subspan first u - (not atom first u and_ + (cons? first u and_ atom CAAR u and_ not NUMBERP CAAR u and_ GETL(CAAR u, 'SUBSPAN) ) => @@ -1887,7 +1887,7 @@ agggsub u == subspan rest u superspan u == atom u => 0 NUMBERP rest u => superspan first u - (not atom first u and_ + (cons? first u and_ atom CAAR u and_ not NUMBERP CAAR u and_ GETL(CAAR u, 'SUPERSPAN) ) => @@ -1966,7 +1966,7 @@ appext(u,x,y,d) == temp := 1 + WIDTH agg(2,u) + WIDTH agg(3,u) n := MAX(WIDTH second u, WIDTH agg(4,u), temp) if first(z := agg(5,u)) is ["EXT",:.] and - (n=3 or (n > 3 and not (atom z)) ) then + (n=3 or (n > 3 and cons? z) ) then n := 1 + n d := APP(z, x + n, y, d) @@ -1976,7 +1976,7 @@ apphor(x1,x2,y,d,char) == syminusp x == NUMBERP x => MINUSP x - not (atom x) and EQ(keyp x,'_-) + cons? x and EQ(keyp x,'_-) appsum(u, x, y, d) == null u => d @@ -2042,7 +2042,7 @@ extwidth(u) == 1 + WIDTH agg(2, u) + WIDTH agg(3, u) ) nil or (first(z := agg(5, u)) is ["EXT",:.] and _ - (n=3 or ((n > 3) and null atom z) ) => + (n=3 or ((n > 3) and cons? z) ) => n := 1 + n) true => n + WIDTH agg(5, u) diff --git a/src/interp/i-resolv.boot b/src/interp/i-resolv.boot index efc961e9..012a4b2e 100644 --- a/src/interp/i-resolv.boot +++ b/src/interp/i-resolv.boot @@ -515,7 +515,7 @@ resolveTMRecord(tr,mr) == ra := resolveTM1(third ta, third ma) -- resolve modes null ra => ok := NIL tt := [[first ta,second ta,ra],:tt] - null ok => NIL + not ok => NIL ['Record,nreverse tt] resolveTMUnion(t, m is ['Union,:ums]) == @@ -626,7 +626,7 @@ resolveTMEq1(ct,cm) == ct := rest ct xm := first cm cm := rest cm - if not (atom xm) and first xm = ":" -- i.e. Record + if cons? xm and first xm = ":" -- i.e. Record and first xt = ":" and second xm = second xt then xm := third xm xt := third xt diff --git a/src/interp/i-spec1.boot b/src/interp/i-spec1.boot index 18bbaf8e..dc884bc7 100644 --- a/src/interp/i-spec1.boot +++ b/src/interp/i-spec1.boot @@ -379,7 +379,7 @@ upTARGET t == not isLegitimateMode(m,NIL,NIL) => throwKeyedMsg("S2IE0004",[m]) categoryForm?(m) => throwKeyedMsg("S2IE0014",[m]) $declaredMode:= m - not atom(lhs) and putTarget(lhs,m) + cons? lhs and putTarget(lhs,m) ms := bottomUp lhs first ms ~= m => throwKeyedMsg("S2IC0011",[first ms,m]) @@ -491,7 +491,7 @@ upLoopIters itrl == upLoopIterIN(iter,index,s) == iterMs := bottomUp s - null IDENTP index => throwKeyedMsg("S2IS0005",[index]) + not IDENTP index => throwKeyedMsg("S2IS0005",[index]) if $genValue and first iterMs is ['Union,:.] then v := coerceUnion2Branch getValue s @@ -518,7 +518,7 @@ upLoopIterIN(iter,index,s) == mkIteratorVariable index upLoopIterSTEP(index,lower,step,upperList) == - null IDENTP index => throwKeyedMsg("S2IS0005",[index]) + not IDENTP index => throwKeyedMsg("S2IS0005",[index]) ltype := IFCAR bottomUpUseSubdomain(lower) not (typeIsASmallInteger(ltype) or isEqualOrSubDomain(ltype,$Integer))=> throwKeyedMsg("S2IS0007",['"lower"]) diff --git a/src/interp/i-spec2.boot b/src/interp/i-spec2.boot index e8522eb9..76da8a17 100644 --- a/src/interp/i-spec2.boot +++ b/src/interp/i-spec2.boot @@ -66,7 +66,7 @@ upDEF t == -- performs map definitions. value is thrown away t isnt [op,def,pred,.] => nil v:=addDefMap(["DEF",:def],pred) - null(LISTP(def)) or null(def) => + not(LISTP(def)) or null(def) => keyedSystemError("S2GE0016",['"upDEF",'"bad map definition"]) mapOp := first def if LISTP(mapOp) then @@ -184,7 +184,7 @@ upequation tree == -- this should speed things up a bit tree isnt [op,lhs,rhs] => NIL $Boolean ~= getTarget(op) => NIL - null VECP op => NIL + not VECP op => NIL -- change equation into '=' op.0 := "=" bottomUp tree @@ -363,7 +363,7 @@ putPvarModes(pattern,m) == -- Puts the modes for the pattern variables into $env m isnt ["List",um] => throwKeyedMsg("S2IS0030",NIL) for pvar in pattern repeat - IDENTP pvar => (null (pvar=$quadSymbol)) and put(pvar,'mode,um,$env) + IDENTP pvar => (not (pvar=$quadSymbol)) and put(pvar,'mode,um,$env) pvar is ['_:,var] => null (var=$quadSymbol) and put(var,"mode",m,$env) pvar is ['_=,var] => @@ -788,7 +788,7 @@ getInterpMacroNames() == isInterpMacro name == -- look in local and then global environment for a macro - null IDENTP name => NIL + not IDENTP name => NIL name in $specialOps => NIL (m := get("--macros--",name,$env)) => m (m := get("--macros--",name,$e)) => m diff --git a/src/interp/i-syscmd.boot b/src/interp/i-syscmd.boot index 835e627c..762e27c7 100644 --- a/src/interp/i-syscmd.boot +++ b/src/interp/i-syscmd.boot @@ -159,7 +159,7 @@ selectOptionLC(x,l,errorFunction) == selectOption(x,l,errorFunction) == member(x,l) => x --exact spellings are always OK - null IDENTP x => + not IDENTP x => errorFunction => FUNCALL(errorFunction,x,u) nil u := [y for y in l | stringPrefix?(PNAME x,PNAME y)] @@ -1719,7 +1719,7 @@ resetInCoreHist() == changeHistListLen(n) == -- changes the length of $HistList. n must be nonnegative - null integer? n => sayKeyedMsg("S2IH0015",[n]) + not integer? n => sayKeyedMsg("S2IH0015",[n]) dif:= n-$HistListLen $HistListLen:= n l:= rest $HistList diff --git a/src/interp/interop.boot b/src/interp/interop.boot index 110c35c2..70c86661 100644 --- a/src/interp/interop.boot +++ b/src/interp/interop.boot @@ -438,7 +438,7 @@ hashNewLookupInTable(op,sig,dollar,[domain,opvec],flag) == formatOpSignature(op,subsumptionSig)] nil slot := domain.loc - null atom slot => + cons? slot => slot.op = 'newGoGet => someMatch:=true --treat as if operation were not there --if EQ(QCAR slot,'newGoGet) then diff --git a/src/interp/lisplib.boot b/src/interp/lisplib.boot index d3f3d775..31c00c7e 100644 --- a/src/interp/lisplib.boot +++ b/src/interp/lisplib.boot @@ -207,7 +207,7 @@ loadIfNecessaryAndExists u == loadLibIfNecessary(u,nil) loadLibIfNecessary(u,mustExist) == u = '$EmptyMode => u - null atom u => loadLibIfNecessary(first u,mustExist) + cons? u => loadLibIfNecessary(first u,mustExist) value:= functionp(u) or macrop(u) => u GETL(u,'LOADED) => u @@ -244,7 +244,7 @@ updateCategoryFrameForCategory(category) == addModemap(category, dc, sig, pred, impl, $CategoryFrame)) loadFunctor u == - null atom u => loadFunctor first u + cons? u => loadFunctor first u loadLibIfNotLoaded u u @@ -320,7 +320,7 @@ compConLib1(fun,infileOrNil,outfileOrNil,auxOp,editFlag,traceFlag) == $libFile: local := NIL $lisplibVariableAlist: local := NIL $lisplibSignatureAlist: local := NIL - if null atom fun and null rest fun then fun:= first fun -- unwrap nullary + if cons? fun and null rest fun then fun:= first fun -- unwrap nullary libName:= getConstructorAbbreviation fun infile:= infileOrNil or getFunctionSourceFile fun or throwKeyedMsg("S2IL0004",[fun]) @@ -617,7 +617,7 @@ getConstructorSignature ctor == getSlotFromCategoryForm ([op,:argl],index) == u:= eval [op,:MAPCAR('MKQ,TAKE(#argl,$FormalMapVariableList))] - null VECP u => + not VECP u => systemErrorHere '"getSlotFromCategoryForm" u . index diff --git a/src/interp/mark.boot b/src/interp/mark.boot index 75caa58e..2f8849fa 100644 --- a/src/interp/mark.boot +++ b/src/interp/mark.boot @@ -761,7 +761,7 @@ markInsertChanges(code,form,t,loc) == loc is [i,:r] => x := form for j in 0..(i-1) repeat - if not atom x then x := rest x + if cons? x then x := rest x atom x => pp '"Translator RPLACA error" pp $data @@ -1088,7 +1088,7 @@ markPrintAbbreviation [kind,a,:b] == markTerpri() markSay s == - null atom s => + cons? s => for x in s repeat (markSay(lispStringList2String x); markTerpri()) PRINTEXP s @@ -1451,7 +1451,7 @@ rplacaSubst(x, y, u) == (fn(x, y, u); u) where fn(x,y,u) == atom u => nil while u is [p, :q] repeat if EQ(p, x) then u.first := y - if null atom p then fn(x, y, p) + if cons? p then fn(x, y, p) u := q buildNewDefinition(op,theSig,formPredAlist) == diff --git a/src/interp/modemap.boot b/src/interp/modemap.boot index bb26af46..d1256d48 100644 --- a/src/interp/modemap.boot +++ b/src/interp/modemap.boot @@ -299,7 +299,7 @@ augModemapsFromCategory(domainName,domainView,functorForm,categoryForm,e) == --condlist:=[[cond,:cond1],:condlist] e:= addModemapKnown(op,domainName,sig,cond,fnsel,e) -- cond was cond1 -- for u in sig | (not member(u,$DomainsInScope)) and --- (not atom u) and +-- (cons? u) and -- (not isCategoryForm(u,e)) do -- e:= addNewDomain(u,e) e diff --git a/src/interp/msgdb.boot b/src/interp/msgdb.boot index 0e758b04..c7d06279 100644 --- a/src/interp/msgdb.boot +++ b/src/interp/msgdb.boot @@ -432,7 +432,7 @@ popSatOutput(newmode) == $saturnMode systemErrorHere what == - if not atom what then + if cons? what then what := [first what, " with: ", :rest what] keyedSystemError("S2GE0017",[what]) @@ -686,7 +686,7 @@ brightPrint0AsTeX(x, out == $OutputStream) == blankIndicator x == if IDENTP x then x := PNAME x - null string? x or MAXINDEX x < 1 => nil + not string? x or MAXINDEX x < 1 => nil x.0 = '% and x.1 = 'x => MAXINDEX x > 1 => readInteger SUBSTRING(x,2,nil) 1 diff --git a/src/interp/nruncomp.boot b/src/interp/nruncomp.boot index 6d76fe6e..7bb931ab 100644 --- a/src/interp/nruncomp.boot +++ b/src/interp/nruncomp.boot @@ -204,12 +204,12 @@ genDeltaEntry(opMmPair,e) == ['applyFun,['compiledLookupCheck,MKQ op, mkList consSig(nsig,dc),consDomainForm(dc,nil)]] odc := dc - if not atom dc then + if cons? dc then dc := substitute("$$","$",dc) opModemapPair := [op,[dc,:[NRTgetLocalIndex x for x in nsig]],["T",cform]] -- force pred to T if null NRTassocIndex dc and - (member(dc,$functorLocalParameters) or not atom dc) then + (member(dc,$functorLocalParameters) or cons? dc) then --create "%domain" entry to $NRTdeltaList $NRTdeltaList:= [["%domain",NRTaddInner dc],:$NRTdeltaList] saveNRTdeltaListComp:= $NRTdeltaListComp:=[nil,:$NRTdeltaListComp] @@ -320,7 +320,7 @@ NRTisExported? opSig == or/[u for u in $domainShell.1 | u.0 = opSig] consOpSig(op,sig,dc) == - if not atom op then + if cons? op then keyedSystemError("S2GE0016",['"consOpSig",'"bad operator in table"]) mkList [MKQ op,mkList consSig(sig,dc)] diff --git a/src/interp/nrunfast.boot b/src/interp/nrunfast.boot index 870db913..76512b38 100644 --- a/src/interp/nrunfast.boot +++ b/src/interp/nrunfast.boot @@ -200,7 +200,7 @@ newLookupInTable(op,sig,dollar,[domain,opvec],flag) == i := start numArgs ~= (numTableArgs :=numvec.i) => nil predIndex := numvec.(i := QSADD1 i) - NE(predIndex,0) and null testBitVector(predvec,predIndex) => nil + NE(predIndex,0) and not testBitVector(predvec,predIndex) => nil loc := newCompareSig(sig,numvec,(i := QSADD1 i),dollar,domain) null loc => nil --signifies no match loc = 1 => (someMatch := true) @@ -216,7 +216,7 @@ newLookupInTable(op,sig,dollar,[domain,opvec],flag) == formatOpSignature(op,subsumptionSig)] nil slot := domain.loc - null atom slot => + cons? slot => slot.op = 'newGoGet => someMatch:=true --treat as if operation were not there --if EQ(QCAR slot,'newGoGet) then @@ -263,7 +263,7 @@ newLookupInDomain(op,sig,addFormDomain,dollar,index) == addFormCell := addFormDomain.index => integer? KAR addFormCell => or/[newLookupInDomain(op,sig,addFormDomain,dollar,i) for i in addFormCell] - if null VECP addFormCell then lazyDomainSet(addFormCell,addFormDomain,index) + if not VECP addFormCell then lazyDomainSet(addFormCell,addFormDomain,index) lookupInDomainVector(op,sig,addFormDomain.index,dollar) nil @@ -325,7 +325,7 @@ newLookupInCategories(op,sig,dom,dollar) == packageVec.i := package package nil - null success => + not success => if $monitorNewWorld = true then sayBrightlyNT '" not in: " pp (packageForm and devaluate package or entry) @@ -398,7 +398,7 @@ newLookupInCategories1(op,sig,dom,dollar) == packageVec.i := package package nil - null success => + not success => if $monitorNewWorld = true then sayBrightlyNT '" not in: " pp (packageForm and devaluate package or entry) @@ -464,7 +464,7 @@ lazyMatchArg2(s,a,dollar,domain,typeFlag) == --s = a lazyMatch(source,lazyt,dollar,domain) == - lazyt is [op,:argl] and null atom source and op=first source + lazyt is [op,:argl] and cons? source and op=first source and #(sargl := rest source) = #argl => op in '(Record Union) and first argl is [":",:.] => and/[stag = atag and lazyMatchArg(s,a,dollar,domain) @@ -520,11 +520,11 @@ lookupInDomainByName(op,domain,arg) == i := start numberOfArgs :=numvec.i predIndex := numvec.(i := QSADD1 i) - NE(predIndex,0) and null testBitVector(predvec,predIndex) => nil + NE(predIndex,0) and not testBitVector(predvec,predIndex) => nil slotIndex := numvec.(i + 2 + numberOfArgs) newStart := QSPLUS(start,QSPLUS(numberOfArgs,4)) slot := domain.slotIndex - null atom slot and EQ(first slot,first arg) and EQ(rest slot,rest arg) => return (success := true) + cons? slot and EQ(first slot,first arg) and EQ(rest slot,rest arg) => return (success := true) start := QSPLUS(start,QSPLUS(numberOfArgs,4)) success @@ -637,7 +637,7 @@ newHasTest(domform,catOrAtt) == HasCategory(evalDomain a,b) => true -- for asharp domains: must return Boolean op := opOf catOrAtt isAtom := atom catOrAtt - null isAtom and op = 'Join => + not isAtom and op = 'Join => and/[newHasTest(domform,x) for x in rest catOrAtt] -- we will refuse to say yes for 'Cat has Cat' --getConstructorKindFromDB opOf domform = "category" => throwKeyedMsg("S2IS0025",NIL) @@ -656,7 +656,7 @@ newHasTest(domform,catOrAtt) == pred in '(OR or %or) => or/[evalCond i for i in l] pred in '(AND and %and) => and/[evalCond i for i in l] x - null isAtom and constructor? op => + not isAtom and constructor? op => domain := eval mkEvalable domform newHasCategory(domain,catOrAtt) catOrAtt is [":",op,type] => diff --git a/src/interp/nrungo.boot b/src/interp/nrungo.boot index 59998333..007b6416 100644 --- a/src/interp/nrungo.boot +++ b/src/interp/nrungo.boot @@ -44,7 +44,7 @@ $insideCompileBodyIfTrue := false --% Monitoring functions lookupDisplay(op,sig,vectorOrForm,suffix) == - null $NRTmonitorIfTrue => nil + not $NRTmonitorIfTrue => nil prefix := (suffix = '"" => ">"; "<") sayBrightly concat(prefix,formatOpSignature(op,sig), @@ -151,14 +151,14 @@ lookupInTable(op,sig,dollar,[domain,table]) == someMatch := false while not success for [sig1,:code] in LASSQ(op,table) repeat success := - null compareSig(sig,sig1,dollar.0,domain) => false + not compareSig(sig,sig1,dollar.0,domain) => false code is ['subsumed,a] => subsumptionSig := EQSUBSTLIST(rest(domain.0),$FormalMapVariableList,a) someMatch:=true false predIndex := QSQUOTIENT(code,8192) - predIndex ~= 0 and null lookupPred($predVector.predIndex,dollar,domain) + predIndex ~= 0 and not lookupPred($predVector.predIndex,dollar,domain) => false loc := QSQUOTIENT(QSREMAINDER(code,8192),2) loc = 0 => diff --git a/src/interp/nrunopt.boot b/src/interp/nrunopt.boot index f04d56ef..963a032c 100644 --- a/src/interp/nrunopt.boot +++ b/src/interp/nrunopt.boot @@ -59,7 +59,7 @@ makeDomainTemplate vec == null item => nil newVec.index := atom item => item - null atom first item => makeGoGetSlot(item,index) + cons? first item => makeGoGetSlot(item,index) item $byteVec := "append"/nreverse $byteVec newVec @@ -168,7 +168,7 @@ stuffDomainSlots dollar == predvec := first proto4 packagevec := second proto4 auxvec := LIST2VEC [fn for i in 0..MAXINDEX predvec] where fn() == - null testBitVector(bitVector,predvec.i) => nil + not testBitVector(bitVector,predvec.i) => nil packagevec.i or true [auxvec,:CDDR proto4] @@ -710,7 +710,7 @@ dcSize(:options) == dcSizeAll() == count := 0 total := 0 - for x in allConstructors() | null atom GETL(x,'infovec) repeat + for x in allConstructors() | cons? GETL(x,'infovec) repeat count := count + 1 s := dcSize(x,'quiet) sayBrightly [s,'" : ",x] @@ -848,7 +848,7 @@ extendsCategory(dom,u,v) == extendsCategoryBasic0(dom,u,v) == v is ['IF,p,['ATTRIBUTE,c],.] => uVec := (compMakeCategoryObject(u,$EmptyEnvironment)).expr - null atom c and isCategoryForm(c,nil) => + cons? c and isCategoryForm(c,nil) => slot4 := uVec.4 LASSOC(c,second slot4) is [=p,:.] slot2 := uVec.2 diff --git a/src/interp/pf2atree.boot b/src/interp/pf2atree.boot index fddbaf39..42453835 100644 --- a/src/interp/pf2atree.boot +++ b/src/interp/pf2atree.boot @@ -525,7 +525,7 @@ pfCollect2Atree pf == -- patternVarsOf1(expr, varList) == -- null expr => varList -- atom expr => --- null symbol? expr => varList +-- not symbol? expr => varList -- SymMemQ(expr, varList) => varList -- [expr, :varList] -- expr is [op, :argl] => diff --git a/src/interp/pf2sex.boot b/src/interp/pf2sex.boot index 3ec5b720..1d7b6fb8 100644 --- a/src/interp/pf2sex.boot +++ b/src/interp/pf2sex.boot @@ -474,7 +474,7 @@ patternVarsOf expr == patternVarsOf1(expr, varList) == null expr => varList atom expr => - null symbol? expr => varList + not symbol? expr => varList SymMemQ(expr, varList) => varList [expr, :varList] expr is [op, :argl] => diff --git a/src/interp/pspad1.boot b/src/interp/pspad1.boot index 6e299b50..925a4a94 100644 --- a/src/interp/pspad1.boot +++ b/src/interp/pspad1.boot @@ -401,7 +401,7 @@ formatApplication u == formatSelection u formatHasDotLeadOp u == - u is [op,:.] and (op = "." or not atom op) + u is [op,:.] and (op = "." or cons? op) formatApplication0 u == --format as f(x) as f x if possible @@ -453,7 +453,7 @@ formatSelectionOp op == formatSelectionOp1 f == f is [op,:argl] => argl is [a] => - not atom op and atom a => formatSelection1 [op,a] + cons? op and atom a => formatSelection1 [op,a] formatPren f format f formatOp f diff --git a/src/interp/pspad2.boot b/src/interp/pspad2.boot index 3ece41b6..173fca07 100644 --- a/src/interp/pspad2.boot +++ b/src/interp/pspad2.boot @@ -487,7 +487,7 @@ formatComments(u,op,types) == u consComments(s,plusPlus) == - s is [word,:r] and null atom r => consComments(r, plusPlus) + s is [word,:r] and cons? r => consComments(r, plusPlus) s := first s null s => nil s := consCommentsTran s diff --git a/src/interp/setvars.boot b/src/interp/setvars.boot index c5932545..2fced3b3 100644 --- a/src/interp/setvars.boot +++ b/src/interp/setvars.boot @@ -775,7 +775,7 @@ countCache n == $options => $options is [["vars",:l]] => for x in l repeat - null IDENTP x => sayKeyedMsg("S2IF0007",[x]) + not IDENTP x => sayKeyedMsg("S2IF0007",[x]) $cacheAlist:= insertAlist(x,n,$cacheAlist) cacheCountName:= INTERNL(x,'";COUNT") setDynamicBinding(cacheCountName,n) diff --git a/src/interp/wi1.boot b/src/interp/wi1.boot index f698c8a8..365e319d 100644 --- a/src/interp/wi1.boot +++ b/src/interp/wi1.boot @@ -65,7 +65,7 @@ put(x,prop,val,e) == $InteractiveMode and not EQ(e,$CategoryFrame) => putIntSymTab(x,prop,val,e) --e must never be $CapsuleModemapFrame - null atom x => put(first x,prop,val,e) + cons? x => put(first x,prop,val,e) newProplist:= augProplistOf(x,prop,val,e) prop="modemap" and $insideCapsuleFunctionIfTrue=true => SAY ["**** modemap PUT on CapsuleModemapFrame: ",val] @@ -91,7 +91,7 @@ pmatchWithSl(s,p,al) == s=p => al v:= assoc(p,al) => s=rest v or al MEMQ(p,$PatternVariableList) => [[p,:s],:al] - null atom p and null atom s and (al':= pmatchWithSl(first s,first p,al)) and + cons? p and cons? s and (al':= pmatchWithSl(first s,first p,al)) and pmatchWithSl(rest s,rest p,al') --====================================================================== @@ -568,7 +568,7 @@ setqSingle(id,val,m,E) == assignError(val,T.mode,id,m'') T':= [x,m',e']:= convert(T,m) or return nil if $profileCompiler = true then - null IDENTP id => nil + not IDENTP id => nil key := MEMQ(id,rest $form) => 'arguments 'locals diff --git a/src/interp/wi2.boot b/src/interp/wi2.boot index f1e9185a..828afd4c 100644 --- a/src/interp/wi2.boot +++ b/src/interp/wi2.boot @@ -653,13 +653,13 @@ genDeltaEntry(opMmPair,e) == setDifference(listOfBoundVars dc,$functorLocalParameters) ~= [] => ['applyFun,['compiledLookupCheck,MKQ op, mkList consSig(sig,dc),consDomainForm(dc,nil)]] - --if null atom dc then + --if cons? dc then -- sig := substitute('$,dc,sig) -- cform := substitute('$,dc,cform) opModemapPair := [op,[dc,:[genDeltaSig x for x in sig]],['T,cform]] -- force pred to T if null NRTassocIndex dc and - (member(dc,$functorLocalParameters) or null atom dc) then + (member(dc,$functorLocalParameters) or cons? dc) then --create "%domain" entry to $NRTdeltaList $NRTdeltaList:= [["%domain",NRTaddInner dc,:dc],:$NRTdeltaList] saveNRTdeltaListComp:= $NRTdeltaListComp:=[nil,:$NRTdeltaListComp] @@ -711,7 +711,7 @@ makeSimplePredicateOrNil p == nil mkUserConstructorAbbreviation(c,a,type) == if $AnalyzeOnly or $convert2NewCompiler then $abbreviationStack := [[type,a,:c],:$abbreviationStack] - if not atom c then c:= first c -- Existing constructors will be wrapped + if cons? c then c:= first c -- Existing constructors will be wrapped constructorAbbreviationErrorCheck(c,a,type,'abbreviationError) clearClams() clearConstructorCache(c) diff --git a/src/interp/word.boot b/src/interp/word.boot index ad819549..2ae1dae5 100644 --- a/src/interp/word.boot +++ b/src/interp/word.boot @@ -359,7 +359,7 @@ forge(word,w,W,entry,e,E,n) == -- String Pattern Matching --======================================================================= patternTran pattern == - null hasWildCard? pattern and LITER pattern.0 and + not hasWildCard? pattern and LITER pattern.0 and UPCASE copy pattern = pattern => name:= abbreviation? INTERN pattern or browseError [:bright pattern, |