Oberon/ETH Oberon/MediaWiki.Mod

From Wikibooks, open books for an open world
Jump to navigation Jump to search
(* ETH Oberon, Copyright (c) 1990-present Computer Systems Institute, ETH Zurich, CH-8092 Zurich.
	All rights reserved.  License at ftp://ftp.ethoberon.ethz.ch/ETHOberon/license.txt . *)

(* Conversion of an Oberon Text to MediaWiki markup with font attributes preserved.  
	Analogous to the HTML module, https://en.wikibooks.org/wiki/Oberon/Oberon.HTML.Mod .

	The MediaWiki markup language is described in these pages.
	https://www.mediawiki.org/wiki/Help:Editing_pages
	https://en.wikibooks.org/wiki/Help:Editing
	https://en.wikibooks.org/wiki/Editing_Wikitext  

	In MediaWiki markup, a series of lines, each beginning with a blank, 
	is evaluated as preformatted.  In MediaWiki, an indent can be 
	represented by ":" rather than by blanks or a tab.  Nevertheless 
	MediaWiki.Markup preserves blanks and tabs.

	In the HTML delivered by the Wikimedia servers, indentation is 
	represented by nested description lists using the <dl> and <dd> tags.
	https://www.w3.org/wiki/HTML/Elements/dl
	https://www.w3.org/TR/2012/WD-html-markup-20120315/dl.html 

	The consequence of the conversions, Oberon Text to MediaWiki markup, 
	markup to HTML and HTML to displayed Text or text, is a display  
	matching the original Oberon Text in appearance.  
	
	Ideally, Desktops.OpenDoc in ETH Oberon should recover an Oberon Text 
	matching the original at the binary level.  While the HTML code has the 
	correct attributes of typeface, size, weight, style, color and vertical offset, 
	Desktops modules do not yet handle all of this information.

	SYNTAX OF OUTPUT
	markup = " <span style=" globalAttributes ">" {{ch} {span {ch}}} "</span>".
	globalAttributes = """ fontSpec ";" sizeSpec ";" weightSpec ";" styleSpec ";"
	                               colorSpec ";" voffSpec ";" tabSpec """. 
	span = "<span style=" """ attributeSpec {";" attributeSpec} """ ">" {ch} "</span>".
	attributeSpec = fontSpec | colorSpec | sizeSpec | weightSpec | styleSpec.
	fontSpec = "font-family: " fontFamily.
	fontFamily = fontName (", monospace" | ", Arial, sans-serif").
	fontName = letter {letter | digit}.
	sizeSpec = "font-size: " size.
	size = (digit "." digit digit "rem") | "normal" | "small".
	weightSpec = "font-weight: " weight.
	weight = "b" | "m" | "n".  (Bold, medium or normal.)
	styleSpec = "font-style: " style.
	style = "i" | "n".  (Italic or normal.))
	colorSpec = "color: #" color.
	color = hexDigit hexDigit hexDigit hexDigit hexDigit hexDigit.
	voffSpec = "position: relative; top:" offset "%".  (Script.Tool specifies % rather than points.)
	offset = ["-"] digit {digit}.  (Positive offset shifts down.  Signs of voff and offset are opposed.)
	tabSpec = "-moz-tab-size: " digit ";" "tab-size: " digit. 

	TEXT ATTRIBUTES
	The first character of the input Text determines the attributes of a 
	global span enclosing the entire markup.  Where any attribute 
	changes, another span is opened.  If a span is open, it is closed 
	before a new span is opened.  Therefore there is a global span and, 
	possibly, nested spans, never more than one deep.  In a nested span, 
	the inSpan flag is TRUE.

	DEFICIENCIES
	While Oberon Text and HTML can contain non-character objects, 
	including links and images, this markup preserves only characters 
	of Text, with attributes.

	HEAP USE
	For interest, heap use is reported at the end of MarkupFiles.
*)

