login  home  contents  what's new  discussion  bug reports     help  links  subscribe  changes  refresh  edit

Allow adding additional sub/superscripts to symbols.

spad
)abbrev domain SYMBOL Symbol
++ Author: Stephen Watt
++ Date Created: 1986
++ Date Last Updated: 7 Mar 1991, 29 Apr. 1994 (FDLL)
++ Description:
++   Basic and scripted symbols.
++ Keywords: symbol.
Symbol() : Exports == Implementation where
  L ==> List OutputForm
  Scripts ==> Record(sub : L, sup : L, presup : L, presub : L, args : L)
Exports ==> Join(OrderedSet, ConvertibleTo InputForm, OpenMath, ConvertibleTo Symbol, ConvertibleTo Pattern Integer, ConvertibleTo Pattern Float, PatternMatchable Integer, PatternMatchable Float) with new : () -> % ++ new() returns a new symbol whose name starts with %. new : % -> % ++ new(s) returns a new symbol whose name starts with %s. conjugate : % -> % ++ conjugate(s) returns the symbolic conjugate of s. resetNew : () -> Void ++ resetNew() resets the internals counters that new() and ++ new(s) use to return distinct symbols every time. coerce : String -> % ++ coerce(s) converts the string s to a symbol. name : % -> % ++ name(s) returns s without its scripts. scripted? : % -> Boolean ++ scripted?(s) is true if s has been given any scripts. scripts : % -> Scripts ++ scripts(s) returns all the scripts of s. script : (%, List L) -> % ++ script(s, [a, b, c, d, e]) returns s with subscripts a, ++ superscripts b, pre-superscripts c, pre-subscripts d, ++ and argument-scripts e. Omitted components are taken to be empty. ++ For example, \spad{script(s, [a, b, c])} is equivalent to ++ \spad{script(s, [a, b, c, [], []])}. script : (%, Scripts) -> % ++ script(s, [a, b, c, d, e]) returns s with subscripts a, ++ superscripts b, pre-superscripts c, pre-subscripts d, ++ and argument-scripts e. subscript : (%, L) -> % ++ subscript(s, [a1, ..., an]) returns s ++ subscripted by \spad{[a1, ..., an]}. superscript : (%, L) -> % ++ superscript(s, [a1, ..., an]) returns s ++ superscripted by \spad{[a1, ..., an]}. argscript : (%, L) -> % ++ argscript(s, [a1, ..., an]) returns s ++ arg-scripted by \spad{[a1, ..., an]}. elt : (%, L) -> % ++ elt(s, [a1, ..., an]) or s([a1, ..., an]) returns s subscripted by \spad{[a1, ..., an]}. _^ : (%,L) -> % string : % -> String ++ string(s) converts the symbol s to a string. ++ Error: if the symbol is subscripted. sample : constant -> % ++ sample() returns a sample of %
Implementation ==> add
import from Character import from List(OutputForm) import from List(%)
count : Reference(Integer) := ref 0 xcount : AssociationList(%, Integer) := empty() istrings : PrimitiveArray(String) := construct ["0","1","2","3","4","5","6","7","8","9"] -- the following 3 strings shall be of empty intersection nums:String := "0123456789" ALPHAS:String := "ABCDEFGHIJKLMNOPQRSTUVWXYZ" alphas:String := "abcdefghijklmnopqrstuvwxyz"
writeOMSym(dev : OpenMathDevice, x : %) : Void == scripted? x => error "Cannot convert a scripted symbol to OpenMath" OMputVariable(dev, x pretend Symbol)
OMwrite(dev : OpenMathDevice, x : %, wholeObj : Boolean) : Void == if wholeObj then OMputObject(dev) writeOMSym(dev, x) if wholeObj then OMputEndObject(dev)
hd:String := "*" lhd := #hd ord0 := ord char("0")$Character pcnt ==> 4 conj:String := "*"
istring : Integer -> String syprefix : Scripts -> String syscripts : Scripts -> L conjugate? : % -> Boolean
convert(s : %) : InputForm == --conjugate? s => prefix(outputForm 'conjugate,[conjugate(s) pretend OutputForm]) pretend InputForm conjugate? s => convert([convert('conjugate)@InputForm,conjugate(s) pretend InputForm]$List(InputForm))@InputForm scripted? s => sc:Scripts := scripts s convert([convert('script)@InputForm,name(s) pretend InputForm, _ convert([convert('construct)@InputForm, _ prefix(outputForm 'construct, sc.sub pretend List OutputForm) _ pretend InputForm, _ prefix(outputForm 'construct, sc.sup pretend List OutputForm) _ pretend InputForm, _ prefix(outputForm 'construct, sc.presub pretend List OutputForm) _ pretend InputForm, _ prefix(outputForm 'construct, sc.presub pretend List OutputForm) _ pretend InputForm, _ prefix(outputForm 'construct, sc.args pretend List OutputForm) _ pretend InputForm _ ]$List(InputForm))@InputForm _ ]$List(InputForm))@InputForm convert(s pretend Symbol)$InputForm convert(s : %) : Symbol == s pretend Symbol coerce(s : String) : % == VALUES(INTERN(s)$Lisp)$Lisp x = y == EQUAL(x, y)$Lisp hashUpdate!(hs, s) == update!(hs, SXHASH(s)$Lisp)$HashState x < y == GGREATERP(y, x)$Lisp
coerce(x : %) : OutputForm == not(scripted? x) => conjugate? x => overbar(outputForm(conjugate x pretend Symbol)) outputForm(x pretend Symbol) ss : Scripts := scripts x rsl : List(L) := [ss.presub, ss.presup, ss.sup, ss.sub] sl : L := [] for si in rsl repeat empty?(sl) and empty?(si) => "iterate" se := #si = 1 => first(si) commaSeparate(si) sl := cons(se, sl) if conjugate? x then x0 := scripts(outputForm(conjugate name(x) pretend Symbol), sl) else x0 := scripts(outputForm(name(x) pretend Symbol), sl) a := ss.args if not empty?(a) then x0 := prefix(x0, a) conjugate? x => overbar x0 x0
subscript(sy, lx) == script(sy, [lx, nil, nil(), nil(), nil()]) elt(sy, lx) == subscript(sy, lx) sy ^ lx == superscript(sy, lx) superscript(sy, lx) == script(sy, [nil(), lx, nil(), nil(), nil()]) argscript(sy, lx) == script(sy, [nil(), nil(), nil(), nil(), lx])
patternMatch(x : %, p : Pattern Integer, l : PatternMatchResult(Integer, %))== (patternMatch(x pretend Symbol, p, l pretend PatternMatchResult(Integer, Symbol))$PatternMatchSymbol(Integer)) pretend PatternMatchResult(Integer, %)
patternMatch(x : %, p : Pattern Float, l : PatternMatchResult(Float, %)) == (patternMatch(x pretend Symbol, p, l pretend PatternMatchResult(Float, Symbol))$PatternMatchSymbol(Float)) pretend PatternMatchResult(Float, %)
convert(x : %) : Pattern(Float) == coerce(x pretend Symbol)$Pattern(Float)
convert(x : %) : Pattern(Integer) == coerce(x pretend Symbol)$Pattern(Integer)
syprefix sc == ns : List Integer := [#sc.presub, #sc.presup, #sc.sup, #sc.sub] concat concat(concat(hd, istring(#sc.args)), [istring n for n in reverse! ns])
syscripts sc == all := sc.presub all := concat(sc.presup, all) all := concat(sc.sup, all) all := concat(sc.sub, all) concat(all, sc.args)
script(sy : %, ls : List L) == sc : Scripts := [nil(), nil(), nil(), nil(), nil()] if not null ls then (sc.sub := first ls; ls := rest ls) if not null ls then (sc.sup := first ls; ls := rest ls) if not null ls then (sc.presup := first ls; ls := rest ls) if not null ls then (sc.presub := first ls; ls := rest ls) if not null ls then (sc.args := first ls; ls := rest ls) script(sy, sc)
script(sy : %, sc : Scripts) == --scripted? sy => error "Cannot add scripts to a scripted symbol" oldsc:=scripts(sy) --output("symbol oldsc: ",oldsc::OutputForm)$OutputPackage newsc:Scripts := [concat(oldsc.sub,sc.sub), _ concat(oldsc.sup,sc.sup), _ concat(oldsc.presup,sc.presup), _ concat(oldsc.presub,sc.presub), _ concat(oldsc.args,sc.args)] --output("symbol newsc: ",newsc::OutputForm)$OutputPackage (concat(concat(syprefix newsc, string name sy)::% pretend OutputForm, syscripts newsc)) pretend %
string e == not scripted? e => PNAME(e)$Lisp error "Cannot form string from non-atomic symbols."
-- Scripts ==> Record(sub: L, sup: L, presup: L, presub: L, args: L) latex e == s : String := (PNAME(name e)$Lisp) pretend String if #s > 1 and s.1 ~= char "\" then s := concat("\mbox{\it ", concat(s, "}")$String)$String not scripted? e => s ss : Scripts := scripts e lo : List OutputForm := ss.sub sc : String if not empty? lo then sc := "__{" while not empty? lo repeat sc := concat(sc, latex first lo)$String lo := rest lo if not empty? lo then sc := concat(sc, ", ")$String sc := concat(sc, "}")$String s := concat(s, sc)$String lo := ss.sup if not empty? lo then sc := "^{" while not empty? lo repeat sc := concat(sc, latex first lo)$String lo := rest lo if not empty? lo then sc := concat(sc, ", ")$String sc := concat(sc, "}")$String s := concat(s, sc)$String lo := ss.presup if not empty? lo then sc := "{}^{" while not empty? lo repeat sc := concat(sc, latex first lo)$String lo := rest lo if not empty? lo then sc := concat(sc, ", ")$String sc := concat(sc, "}")$String s := concat(sc, s)$String lo := ss.presub if not empty? lo then sc := "{}__{" while not empty? lo repeat sc := concat(sc, latex first lo)$String lo := rest lo if not empty? lo then sc := concat(sc, ", ")$String sc := concat(sc, "}")$String s := concat(sc, s)$String lo := ss.args if not empty? lo then sc := "\left( {" while not empty? lo repeat sc := concat(sc, latex first lo)$String lo := rest lo if not empty? lo then sc := concat(sc, ", ")$String sc := concat(sc, "} \right)")$String s := concat(s, sc)$String s
anyRadix(n : Integer, s : String) : String == ns:String := "" repeat qr := divide(n, #s) n := qr.quotient ns := concat(s.(qr.remainder+minIndex s), ns) if zero?(n) then return ns
new() == sym := anyRadix(count()::Integer, ALPHAS) count() := count() + 1 concat("%",sym)::%
new x == n : Integer := (u := search(x, xcount)) case "failed" => 0 inc(u::Integer) xcount(x) := n xx := not scripted? x => string x string name x xx := concat("%",xx) xx := (position(xx.maxIndex(xx), nums)>=minIndex(nums)) => concat(xx, anyRadix(n, alphas)) concat(xx, anyRadix(n, nums)) not scripted? x => xx::% script(xx::%, scripts x)
resetNew() == count() := 0 for k in keys xcount repeat remove!(k, xcount) void
scripted? sy == not ATOM(sy)$Lisp
of_list(x : %) : L == x pretend L
name sy == not scripted? sy => sy str := string(first(of_list(sy)) pretend %) si := lhd + pcnt + 2 str(si..#str)::%
conjugate? sy == str:=string(name sy) str(#str..#str)=conj
conjugate sy == str:=string(name sy) if conjugate? sy then str:=str(1..#str-1) else str:=concat(str,conj) str not scripted? sy => str::% script(str::%, scripts sy)
scripts sy == not scripted? sy => [nil(), nil(), nil(), nil(), nil()] nscripts : List NonNegativeInteger := [0, 0, 0, 0, 0] lscripts : List L := [nil(), nil(), nil(), nil(), nil()] str := string(first(of_list(sy)) pretend %) nstr := #str m := minIndex nscripts for i in m.. for j in (lhd + 1)..(lhd + pcnt + 1) repeat nscripts.i := (ord(str.j) - ord0)::NonNegativeInteger -- Put the number of function scripts at the end. nscripts := concat(rest nscripts, first nscripts) allscripts := rest(of_list(sy)) m := minIndex lscripts for i in m.. for n in nscripts repeat #allscripts < n => error "Improper script count in symbol" lscripts.i := first(allscripts, n) allscripts := rest(allscripts, n) [lscripts.m, lscripts.(m+1), lscripts.(m+2), lscripts.(m+3), lscripts.(m+4)]
istring n == n > 9 => error "Can have at most 9 scripts of each kind" istrings.(n + minIndex istrings)
sample() == "aSymbol"::%
--Copyright (c) 1991-2002, The Numerical ALgorithms Group Ltd. --All rights reserved. -- --Redistribution and use in source and binary forms, with or without --modification, are permitted provided that the following conditions are --met: -- -- - Redistributions of source code must retain the above copyright -- notice, this list of conditions and the following disclaimer. -- -- - Redistributions in binary form must reproduce the above copyright -- notice, this list of conditions and the following disclaimer in -- the documentation and/or other materials provided with the -- distribution. -- -- - Neither the name of The Numerical ALgorithms Group Ltd. nor the -- names of its contributors may be used to endorse or promote products -- derived from this software without specific prior written permission. -- --THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS --IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED --TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A --PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER --OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, --EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, --PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR --PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF --LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING --NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS --SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
spad
   Compiling FriCAS source code from file 
      /var/lib/zope2.10/instance/axiom-wiki/var/LatexWiki/2136517885840098381-25px001.spad
      using old system compiler.
   SYMBOL abbreviates domain Symbol 
------------------------------------------------------------------------
   initializing NRLIB SYMBOL for Symbol 
   compiling into NRLIB SYMBOL 
   importing Character
   importing List OutputForm
   importing List $
   compiling local writeOMSym : (OpenMathDevice,$) -> Void
;;; *** |SYMBOL;writeOMSym| REDEFINED Time: 0.06 SEC.
compiling exported OMwrite : (OpenMathDevice,$,Boolean) -> Void
;;; *** |SYMBOL;OMwrite;Omd$BV;2| REDEFINED Time: 0.01 SEC.
processing macro definition pcnt ==> 4 compiling exported convert : $ -> InputForm
;;; *** |SYMBOL;convert;$If;3| REDEFINED Time: 1.10 SEC.
compiling exported convert : $ -> Symbol SYMBOL;convert;2$;4 is replaced by s
;;; *** |SYMBOL;convert;2$;4| REDEFINED Time: 0 SEC.
compiling exported coerce : String -> $
;;; *** |SYMBOL;coerce;S$;5| REDEFINED Time: 0 SEC.
compiling exported = : ($,$) -> Boolean SYMBOL;=;2$B;6 is replaced by EQUAL
;;; *** |SYMBOL;=;2$B;6| REDEFINED Time: 0 SEC.
compiling exported hashUpdate! : (HashState,$) -> HashState
;;; *** |SYMBOL;hashUpdate!;Hs$Hs;7| REDEFINED Time: 0 SEC.
compiling exported < : ($,$) -> Boolean SYMBOL;<;2$B;8 is replaced by GGREATERPyx
;;; *** |SYMBOL;<;2$B;8| REDEFINED Time: 0 SEC.
compiling exported coerce : $ -> OutputForm
;;; *** |SYMBOL;coerce;$Of;9| REDEFINED Time: 0.02 SEC.
compiling exported subscript : ($,List OutputForm) -> $ ****** comp fails at level 4 with expression: ****** error in function subscript
(|script| |sy| (|construct| |lx| |nil| (|nil|) (|nil|) (|nil|))) ****** level 4 ****** $x:= nil $m:= (List (OutputForm)) $f:= ((((|lx| # . #1=#) (|sy| # . #2=#) (|lx| . #1#) (|sy| . #2#) ...) ((|writeOMSym| #) (|coerce| #) (|void| #) (|$DomainsInScope| # # #) ...)))
>> Apparent user error: Cannot coerce lx of mode (List (OutputForm)) to mode (OutputForm)

Examples

fricas
conjugate x

\label{eq1}\overline x(1)
Type: Expression(Integer)
fricas
conjugate %

\label{eq2}x(2)
Type: Expression(Integer)
fricas
test(conjugate conjugate x = x)

\label{eq3} \mbox{\rm true} (3)
Type: Boolean
fricas
x[1][2]
>> Error detected within library code: Cannot add scripts to a scripted symbol

InputForm

fricas
conjugate(x)::InputForm

\label{eq4}\left(conjugate \  x \right)(4)
Type: InputForm
fricas
convert(conjugate(x))$Symbol@InputForm
There are 23 exposed and 12 unexposed library operations named convert having 1 argument(s) but none was determined to be applicable. Use HyperDoc Browse, or issue )display op convert to learn more about the available operations. Perhaps package-calling the operation or using coercions on the arguments will allow you to apply the operation.
Cannot find a definition or applicable library operation named convert with argument type(s) Expression(Integer)
Perhaps you should use "@" to indicate the required return type, or "$" to specify which version of the function you need.




  Subject:   Be Bold !!
  ( 14 subscribers )  
Please rate this page: