< Oberon < A2
(* 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 the 
	MediaWiki.Markup command converts a blank in indentation to "&#160;" 
	and a tab in indentation to "&#9;".

	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 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 interpret all of this information.

	SYNTAX OF OUTPUT
	markup = " <span style=" globalAttributes ">" {{ch} {span {ch}}} "</span>".
	globalAttributes = """ fontSpec ";" sizeSpec ";" weightSpec ";" styleSpec ";" colorSpec ";" voffSpec """. 
	span = "<span style=" """ attributeSpec {";" attributeSpec} """ ">" {ch} "</span>".
	attributeSpec = fontSpec | colorSpec | sizeSpec | weightSpec | styleSpec.
	fontSpec = "font-family: " fontFamily.
	fontFamily = fontName (", monospace" | ", Helvetica, sans-serif").
	fontName = letter {letter | digit}
	sizeSpec = "font-size: " size.
	size = digit "." digit digit "rem".
	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}.  (voff and offset have opposed signs.  Positive offset shifts down.)

	TEXT ATTRIBUTES
	The first character of the 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 a nested 
	internal or local span.  The inSpan flag is TRUE in an internal span.

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

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

MODULE MediaWiki IN Oberon;	(** portable *)

IMPORT  
	Files, Texts, Oberon, Out := OutStub, Fonts, Display, TextFrames, Viewers, 
	MenuViewers, Objects, Documents
	(* , Kernel; 	S3 *)
	, Machine IN A2, Heaps IN A2; (* A2 *)
	(* Change OutStub to Out for profuse tracing information. *)

CONST
	Menu = "System.Close System.Copy System.Grow ET.Search ET.Replace ET.StoreAscii";
	MediaWikiSuffix = ".mw";
	nOrdinals = 128;
	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
		 FALSE and calculate hexadecimals. *)

TYPE 
	Integer = LONGINT; (* LONGINT in S3, 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, newName: ARRAY 64 OF CHAR; (* Names of input file or viewer and 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: CHAR;
	inLeftMargin: 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; (* Size of character as percentage of defaultSize. 
		In Oberon, the default size is in Fonts.Default.
		In the CSS model, rem abbreviates root em and 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. *)
	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;

(* Add suffix to name without overrunning the containing array. *)
PROCEDURE AddSuffix(CONST name, suffix: ARRAY OF CHAR; VAR new: ARRAY OF CHAR);
	VAR i, si: Integer;
	BEGIN
		Out.String("MediaWiki.AddSuffix BEGIN: (name,  suffix,  new)"); Out.Ln();
		Out.String("= ("); Out.String(name); Out.String(", "); Out.String(suffix); Out.String(", "); 
		Out.String(new); Out.Char(")"); Out.Ln();
		(* Locate upper bound of the first character of suffix. *)
		i := 0; si := LEN(new) - 1;
		WHILE (suffix[i] # 0X) & (0 < si) DO INC(i); DEC(si) END;
		IF suffix[i] # 0X THEN
			Texts.WriteString(Log, "Long suffix truncated to fit in new array."); Texts.WriteLn(Log);
			Texts.Append(Oberon.Log, Log.buf)
		END; 
		(* Retain or copy as much of the original name as suffix allows. *)
		i := 0; 
		IF name = new THEN
			WHILE (i < si) & (name[i] # 0X) DO INC(i) END
		ELSE
			WHILE (i < si) & (name[i] # 0X) DO new[i] := name[i]; INC(i) END
		END;
		IF name[i] # 0X THEN
			Texts.WriteString(Log, "Name truncated to fit suffix."); Texts.WriteLn(Log);
			Texts.Append(Oberon.Log, Log.buf)
		END;
		(* Add suffix. *)
		si := 0;
		WHILE (suffix[si] # 0X) & (i +1 < LEN(new)) DO 
			new[i] := suffix[si]; INC(i); INC(si)
		END;
		new[i] := 0X;
		Out.String("MediaWiki.AddSuffix END: (name,  suffix,  new)"); Out.Ln();
		Out.String("= ("); Out.String(name); Out.String(", "); Out.String(suffix); Out.String(", "); 
		Out.String(new); Out.Char(")"); Out.Ln()
	END AddSuffix;

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 Read(): BOOLEAN;
	BEGIN
		Texts.Read(sourceRdr, ch);
		RETURN ~sourceRdr.eot
	END Read;

(** 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 ELSE L(); S(linePrefix) END
	END Separate;

(** Begin a <span ...> containing each attribute of ch differing from the attribute in globalAttr. 
The global span contains all attributes. *)
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.Ln();
		S("<span style="); C(22X);
		attributeWritten := FALSE;
		IF extantAttr.typeface # globalAttr.typeface THEN
			S("font-family: "); S(extantAttr.typeface);
			IF extantAttr.typeface = "Courier" THEN
				S(", monospace")
			ELSE
				S(", Helvetica, sans-serif")
			END;
			attributeWritten := TRUE
		END;
		IF (extantAttr.size # globalAttr.size) THEN
			IF attributeWritten THEN Separate() END;
			S("font-size: ");
			(* Calculate remstring for extantAttr.size. *)
			IF (extantAttr.size MOD defaultSize) = 0 THEN
				remString[0] := CHR(extantAttr.size DIV defaultSize + ORD("0"));
				remString[1] := 0X
			ELSE
				(* Calculate font scale factor rounded to two digits and express as string with decimal. *)
				remSize := SHORT(ENTIER(extantAttr.size * 100 / defaultSize + 0.5));
				remString[4] := 0X;
				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"));
			END;
			S(remString); 
			S("rem");
			attributeWritten := TRUE
		END;
		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;
		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;
		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;
		(* 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;
		C(22X); L();
		S(linePrefix); C(">");
		Out.String("BeginSpan(): END BeginSpan."); Out.Ln()
	END BeginSpan;

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

(* Identify characters which have Wiki text significance anywhere. *)
PROCEDURE  isWikiChar(): BOOLEAN;
	VAR res: BOOLEAN;
	BEGIN
		IF		(ch = "&")	(* HTML and Wikimedia character reference. *)
			OR (ch = "'")	(* Wikimedia italic and bold notation. *)
			OR (ch = ":")	(* Wikimedia indentation and HTML URL. *)
			OR (ch = "<")	(* HTML tag. *)
			OR (ch = "=")	(* Wikimedia heading. *)
			OR (ch = ">")		(* HTML tag. *)
			OR (ch = "[")	(* Wikimedia link. *)
			OR (ch = "]")	(* Wikimedia link. *)
			OR (("{" <= ch) & (ch <= "~")) (* Wikimedia template, pipe and username notations. *)
				THEN res := TRUE
		ELSE
			res := FALSE
		END;
		RETURN res
	END isWikiChar;

(* Identify characters having markup significance & requiring replacement with HTML character references. *)
PROCEDURE  ChRefRequired(): BOOLEAN;
	VAR res: BOOLEAN;
	BEGIN
		IF inLeftMargin THEN (* Wiki characters at left margin. *)
			IF      (ch = 09X)  (* Tabs in left margin are deleted by Wikimedia. *)
				OR (ch = " ")   (* Wikimedia preformatted box. *)
				OR (ch = "#")  (* Wikimedia numbered list. *)
				OR (ch = "*")  (* Wikimedia bullet list. *)
				OR (ch = ";")  (* Wikimedia definition list. *)
				THEN res := TRUE
			ELSIF isWikiChar() THEN inLeftMargin := FALSE; res := TRUE
			ELSE
				inLeftMargin := FALSE; res := FALSE
			END
		ELSE  (* ~inLeftMargin *)
			res := isWikiChar()
		END;
		RETURN res
	END  ChRefRequired;

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

PROCEDURE WriteCh();
BEGIN
	IF ch = 0DX THEN (* Begin a new line. *)
		L(); 
		inLeftMargin := TRUE;
		S(linePrefix)
	ELSE
		IF ChRefRequired() THEN
			WriteChRef()
		ELSE
			C(ch)
		END
	END
END WriteCh;

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

PROCEDURE MarkupInT();
VAR
BEGIN
	Texts.OpenWriter(mwWtr);
	IF inT = NIL THEN
		Out.String("MediaWiki.MarkupInT: inT = NIL.  No Text to convert."); Out.Ln()
	ELSIF inT.len > 0 THEN
		Texts.OpenReader(sourceRdr, inT, 0);
		REPEAT 
			Texts.Read(sourceRdr, ch);
			IF sourceRdr.eot THEN
				Out.String("MarkupInT(): sourceRdr at eot."); Out.Ln()
			END;
			IF sourceRdr.lib = NIL THEN
				Out.String("MarkupInT(): sourceRdr.lib = NIL at Texts.Pos = "); Out.Int(Texts.Pos(sourceRdr)-1, 3); Out.Ln()
			END
		UNTIL (sourceRdr.eot OR (sourceRdr.lib IS Fonts.Font));
		Out.String("MarkupInT: (sourceRdr.eot OR (sourceRdr.lib IS Fonts.Font))."); Out.Ln();
		IF 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."); Out.Ln();
			S(linePrefix); 
			inSpan := FALSE;
			BeginSpan(); (* Write global attributes according to first character. *)
			WriteCh();
			COPY(extantAttr.fntName, globalAttr.fntName);
			DecodeAttributes(globalAttr);
			Out.String("Attributes of first character recorded in globalAttr."); Out.Ln();
			WHILE Read() DO 
				IF (sourceRdr.lib = NIL) THEN 
					Out.String("MarkupInT: sourceRdr.lib = NIL at Texts.Pos = "); Out.Int(Texts.Pos(sourceRdr)-1, 3); Out.Ln()
				ELSIF (sourceRdr.lib IS Fonts.Font) THEN (* Got a character. *)
					IF ~ChFitsAttr(extantAttr) THEN (* Change of attributes. *)
						IF inSpan THEN EndSpan(); inSpan := FALSE END;
						COPY(sourceRdr.lib.name, extantAttr.fntName);
						DecodeAttributes(extantAttr);
						IF ~ChFitsAttr(globalAttr) THEN inSpan := TRUE; BeginSpan() END
					END;
					WriteCh()
				END
			END;  (* WHILE *)
			IF inSpan THEN EndSpan() END;
			EndSpan(); L(); (* Close global span. *)
			L(); 
			S("{{BookCat}}"); L() (* Wikibook requirement. *)
		END;
		Out.String("MarkupInT: ELSIF inT.len > 0 ... END"); Out.Ln()
		(* If inT is empty then mwWtr.buf is empty? *)
	END;
	Texts.Open(mwT, "");
	Out.String("MarkupInT(): completed Texts.Open(mwT, ..."); Out.Ln();
	Texts.Append(mwT, mwWtr.buf);
	Out.String("MediaWiki: END MarkupInT"); Out.Ln()
END MarkupInT;

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 MarkupInT() 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;
		MarkupInT();
		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 MarkupInT() 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 MarkupInT() complete."); Out.Ln();
		MarkupInT();
		Out.String("MarkupFile(): finished writing to 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 CreateNewName();
BEGIN
	COPY(name, newName);
	AddSuffix(name, MediaWikiSuffix, newName)
END CreateNewName;

PROCEDURE WriteK(VAR W: Texts.Writer;  k: LONGINT);
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: SIZE (* in A2 *) (* Integer in S3 *);
	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. *)
					CreateNewName();
					MarkupFile()
				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. *)
						CreateNewName();
						MarkupFile()
					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, LONGINT(free)); Texts.WriteString(Log, " of ");
		WriteK(Log, LONGINT(total)); Texts.WriteString(Log, " free (");
		WriteK(Log, LONGINT(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;
				AddSuffix(name, suffixArray, newName);
				MarkupViewer();
				Out.String("Diff.Do  "); (* Facilitate visual check of consistency beween original
					Text and Text derived from markup via HTML. *)
				IF inT # NIL THEN Out.String(newName) END;
				Out.String(" t.mw"); Out.Ln()
			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 arithmetic. *)
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 counts without arithmetic. *)
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.BuildOrdinals1: 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
		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  Oberon.MediaWiki.Mod ~  MediaWiki.Markup  t tt ~
System.DeleteFiles  Oberon.MediaWiki.Mod.mw ~


This article is issued from Wikibooks. The text is licensed under Creative Commons - Attribution - Sharealike. Additional terms may apply for the media files.