MODULE MediaWiki (* IN ETH Oberon *);	(** portable *)

	(* For profuse tracing import Out.  To suppress profuse tracing import Out := OutStub. *)
	IMPORT
		Files, Texts, Oberon, Out := OutStub, Fonts, Display, TextFrames, Viewers, 
		MenuViewers, Objects, Documents
		, Kernel; 	(* S3 *)
		(* , Machine IN A2, Heaps IN A2; *)

	CONST
		Menu = "System.Close System.Copy System.Grow ET.Search ET.Replace ET.StoreAscii";
		(* mediaWikiPrefix and mediaWikiSuffix are added to the input file name to create the output file name. *)
		mediaWikiPrefix = "";
		MediaWikiSuffix = ".mw";

		(* If globalFontFamily is empty, fontFamily is derived from the Oberon font name. *)
		globalFontFamily = "";

		(* A non-empty globalFontFamily is substituted for the family implied from the Oberon font name. *) 
		(* globalFontFamily = "'Times New Roman', serif"; *)

		fontScale = 90; (* (Browser rendered size/browser default size) expressed as percent. 
			If fontScale = 100, the Oberon default is rendered to the browser default. 
			If fontScale = 80, the Oberon default is converted to 80% of the browser default. *)

		defaultTabSize = 2;

		nOrdinals = 256;
		ten       = 9+1; (* Acceptable radix for HTML character references. *)
		sixteen = 0FH+1; (* Another acceptable radix.  https://en.wikipedia.org/wiki/Radix
			https://en.wikipedia.org/wiki/Character_encodings_in_HTML#HTML_character_references *)
		hexaDecimalCharacterRefs = FALSE; (* To use hexadecimal character references change this to
			 TRUE and calculate hexadecimals. *)

	TYPE 
		Integer = LONGINT; (* LONGINT in S3, SIGNED32 in A2O, INTEGER in V5. *)
		TextAttributes = RECORD
			fntName: ARRAY 24 OF CHAR; (* To contain "Courier10.Pr6.Fnt" or "Oberon10.Scn.Fnt" 
			or "Syntax12i.Scn.Fnt" for example. *)
			typeface: ARRAY 16 OF CHAR; (* Name of typeface.	"Courier" for example. *)
			size: Integer; (* Oberon font size in points. *)
			weight: CHAR; (* "n" denoting normal, "b", bold. *)
			style: CHAR; (* "n" denoting normal, "i", italic. *)
			col: Display.Color;
			voff: Integer (* Vertical offset of character. *)
		END;
		CharWriter = PROCEDURE(ch: CHAR);
		StringWriter = PROCEDURE(s: ARRAY OF CHAR);
		EolWriter = PROCEDURE();
		OrdinalStrings = ARRAY nOrdinals OF ARRAY 4 OF CHAR; (* 0 .. nOrdinals as strings of numeric characters. *)

	VAR
		C: CharWriter;
		S: StringWriter;
		L: EolWriter; (* to write the end of line. *)
		parT: Texts.Text; (* Parameter Text. *)
		parScn: Texts.Scanner; (* for command parameters. *)
		inT: Texts.Text; (* Input Text. *)
		D: Objects.Object; (* Document alternative to inT. *)
		sourceRdr: Texts.Reader;
		name: ARRAY 64 OF CHAR; (* Name of input file or viewer. *)
		newName: ARRAY 64 OF CHAR; (* Name of output file or viewer. *)
		nameScn: Texts.Scanner; (* for the name of the source viewer. *)
		v: Viewers.Viewer;
		mwF: Files.File; (* Mediawiki output. *)
		mwRider: Files.Rider; (* Rider for output file. *)
		mwT: Texts.Text; (* Output Text. *)
		mwWtr: Texts.Writer; (* for the MediaWiki output. *)
		Log: Texts.Writer; (* for Oberon.Log output. *)
		begin: Integer; (* Offset of selected beginning of input in parT. *)
		digits: ARRAY 17 OF CHAR;
		suffixArray: ARRAY 8 OF CHAR;
		linePrefix: ARRAY 64 OF CHAR; (* Prefix for output line. "" will produce flowed markup.
			Default, " ", produces fixed format. *)
		ch, previousCh: CHAR;
		atLeftMargin: BOOLEAN; (* TRUE when beginning a fresh line.	Pertinent to indentation and lists. *)
		globalAttr: TextAttributes; (* Attributes of the first character of the Text. *)
		extantAttr: TextAttributes; (* Attributes of the character being processed. *)
		remSize: Integer; (* (intended size of character)/(defaultSize).
			In Oberon, the default size is in Fonts.Default.
			In the CSS model, rem abbreviates root em.	The default size is 1 rem.
			https://www.w3.org/TR/css3-values/#rem 
			In Oberon, fonts range from 8 points to 24 points.	Equivalently in CSS, the smallest 
			possible font size is 1/3 rem and the largest is 3 rem. *)
		remString: ARRAY 5 OF CHAR; (* remSize as a string ranging '0.33" to "3.00". *)
		defaultSize: Integer; (* Size of Fonts.Default in Oberon. *)
		inSpan: BOOLEAN; (* TRUE in an inner span; where at least one attribute of ch doesn't match globalAttr. *)
		commentDepth: Integer;
		stringDepth: Integer;
		red, grn, blu: INTEGER;
		decimals: OrdinalStrings; (* 0 .. nOrdinals as strings of numeric characters in decimal notation. *)
		(* hexaDecimals: OrdinalStrings;  0 .. nOrdinals as strings of numeric characters in hexadecimal notation.. *)
		i: Integer;
		tabSize: Integer; (* Decimal number of blanks presented for a tab character. *)

	(* Add prefix and suffix to name, to obtain new name. *)
	PROCEDURE AddPrefixSuffix(prefix, name, suffix: ARRAY OF CHAR; VAR newName: ARRAY OF CHAR): BOOLEAN;
		VAR pi (* index in prefix *), ni (* index in name *), si (* index in suffix *), nni (* index in new name *): Integer;
			success: BOOLEAN;
	BEGIN
		Out.String("(prefix, name, suffix)= (");
		Out.String(prefix); Out.String(", "); Out.String(name); Out.String(", "); Out.String(suffix); Out.Char(")"); Out.Ln();
		(* i := 0; WHILE i < LEN(new) DO new[i] := "x"; INC(i) END; new[LEN(new)-1] := 0X;
		Out.String("new = "); Out.String(new); Out.Ln(); *)
		(* Characters are placed beginning at the high index. *)

		nni := 0;
		pi := 0;
		WHILE (pi < LEN(prefix)) & (prefix[pi] # 0X) (*& nni < LEN(new)*) DO INC(pi); INC(nni) END;
		IF (pi < LEN(prefix)) & (prefix[pi] = 0X) THEN DEC(pi); DEC(nni) END;
		INC(nni);
		Out.String("pi = "); Out.Int(pi, 0); Out.Ln();
		Out.String("nni = "); Out.Int(nni, 0); Out.Ln();

		ni := 0;
		WHILE (ni < LEN(name)) & (name[ni] # 0X) (*& nni < LEN(new)*) DO INC(ni); INC(nni) END;
		IF (ni < LEN(name)) & (name[ni] = 0X) THEN DEC(ni); DEC(nni) END;
		INC(nni);
		Out.String("ni = "); Out.Int(ni, 0); Out.Ln();
		Out.String("nni = "); Out.Int(nni, 0); Out.Ln();

		si := 0;
		WHILE (si < LEN(suffix)) & (suffix[si] # 0X) (*& nni < LEN(new)*) DO INC(si); INC(nni) END;
		IF (si < LEN(suffix)) & (suffix[si] = 0X) THEN DEC(si); DEC(nni) END;
		INC(nni);
		Out.String("si = "); Out.Int(si, 0); Out.Ln();
		Out.String("nni = "); Out.Int(nni, 0); Out.Ln();

		(* Begin copying characters at the high index. *)
		IF nni < LEN(name) THEN
			success := TRUE;
			newName[nni] := 0X; DEC(nni);
			Out.String("newName = "); Out.String(newName); Out.Ln();
			WHILE (-1 < si) & (-1 < nni) DO newName[nni] := suffix[si]; DEC(nni); DEC(si) END;
			Out.String("newName = "); Out.String(newName); Out.Ln();
			WHILE (-1 < ni) & (-1 < nni) DO newName[nni] := name[ni]; DEC(nni); DEC(ni) END;
			Out.String("newName = "); Out.String(newName); Out.Ln();
			WHILE (-1 < pi) & (-1 < nni) DO newName[nni] := prefix[pi]; DEC(nni); DEC(pi) END;
			Out.String("newName = "); Out.String(newName); Out.Ln();
			IF nni # -1 THEN
				Texts.WriteString(Log, "Construction of new name for file or viewer not completed correctly.");
				Texts.WriteLn(Log);
				Texts.WriteString(Log, "Index of new name, nni = "); Texts.WriteInt(Log, nni, 0);
				Texts.WriteLn(Log);
				Texts.WriteString(Log, "Index should be -1."); Texts.WriteLn(Log)
			END
		ELSE
			success := FALSE;
			Texts.WriteString(Log, "New name is too large for array provided."); Texts.WriteLn(Log);
		END;
		Texts.Append(Oberon.Log, Log.buf);
		RETURN success
	END AddPrefixSuffix;

	PROCEDURE CF(ch: CHAR); BEGIN Files.Write(mwRider, ch) END CF;

	PROCEDURE CT(ch: CHAR); BEGIN Texts.Write(mwWtr, ch) END CT;

	PROCEDURE SF(s: ARRAY OF CHAR);
		VAR i: Integer;
	BEGIN
		i := 0;
		WHILE s[i] # 0X DO Files.Write(mwRider, s[i]); INC(i) END
	END SF;

	PROCEDURE ST(s: ARRAY OF CHAR);
		VAR i: Integer;
	BEGIN
		i := 0;
		WHILE s[i] # 0X DO Texts.Write(mwWtr, s[i]); INC(i) END
	END ST;

	PROCEDURE LF(); BEGIN Files.Write(mwRider, 0DX); Files.Write(mwRider, 0AX) END LF;

	PROCEDURE LT(); BEGIN Texts.Write(mwWtr, 0DX) END LT;

	PROCEDURE ReadCh();
	BEGIN
		previousCh := ch;
		REPEAT Texts.Read(sourceRdr, ch) UNTIL (sourceRdr.eot OR (sourceRdr.lib IS Fonts.Font));
		IF (previousCh = "(") & (ch = "*") THEN INC(commentDepth) END;
		IF (previousCh = "*") & (ch = ")") THEN DEC(commentDepth) END;
		IF commentDepth = 0 THEN
			IF ch = 22X THEN
				IF stringDepth = 0 THEN
					INC(stringDepth)
				ELSIF stringDepth = 1 THEN
					DEC(stringDepth)
				ELSE
					Out.String("MediaWiki.Read: stringDepth is neither 0 nor 1.")
				END
			END
		END
	END ReadCh;

	(** Precondition: attr.fntName contains the name of an Oberon font. "Oberon10.Scn.Fnt" for example.
			Postcondition: typeface name, size, weight, style, col and voff have values according to ch. *)
	PROCEDURE DecodeAttributes(VAR attr: TextAttributes);
		VAR i: Integer; (* Index to characters in font name. *)
	BEGIN
		i := 0;
		WHILE ("@" < attr.fntName[i]) & (attr.fntName[i] < "{") DO
			attr.typeface[i] := attr.fntName[i];
			INC(i)
		END;
		attr.typeface[i] := 0X;
		attr.size := 0;
		WHILE ("/" < attr.fntName[i]) & (attr.fntName[i] < ":") DO
			attr.size := (10 * attr.size) + ORD(attr.fntName[i]) - ORD("0");
			INC(i)
		END;
		IF attr.fntName[i] = "b" THEN
			attr.weight := "b"; attr.style := "n"
		ELSIF attr.fntName[i] = "i" THEN
			attr.weight := "n"; attr.style := "i"
		ELSIF attr.fntName[i] = "m" THEN
			attr.weight := "m"; attr.style := "n"
		ELSIF attr.fntName[i] = "." THEN
			attr.weight := "n"; attr.style := "n"
		ELSE
			Out.String("MediaWiki.DecodeAttributes: character "); 
			Out.Char(22X); Out.Char(ch); Out.Char(22X);
			Out.String(" following digit in font name not recognized."); Out.Ln()
		END;
		attr.col := sourceRdr.col;
		attr.voff := sourceRdr.voff
	END DecodeAttributes;

	PROCEDURE Separate(); (* Write the appropriate attribute separator. *)
	BEGIN
		S("; "); IF ~inSpan THEN L(); S(linePrefix) END
	END Separate;

	(** Begin a span.  The global span has all attributes.  A local span 
	contains each attribute of ch differing from the attribute in globalAttr. *)
	PROCEDURE BeginSpan();
		VAR
			attributeWritten: BOOLEAN;
	BEGIN
		Out.String("MediaWiki.BeginSpan: "); Out.Ln();
		Out.String("extantAttr.fntName = "); Out.String(extantAttr.fntName); Out.String(", "); Out.Ln();
		Out.String("typeface = "); Out.String(extantAttr.typeface);
		Out.String(", size = "); Out.Int(extantAttr.size, 0);
		Out.String(", weight = "); Out.Char(extantAttr.weight);
		Out.String(", style = "); Out.Char(extantAttr.style); Out.String(", "); Out.Ln();
		Out.String("col = "); Out.Int(extantAttr.col, 0);
		Out.String(", voff = "); Out.Int(extantAttr.voff, 0);
		Out.String(", tabSize = "); Out.String(decimals[tabSize]); Out.Ln();
		S("<span style="); C(22X);
		attributeWritten := FALSE;
		(* Typeface *)
		IF extantAttr.typeface # globalAttr.typeface THEN
			S("font-family: ");
			IF (globalFontFamily = "") OR inSpan THEN
				S(extantAttr.typeface);
				IF (extantAttr.typeface = "Oberon") OR (extantAttr.typeface = "Syntax") THEN
					S(", sans-serif") (* When Oberon or Syntax is not available suggest substitution of any sans-serif. 
						See https://www.w3schools.com/cssref/css_websafe_fonts.asp . *)
				ELSIF extantAttr.typeface = "Courier" THEN (* Probably available.  If not substitute any monospace. *)
					S(", monospace")
				ELSE (* Another font in Oberon?  Unlikely to happen but suggest sans-serif. *)
					S(", sans-serif")
				END
			ELSE
				S(globalFontFamily)
			END;
			attributeWritten := TRUE
		END;
		(* Font size *)
		IF (extantAttr.size # globalAttr.size) THEN
			IF attributeWritten THEN Separate() END;
			S("font-size: ");
			(* Calculate font scale factor rounded to two digits and express as string with decimal. *)
			remString[4] := 0X;
			remSize := SHORT(ENTIER(extantAttr.size * fontScale / defaultSize + 0.5));
			remString[3] := CHR(remSize MOD 10 + ORD("0"));
			remSize := remSize DIV 10;
			remString[2] := CHR(remSize MOD 10 + ORD("0"));
			remSize := remSize DIV 10;
			remString[1] := ".";
			remString[0] := CHR(remSize MOD 10 + ORD("0"));
			S(remString); 
			S("rem");
			attributeWritten := TRUE
		END;
		(* Font weight *)
		IF extantAttr.weight # globalAttr.weight THEN
			IF attributeWritten THEN Separate() END;
			S("font-weight: ");
			IF extantAttr.weight = "n" THEN S("normal") 
			ELSIF extantAttr.weight = "b" THEN S("bold")
			ELSIF extantAttr.weight = "m" THEN S("600")
			ELSE
				Texts.WriteString(Log, "MediaWiki.ChangeAttributes: font weight "); 
				Texts.Write(Log, extantAttr.weight);
				Texts.WriteString(Log, " failed to match a weight symbol."); Texts.WriteLn(Log);
				Texts.Append(Oberon.Log, Log.buf)
			END;
			attributeWritten := TRUE
		END;
		(* Font style *)
		IF extantAttr.style # globalAttr.style THEN
			IF attributeWritten THEN Separate() END;
			S("font-style: ");
			IF extantAttr.style = "n" THEN S("normal") 
			ELSIF extantAttr.style = "i" THEN S("italic")
			ELSE
				Out.String("MediaWiki.ChangeAttributes: font style "); Out.Char(extantAttr.style);
				Out.String(" failed to match a style symbol."); Out.Ln()
			END;
			attributeWritten := TRUE
		END;
		(* Text (font) color *)
		IF extantAttr.col # globalAttr.col THEN
			IF attributeWritten THEN Separate() END;
			S("color: #");
			Display.GetColor(extantAttr.col, red, grn, blu);
			C(digits[red  DIV  16]);
			C(digits[red MOD 16]);
			C(digits[grn  DIV  16]);
			C(digits[grn MOD 16]);
			C(digits[blu  DIV  16]);
			C(digits[blu MOD 16]);
			attributeWritten := TRUE
		END;
		(* Text vertical offset *)
		(* TextFrames ignores voff.  ScriptFrames assumes % and Script.Tool notes percent; not points. *)
		IF extantAttr.voff # globalAttr.voff THEN
			IF attributeWritten THEN Separate() END;
			S("position: relative"); Separate(); S("top: ");
			Out.String("MediaWiki.BeginSpan: extantAttr.voff = "); Out.Int(extantAttr.voff, 0); Out.Ln();
			IF extantAttr.voff > 0 THEN
				C("-"); S(decimals[extantAttr.voff])
			ELSE
				S(decimals[-extantAttr.voff])
			END;
			C("%")
		END;
		(* Tab size. *)
		IF ~inSpan THEN
			Separate(); S("-moz-tab-size: "); S(decimals[tabSize]);
			Separate(); S("tab-size: "); S(decimals[tabSize])
		END;
		C(22X); C(">"); (* IF ~inSpan THEN L(); S(linePrefix) END; *)
		Out.String("BeginSpan(): END BeginSpan."); Out.Ln()
	END BeginSpan;

	PROCEDURE EndSpan();
	BEGIN
		S("</span>")
	END EndSpan;

	(* Identify a character having markup significance & requiring replacement with the HTML character reference. *)
	PROCEDURE  ChRefRequired(): BOOLEAN;
		VAR res: BOOLEAN;
	BEGIN
		IF		("~" < ch)
			OR ((previousCh = "&") & (ch = "#"))	(* HTML and Wikimedia character reference. *)
			OR ((previousCh = "'") & (ch = "'"))	(* Wikimedia italic and bold notation. *)
			OR ((previousCh = ":") & (ch = "/"))	(* URL. *)
			OR ((0 < commentDepth) & ((ch = "<") (* HTML tag *) OR (ch = "[") (* Wikimedia link *)))
			OR ((0 = commentDepth) & ((ch = "<") (* HTML tag *) OR (ch = "[") (* Wikimedia link *)))
			OR ((previousCh = "{") & (ch = "{")) (* Wikimedia template. *)
			OR ((previousCh = "~") & (ch = "~")) (* Wikimedia userid. *)
				THEN res := TRUE
		ELSIF atLeftMargin THEN
			IF      (ch = 09X)  (* Tab at left margin is deleted by Wikimedia. *)
				OR (ch = " ")   (* Wikimedia preformatted box. *)
				OR (ch = "#")  (* Wikimedia numbered list. *)
				OR (ch = "*")  (* Wikimedia bullet list. *)
				OR (ch = ":")	(* Wikimedia indentation. *)
				OR (ch = ";")  (* Wikimedia definition list. *)
				OR (ch = "=")  (* Wikimedia heading. *)
				THEN res := TRUE
			END
		ELSE
			res := FALSE
		END;
		RETURN res
	END  ChRefRequired;

	PROCEDURE WriteChRef(); 
	BEGIN
		S("&#"); IF hexaDecimalCharacterRefs THEN C("x") END; S(decimals[ORD(ch)]); C(";")
	END WriteChRef;

	PROCEDURE HandleCh();
	BEGIN
		IF ch = 0DX THEN (* Begin a new line. *)
			L();
			IF linePrefix[0] = 0X THEN
				atLeftMargin := TRUE;
			ELSE
				S(linePrefix);
				atLeftMargin := FALSE
			END
		ELSE
			IF ChRefRequired() THEN
				WriteChRef()
			ELSE
				C(ch)
			END;
			atLeftMargin := FALSE
		END
	END HandleCh;

	(* Return TRUE when all attributes of ch match attr.  Used to compare attributes of 
		ch to those of preceding character and to the global attributes. *)
	PROCEDURE ChAttrMatch(VAR attr: TextAttributes): BOOLEAN;
	BEGIN
		RETURN ((attr.fntName = sourceRdr.lib.name) & (attr.col = sourceRdr.col) & (attr.voff = sourceRdr.voff))
	END ChAttrMatch;

	PROCEDURE MarkupText();
	BEGIN
		Texts.OpenWriter(mwWtr);
		IF inT = NIL THEN
			Out.String("MediaWiki.MarkupText: inT = NIL.  No Text to convert."); Out.Ln()
		ELSIF inT.len = 0 THEN (* mwWtr.buf is empty? *)
		ELSIF inT.len > 0 THEN
			atLeftMargin := TRUE;
			commentDepth := 0;
			stringDepth := 0;
			ch := "a";
			Texts.OpenReader(sourceRdr, inT, 0);
			ReadCh();
			IF sourceRdr.eot THEN Out.String("MarkupText: sourceRdr.eot."); Out.Ln()
			ELSIF sourceRdr.lib = NIL THEN Out.String("sourceRdr.lib = NIL."); Out.Ln()
			ELSIF sourceRdr.lib IS Fonts.Font THEN (* Got a character in ch. *)
				InitAttr(); (* Initialize attributes with values never realized in a Text. *)
				COPY(sourceRdr.lib.name, extantAttr.fntName);
				DecodeAttributes(extantAttr);
				Out.String("Attributes of first character decoded to extantAttr."); Out.Ln();
				S(linePrefix); 
				inSpan := FALSE;
				BeginSpan(); (* Write attributes according to first character. *)
				HandleCh();
				COPY(extantAttr.fntName, globalAttr.fntName);
				DecodeAttributes(globalAttr);
				Out.String("Attributes of first character decoded to globalAttr."); Out.Ln();
				WHILE ~sourceRdr.eot DO 
					ReadCh();
					IF sourceRdr.eot THEN 
						Out.String("MarkupText: sourceRdr.eot at Texts.Pos = ");
						Out.Int(Texts.Pos(sourceRdr)-1, 3); Out.Ln() END;
					IF (sourceRdr.lib = NIL) THEN 
						Out.String("MarkupText: sourceRdr.lib = NIL at Texts.Pos = ");
						Out.Int(Texts.Pos(sourceRdr)-1, 3); Out.Ln()
					ELSIF ~(sourceRdr.lib IS Fonts.Font) THEN
						Out.String("MarkupText: sourceRdr.lib is not Fonts.Font at Texts.Pos = ");
						Out.Int(Texts.Pos(sourceRdr)-1, 3); Out.Ln()
					ELSE
						IF ~ChAttrMatch(extantAttr) THEN (* Change of attributes. *)
							IF inSpan THEN EndSpan(); inSpan := FALSE END;
							COPY(sourceRdr.lib.name, extantAttr.fntName);
							DecodeAttributes(extantAttr);
							IF ~ChAttrMatch(globalAttr) THEN inSpan := TRUE; BeginSpan() END
						END;
						HandleCh()
					END
				END;  (* WHILE *)
				IF inSpan THEN EndSpan() END;
				EndSpan(); L(); (* Close global span. *)
				L();
				S("{{BookCat}}"); (* Wikibook requirement. *) L()
			END
		END;
		Texts.Open(mwT, "");
		Out.String("MarkupText(): completed Texts.Open(mwT, ..."); Out.Ln();
		Texts.Append(mwT, mwWtr.buf);
		Out.String("MediaWiki: END MarkupText"); Out.Ln()
	END MarkupText;

	PROCEDURE StrLen(s: ARRAY OF CHAR):Integer;
		VAR len: Integer;
	BEGIN
		len := 0;
		WHILE (len < LEN(s)) & (s[len] # 0X) DO INC(len) END;
		RETURN len 
	END StrLen;

	PROCEDURE MarkupViewer();
		VAR
			V: Viewers.Viewer;
			X, Y: INTEGER;
	BEGIN
		Out.String("MarkupViewer(): invoking MarkupText() on Text in viewer ");
		Out.String(name); Out.Ln();
		(* Set write procedures for output into a Text.Writer.buf. *)
		C := CT;
		S := ST;
		L := LT;
		MarkupText();
		Oberon.AllocateUserViewer(Oberon.Par.vwr.X, X, Y);
		V := MenuViewers.New(TextFrames.NewMenu(newName, Menu),
			TextFrames.NewText(mwT, 0), TextFrames.menuH, X, Y)
	END MarkupViewer;

	(** Mark up the Text in a file and store the result in a file. *)
	PROCEDURE MarkupFile();
	BEGIN
		Out.String("MarkupFile: invoking MarkupText() on Text in file "); Out.String(name); Out.Ln();
		NEW(inT); Texts.Open(inT, name);
		(* Set write procedures for output into a file. *)
		C := CF;
		S := SF;
		L := LF;
		mwF := Files.New(newName);
		Files.Set(mwRider, mwF, 0);
		Out.String("MarkupFile(): preparation for MarkupText() complete."); Out.Ln();
		MarkupText();
		Out.String("MarkupFile(): finished writing to file named in mwF."); Out.Ln();
		Files.Register(mwF);
		Texts.WriteString(Log, name);
		IF (StrLen(name) + StrLen(newName)) > 50 THEN
			Texts.WriteLn(Log); Texts.Write(Log, 09X)
		END;
		Texts.WriteString(Log, " => "); 
		Texts.WriteString(Log, newName); Texts.Write(Log, 09X); Texts.WriteString(Log, "  "); 
		Texts.WriteInt(Log, Files.Length(mwF), 0); 
		Texts.WriteLn(Log); Texts.Append(Oberon.Log, Log.buf);
		Out.String("Diff.Do  "); Out.String(name); Out.Char(" "); Out.String(newName); Out.Ln()
	END MarkupFile;

	PROCEDURE WriteK(VAR W: Texts.Writer;  k: Integer);
		VAR suffix: CHAR;
	BEGIN
		IF k < 10*1024 THEN suffix := "K"
		ELSIF k < 10*1024*1024 THEN suffix := "M"; k := k DIV 1024
		ELSE suffix := "G"; k := k DIV (1024*1024)
		END;
		Texts.WriteInt(W, k, 1);  Texts.Write(W, suffix);  Texts.Write(W, "B")
	END WriteK;

	PROCEDURE MarkupFiles();
		VAR free, total, largest, low, high: Integer (* SIZE in A2 *) (* Integer in ETH Oberon *);
	BEGIN
		Out.String("MarkupFiles() BEGIN: parScn.s = "); Out.String(parScn.s); Out.Ln();
		WHILE (~parScn.eot) & (Texts.Pos(parScn) + 100 < MAX(Integer)) & (parScn.class = Texts.Name) DO
			IF parScn.class = Texts.Name THEN (* A input file name to evaluate. *)
				COPY(parScn.s, name);
				Out.String("MarkupFiles(): token copied to name is "); Out.String(parScn.s); Out.Ln();
				Texts.Scan(parScn);
				IF parScn.class # Texts.Char THEN (* parScn.s contains name of next input file. *)
					IF AddPrefixSuffix(mediaWikiPrefix, name, MediaWikiSuffix, newName) THEN
						MarkupFile()
					END
				ELSE (* parScn.class = Texts.Char ; newName according to "=>" syntax or end of parameter list. *)
					IF parScn.c = "~" THEN (* new name not specified and no more parameters. *)
						IF AddPrefixSuffix(mediaWikiPrefix, name, MediaWikiSuffix, newName) THEN
							MarkupFile()
						END
					ELSIF parScn.c = "=" THEN (* ">" should be next. *)
						Texts.Scan(parScn);
						IF parScn.class = Texts.Char THEN
							IF parScn.c = ">" THEN
								(* Syntax conforms to convention. *)
							ELSE (* Assume ">" was intended but not typed correctly. *)
								Texts.WriteString(Log,
								"MediaWiki.MarkupFiles(): character following = is not >."); 
								Texts.WriteLn(Log); Texts.Append(Oberon.Log, Log.buf)
							END;
							Texts.Scan(parScn); (* Try for output name. *)
							IF parScn.class = Texts.Name THEN
								COPY(parScn.s, newName)
							ELSE
								Texts.WriteString(Log,
								"MediaWiki.MarkupFiles(): output name not acquired according to syntax."); 
								Texts.WriteLn(Log); Texts.Append(Oberon.Log, Log.buf)
							END
						END;
						(* name and newName now available. *)
						MarkupFile();
						Texts.Scan(parScn)
					ELSE
						Texts.WriteString(Log,
						"MediaWiki.MarkupFiles(): character parameter following input file name not appropriate.");
						Texts.WriteLn(Log); Texts.Append(Oberon.Log, Log.buf)
					END
				END
			ELSE
				Texts.WriteString(Log,
				"MediaWiki.MarkupFiles(): no file name acquired by scanning.");
				Texts.WriteLn(Log); Texts.Append(Oberon.Log, Log.buf) 
			END
		END; (* WHILE *)
		(* A2 heap info.
		Heaps.GetHeapInfo(total, free, largest);
		free := (free+512) DIV 1024;
		largest := (largest+512) DIV 1024;
		Machine.GetFreeK(total, low, high);
		INC(free, low+high);
		IF high > largest THEN largest := high END;
		IF low > largest THEN largest := low END;
		Texts.Write(Log, 9X); Texts.WriteString(Log, "Heap has ");
		WriteK(Log, SIGNED32(free)); Texts.WriteString(Log, " of ");
		WriteK(Log, SIGNED32(total)); Texts.WriteString(Log, " free (");
		WriteK(Log, SIGNED32(largest)); Texts.WriteString(Log, " contiguous)");  Texts.WriteLn(Log);
		*)
		(* S3 heap info. *)
		free := (Kernel.Available()+512) DIV 1024;
		total := (Kernel.Available()+Kernel.Used()+512) DIV 1024;
		largest := (Kernel.LargestAvailable()+512) DIV 1024;
		Texts.Write(Log, 9X); Texts.WriteString(Log, "Heap has ");
		WriteK(Log, free); Texts.WriteString(Log, " of ");
		WriteK(Log, total); Texts.WriteString(Log, " free (");
		WriteK(Log, largest); Texts.WriteString(Log, " contiguous)");  Texts.WriteLn(Log);
		
		Texts.Append(Oberon.Log, Log.buf)
	END MarkupFiles;

	(** MediaWiki.Markup ["linePrefix"] ( {File ["=>" mwFile]} | "*" | "^" ) ~
		Examples
		MediaWiki.Markup *    Markup the * marked viewer using the default linePrefix, a blank character.
			In Mediawiki, the " " line prefix produces fixed format in the browser view.
		MediaWiki.Markup "" * ~  Empty linePrefix, producing flowed format in the browser view.
		MediaWiki.Markup "a b" * ~  Prefix each line with "a b".
		MediaWiki.Markup This.Mod  That.Mod ~  Produce files This.Mod.mw and That.Mod.mw with default line prefix.
		MediaWiki.Markup "a b" This.Mod => myThis.Mod.mw  That.Mod => otherThat.Mod ~  Produce files 
			myThis.Mod.mw and otherThat.Mod.  Lines prefixed "a b".
		A series of lines, each beginning with " ", is converted by the Wikimedia software to a preformatted block. *)
	PROCEDURE Markup*;
		VAR
			end, time: Integer;
	BEGIN
		(* Texts.WriteLn(Log);
		Texts.WriteString(Log, "MediaWiki.Markup"); Texts.WriteLn(Log);
		Texts.Append(Oberon.Log, Log.buf); *)
		Texts.OpenScanner(parScn, Oberon.Par.text, Oberon.Par.pos);
		Texts.Scan(parScn);
		IF parScn.class # Texts.String THEN (* No line prefix in command. *)
			linePrefix[0] := " "; linePrefix[1] := 0X
		ELSE
			COPY(parScn.s, linePrefix);
			Texts.Scan(parScn)
		END;
		IF parScn.class = Texts.Name THEN (* Input from named files and output to files. *)
			MarkupFiles()
		ELSIF (parScn.class = Texts.Char) THEN
			IF parScn.c = "~" THEN
				(* Done*)
			ELSIF parScn.c = "^" THEN
				(* Input from files named in selection and output to files. *)
				Oberon.GetSelection(parT, begin, end, time);
				IF time >= 0 THEN 
					Texts.OpenScanner(parScn, parT, begin); 
						Texts.Scan(parScn)
				END;
				MarkupFiles();
			ELSIF parScn.c = "*" THEN (* Input from viewer and output to viewer. *)
				inT := Oberon.MarkedText();
				D := Documents.MarkedDoc();
				IF D = NIL THEN  (* A plain Text viewer? *)
					IF inT # NIL THEN
						v := Oberon.MarkedViewer();
						Texts.OpenScanner(nameScn, v.dsc(TextFrames.Frame).text, 0);
						Texts.Scan(nameScn);
						Out.String("Marking up Text in viewer named "); Out.String(nameScn.s); Out.Ln();
						COPY(nameScn.s, name)
					END
				ELSE  (* A Document viewer. *)
					COPY(D(Documents.Document).name, name)
				END;
				IF ~AddPrefixSuffix(mediaWikiPrefix, name, suffixArray, newName) THEN
					Texts.WriteString(Log, "Failure in construction of new name.  Ref. AddPrefixSuffix().");
					Texts.WriteLn(Log); Texts.Append(Oberon.Log, Log.buf)
				END;
				MarkupViewer();
				(* Facilitate visual check of original Text and Text derived from markup via HTML. *)
				IF inT # NIL THEN
					Out.String("Diff.Do  "); Out.String(newName); Out.String(" a.mw"); Out.Ln();
					Out.String("get  "); Out.String(newName); Out.Ln()
				END;
			END
		ELSE
			Texts.WriteString(Log, "MediaWiki.Markup: parameter of command not recognized.");
			Texts.WriteLn(Log); Texts.Append(Oberon.Log, Log.buf)
		END
	END Markup;

	(* Create an array with rows 0..nOrdinals-1 representing ordinals as characters.
		The ordinal stored in each row terminated by 0X.  ordinals[ord, 0] is the big end. 
		This character representation of ordinals is used for HTML character references
		and for vertical offset. This version uses DIV and MOD.
	PROCEDURE BuildOrdinals0(VAR ordinals: OrdinalStrings; radix: Integer);
		VAR 
			ord, i, j: Integer;
			nn: ARRAY 4 OF Integer;
	BEGIN
		ord := 0;
		WHILE ord < nOrdinals DO
			nn[0] := ord; i := LEN(nn);
			REPEAT
				DEC(i);
				nn[i] := nn[0] MOD radix;
				nn[0] := nn[0] DIV radix
			UNTIL nn[0] = 0;
			j := 0; 
			WHILE i < LEN(nn) DO
				ordinals[ord, j] := digits[nn[i]];
				INC(j); INC(i)
			END;
			ordinals[ord, j] := 0X;
			Out.String(ordinals[ord]); Out.Char(" ");
			INC(ord)
		END;
		Out.Ln();
		Out.String("Largest ordinal in ordinals expressed as string is "); 
		Out.String(ordinals[nOrdinals-1]); Out.String("  "); Out.Ln();
	END BuildOrdinals0; *)

	(* Create an array with rows 0..nOrdinals-1 representing ordinals as characters.
		The ordinal stored in each row terminated by 0X.  ordinals[ord, 0] is the big end. 
		This character representation of ordinals is used for HTML character references
		and for vertical offset.  This version uses elementary counting. *)
	PROCEDURE BuildOrdinals(VAR ordinals: OrdinalStrings; radix: Integer);
		VAR 
			ord, i, j: Integer;
			n: Integer; (* Number of characters in nnn used to represent ord. *)
			nnn: ARRAY 4 OF CHAR; (* An ordinal as a string of characters beginning from the little end. *)
			carry: BOOLEAN;
	BEGIN
		ord := 0;
		nnn[0] := "0"; n := 1;
		WHILE ord < nOrdinals DO
			(* Copy nnn into ordinals, reversing order of digits. *)
			i := 0; j := n;
			ordinals[ord, n] := 0X;
			WHILE i < n DO
				DEC(j);
				ordinals[ord, j] := nnn[i];
				INC(i)
			END;
			(* Increment nnn and ord. *)
			i := 0; carry := TRUE;
			WHILE i < n DO
				IF carry THEN
					CASE nnn[i] OF
						| "0": nnn[i] := "1"; carry := FALSE
						| "1": nnn[i] := "2"; carry := FALSE
						| "2": nnn[i] := "3"; carry := FALSE
						| "3": nnn[i] := "4"; carry := FALSE
						| "4": nnn[i] := "5"; carry := FALSE
						| "5": nnn[i] := "6"; carry := FALSE
						| "6": nnn[i] := "7"; carry := FALSE
						| "7": nnn[i] := "8"; carry := FALSE
						| "8": nnn[i] := "9"; carry := FALSE
						| "9": nnn[i] := "0"; carry := TRUE
					ELSE
						Texts.WriteString(Log, "Mediawiki.BuildOrdinals: nnn["); 
						Texts.WriteInt(Log, i, 0); Texts.WriteString(Log, "] = "); Texts.Write(Log, nnn[i]); 
						Texts.WriteString(Log, "not not a recognized CASE."); Texts.WriteLn(Log);
						Texts.Append(Oberon.Log, Log.buf)
					END
				END; (* IF carry *)
				INC(i)
			END; (* WHILE i < n *)
			(* Now i = n *)
			IF carry THEN nnn[i] := "1"; INC(n) END;
			Out.String(ordinals[ord]); Out.Char(" ");
			INC(ord)
		END; (* WHILE ord *)
		Out.Ln();
		Out.String("Largest ordinal in ordinals expressed as string is "); 
		Out.String(ordinals[nOrdinals-1]); Out.String("  "); Out.Ln();
	END BuildOrdinals;

	PROCEDURE InitAttr(); (* Initialize attributes with values never realized in a Text. *)
	BEGIN
		globalAttr.fntName[0] := "a"; globalAttr.fntName[1] := 0X;
		globalAttr.typeface[0] := "a"; globalAttr.typeface[1] := 0X;
		globalAttr.size := 0;
		globalAttr.weight := "a";
		globalAttr.style := "a";
		globalAttr.col := -1;
		globalAttr.voff := MAX(Integer);
	END InitAttr;

BEGIN
	tabSize := defaultTabSize;
	Texts.OpenWriter(Log);
	digits := "0123456789ABCDEF";
	suffixArray := MediaWikiSuffix;
	BuildOrdinals(decimals, ten);
	(* BuildOrdinals(hexaDecimals, sixteen); *)
	Out.String("Fonts.Default.name = "); Out.String(Fonts.Default.name); Out.Ln();
	i := 0;
	WHILE (Fonts.Default.name[i] < "0") OR ("9" < Fonts.Default.name[i]) DO INC(i) END;
	defaultSize := 0;
	WHILE ("/" < Fonts.Default.name[i]) & (Fonts.Default.name[i] < ":") DO
		defaultSize := (10 * defaultSize) + ORD(Fonts.Default.name[i]) - ORD("0");
		INC(i)
	END;
	Out.String("Oberon.Fonts.Default.name => defaultSize = "); Out.Int(defaultSize, 0); Out.Ln();
	NEW(mwT)
END MediaWiki.

MediaWiki.Markup *    MediaWiki.Markup  t tt ~