TweetFollow Us on Twitter

Text with Style
Volume Number:4
Issue Number:5
Column Tag:Forth Forum

Formatted Text with Style

By Jörg Langowski, MacTutor Editorial Board

TextEdit with Style(s)

TextEdit has always been one of the major conveniences of the Macintosh. Life (as far as programming is concerned) is so much simpler with a standard editing package that takes care of line break, word wrap, text insertion, justification etc. for you, instead of having to write it yourself.

One major reason why TextEdit was inadequate for e.g. word processing had always been that the text style was fixed for one text edit record, i.e. for one piece of edited text. Changing fonts, boldfacing, or changing the size of only one word or one phrase in the text was not possible.

The new implementation of TextEdit that is described in IM Vol.V finally introduces this possibility. TextEdit now recognizes two types of TE records: the old one, having the same text style all over the text, and a new format where style information is associated and displayed with the text. Although contained in IM V, the new TextEdit traps are available (System 4.2 and later) on the Mac Plus as well as on the SE and MacII.

A second inconvenience has been resolved: When working on new type TE records, TECopy and TEPaste now uses the desk scrap (i.e. the general clipboard) for cutting/pasting directly. It is no more necessary to convert between the internal TE scrap and the desk scrap on activate/deactivate events. For old TE records, TECopy and TEPaste still only use the internal scrap (for compatibility).

The new text edit is not yet used very widely, but it is worth it. Therefore I thought it might be a good idea to show its function on a practical example in Mach2 Forth. It is based on the ‘skeleton editor’ on the Mach2 demo disk, but contains a lot of enhancements, such as horizontal scrolling and scroll thumbs that work, and of course the text style support.

The new TE record

How does the system distinguish between the new and the old type TE record?

Mostly, the structure of the new record is the same as the old one, with a couple of exceptions: The txSize field of a new TE record contains -1 (word, offset $50 from beginning of record). In that case, the fields txFont and txFace (offset $4A and $4C) are combined to hold the handle of what is called a style record, a structure that contains the style information associated with the text. Of course, the information previously contained in the txFont, txFace and txSize fields - font, text face, and font size - is not meaningful anymore, since it may change over the length of the text.

Furthermore, the fields lineHeight and fontAscent (offset $18 and $1A) may now also contain -1, in which case the line height and ascent will be calculated individually for each line; if they contain positive numbers, the TErecord has fixed line height and ascent as before.

The style record

This structure contains the style information that belongs to the TErecord. Its layout is give in IM V-261 and I’ll repeat it here (Pascal style):

TYPE
TEStyleHandle = ^TEStylePtr;
TEStylePtr = ^TEStyleRec;
TEStyleRec = RECORD
 nRuns: INTEGER;
 nStyles: INTEGER;
 styleTab:STHandle;
 lhTab: LHHandle;
 teRefCon:LONGINT;
 nullStyle: nullSTHandle;
 runs:  ARRAY [0..0] OF StyleRun
 END;

StyleRun = RECORD
 startChar: INTEGER;
 styleIndex:INTEGER
 END;

The text is characterized by a succession of style runs, characters of the same style in the TE record. The system knows where they start (startChar) and the index styleIndex of the corresponding style in a style table. Each style record contains information about how many style runs and how many different styles there are in the text (nruns, nStyles), and handles to the style and line height tables (styleTab, lhTab). teRefCon can be used freely by the application, and nullStyle contains a handle to the style table that is used when the selection is empty.

The style table contains an entry for each different style encountered in the text:

TYPE
STHandle = ^STPtr;
StPtr = ^TEStyleTable;
TEStyleTable = ARRAY [0..0] OF STElement;

STElement = RECORD
 stCount: INTEGER;
 stHeight:INTEGER;
 stAscent:INTEGER;
 stFont:INTEGER;
 stFace:Style;
 stSize:INTEGER;
 stColor: RGBColor;
 END;

stCount indicates how often this style occurs in the text; the remaining fields indicate the text style.

Since the line height now may differ from line to line, there is another table, the line-height table, which contains an entry for each line in the lineStarts array of the TE record.

TYPE
LHHandle = ^LHPtr;
LHPtr = ^LHTable;
LHTable = ARRAY [0..0] OF LHElement;

LHElement = RECORD
 lhHeight:INTEGER;
 lhAscent:INTEGER;
 END;

For each line, lhHeight and lhAscent contain the maximum height and ascent present in that line.

Fortunately, you don’t have to remember any of this information when using the new Text Edit. For straightforward text editing, all we need to know is that the TECopy, TECut, TEKey and TEDelete routines work as before, but Copy and Cut store a second type of scrap, ‘styl’, in the desk scrap. When you do a TEPaste, this information is not used and only the text is pasted into the edit record using the style that was present at the insertion point. For pasting ‘with style’, a new routine exists, TEStylPaste. This is one of 10 routines that are called through the new trap TEDispatch. This trap will look at a selector (integer) on top of stack and call the new text edit routines accordingly.

Mach2 implements the new TE routines using their names and compiling the glue code for the dispatch routine automatically. One routine, TEStylInsert, has been left out accidentally, and is redefined in the example listing. Two more new traps exist: TEStylNew and TEGetOffset. Mach2 spells the former ‘TEStyleNew’, so watch out for that.

For simple use as in the example, the most important new routines that you have to remember are TEStylNew, TEStylPaste, TEGetOffset, TEGetStyle, and TESetStyle.

TEStylNew is just like TENew, except that it creates a new type TE record. TEStylPaste will use the ‘styl’ information in the scrap, if present, for the text to be pasted.

TEGetOffset works with both old and new type TE records and finds the character offset in the text corresponding to a certain point in the window (local coordinates). This is necessary for updating the font, size and style menu information after a change of the insertion point by a mouse click.

TEGetStyle and TESetStyleare used to get and set style information at the selection of insertion point in the text. They work with another data structure, the TextStyle:

TYPE TextStyle = RECORD
 tsFont:INTEGER;
 tsFace:Style;
 tsSize:INTEGER;
 tsColor: RGBColor
 END;

This record contains the text style information that is passed to/from the TE record.

All these routines are, of course, documented in IM Vol. V. Examples on how to call them can be found in the program listing. Feel free to experiment with the other new TE routines.

The example will create an editor window with vertical and horizontal scroll bars and read the first 1024 characters from a text file. You can use this text for playing around with different style settings (using the menus I provided). Doing this, you will notice that the Style menu doesn’t seem to have any effect on the text. Fonts and font sizes may be changed, but underlining, boldfacing etc. seems to be impossible. However, when you set those text attributes for a certain selection and then click at different positions in the text, you will see that the Style menu changes appropriately, checkmarks appear and disappear in the right positions. Therefore I believe that the style changes are well recorded in the style record/style table; only the text display doesn’t seem to function. Is this a bug still present in the new TextEdit, or have I overlooked something obvious (question to you, the readers)?

You see that editing multi-style text is not too difficult with the new TE routines, since they take care of almost everything. For saving and loading files, you would have to provide code that reads/writes the style record information together with the text, this also seems pretty straightforward. Printing a new style text edit record is a completely different ballgame, since no printing support exists (yet?) that is quite as extensive as the new TextEdit. You would have to extract the style information for each line, using the style record, style and line height tables, and write the printing code from scratch. More difficult, but probably a good ‘exercise for the reader’.

Bugs in the SCSI driver?

Some remarks have been received that the SCSI code published in V4#1/2 was buggy, and someone seems to have crashed his hard disk using it. I feel sorry if application of that example (which was however marked ‘experimental’) should have caused trouble to anyone. The only excuse I have is that it was said that the code had been shown to work only for two types of disk, the Q280 and the ST225N, the only ones available to me for testing at that time.

Let me point out here that we can only do our best to give examples of Macintosh programming, but never guarantee that everything works 100% and bug-free. Feel free to publish your comments, preferably with corrections, in MacTutor, that’s what we’re here for. But for any example that is printed here or published on the source code disks, be prepared that something might go wrong, and especially DON’T run it from the disk that has your only copy of that 40-page report on it that is due in two days! Play it safe and use floppies that have nothing valuable on them. I learned my lesson when I crashed my own hard disk while writing the Forth example for the February article.

I wish you good luck with this month’s example. The source code disk contains two compiled versions, one for Mac Plus/SE/II, and one for Mac II only (contains 68020 code). As far as I have checked them, they don’t crash and work under MultiFinder. But you never know...

Till next month, happy threading.

Listing 1: Text Edit Example with Style
\ New Text Edit example
\ J. Langowski for Mac Tutor March 1988
\ derived from
\ Editor Shell Example Program on Mach 2 demo disk

\ found two ‘features’ of the new text edit while 
\ experimenting:
\ a. when the insertion point is at a boundary between
\    two different styles, the text typed will be TEKeyed 
\    according to the style BEFORE the insertion point,
\    while TEGetStyle will return style information from 
\    AFTER the insertion point.
\ b. Although the text face seems to be set inside the style \    record 
and properly associated with the text 
\    (TEGetStyle returns the correct information after the 
\    text face has been changed), the text is always drawn 
\    plain text style. The font and size changes work OK.
\

only forth definitions
also assembler also mac

\ ***** constants

300 CONSTANT APPLEID 
310 CONSTANT FILEID
320 CONSTANT EDITID
330 CONSTANT SIZEID
340 CONSTANT FontID
350 CONSTANT StyleID

20  CONSTANT InUpArrow   
21  CONSTANT InDownArrow 
22  CONSTANT InPageUp 
23  CONSTANT InPageDown
129 CONSTANT InThumb

$44525652 Constant “drvr
$464F4E54 Constant “font

%000001000000000 CONSTANT ShiftMask 
    
$10 CONSTANTportRect \ Grafport rectangle
$6E CONSTANTwVisible \ visible flag [byte]

\ text edit equates
0  CONSTANT teDestRect  
8  CONSTANT teViewRect  
$C  CONSTANTselRect
$18 CONSTANT   teLineHite 
$1A CONSTANTteFontAscent
$1C CONSTANTteSelPoint  
$20 CONSTANT   teSelStart 
$22 CONSTANT   teSelEnd
$38 CONSTANT   teCarOn  
$39 CONSTANT   teCarAct
$3C CONSTANTteLength
$3E CONSTANTteTextH
$48 CONSTANTteCROnly
$4A CONSTANTteFont
$4C CONSTANTteFace
$4A CONSTANTteStylHandle  
 \ handle to style record for new
 \ text edit. Never accessed directly
$4E CONSTANTteMode \ text mode [word] 
$50 CONSTANT   teSize\ font size [word] 
 \ teFont, teFace, teMode, teSize are only 
 \ meaningful for old style TE records.
 \ for a new style record, teSize contains -1.
 \ in that case, teFont and teFace together contain
 \ the handle to the style record.
$5E CONSTANTteNLines
$60 CONSTANTteLines

$AB0 CONSTANT  TEScrpLength
$AB4 CONSTANT  TEScrpHandle

\ Event Record Equates
$0 CONSTANT What ( event code [word] )
$2 CONSTANT Message( event message [long] )  
$6 CONSTANT When ( ticks since start-up  [long] )
$A CONSTANT Where( mouse loc. pt. global [long] )
$E CONSTANT Modifiers( modifier flags  [word] )

$0A CONSTANT LF  ( ascii ‘linefeed’ )
$20 CONSTANT SP  ( ascii ‘space’ )

create applestring 01 C, $14 C, \ Apple symbol

\ ***** variables

VARIABLE TEHandle( handle for text edit record )
VARIABLE TERect   4 VALLOT
 ( Text Edit view rectangle )
VARIABLE SIZE    ( item# of current textsize )
VARIABLE DESKNAME 252 VALLOT\ holds name of desk accessory
VARIABLE FONTNAME 252 VALLOT\ holds font name selected
VARIABLE ITEMNAME 60 VALLOT 
 \ receives menu item name
VARIABLE MyStyle 8 VALLOT 
 \ text style record for our private use
 \ fields of MyStyle:
 0 CONSTANT tsFont
 2 CONSTANT tsFace
 4 CONSTANT tsSize
 6 CONSTANT RGBColor
VARIABLE currentFont \ menu ID of font in use
VARIABLE #fonts      \ # of currently installed fonts
VARIABLE currentSize  \ menu ID of size in use

76  USER AbortHook
152 USER ContentHook
160 USER GrowHook
164 USER CloseBoxHook
168 USER UpdateHook
172 USER ActivateHook
202 USER CAction \ control action routine vector

\ ***** glue routines for new text edit
\
\ TEStylNew ( destRect viewRect -- TEHandle )
\ is misspelled ‘TEStyleNew’ in the Mach2 trap definitions,
\ but implemented. So are TEGetOffset and most of the 
\ other new text edit routines that are called through 
\ TEDispatch.
\ One exception is TEStylInsert, which we are defining 
\ here:

CODE TEStylInsert ( text length hST hTE -- )
 EXG D4,A7
 MOVE.L $C(A6),-(A7) \ pointer to text
 MOVE.L $8(A6),-(A7) \ length of text
 MOVE.L $4(A6),-(A7) \ style record handle
 MOVE.L (A6),-(A7) \ TE record handle
 ADDA.W #$10,A6
 MOVE.W #$7,-(A7)
 _TEDispatch
 EXG  D4,A7
 RTS
END-CODE

\ ***** windows, menus, controls, tasks etc. *****

NEW.WINDOW Editor
“ Editor” Editor TITLE
42 4 330 507 Editor BOUNDS
DOCUMENT INVISIBLE CLOSEBOX GROWBOX 
 Editor ITEMS

200 1000 TERMINAL EditTask

NEW.MBAR EditBar 

NEW.MENU AppleMenu
APPLESTRING AppleMenu TITLE
0 APPLEID AppleMenu BOUNDS
“ About Editor ...;(-” AppleMenu ITEMS

NEW.MENU FileMenu
“ File” FileMenu TITLE
0 FileID FileMenu BOUNDS
“ New/N;Open.../O;Close;Save;Save as...;Revert to Original;(Print”
 FileMenu ITEMS

NEW.MENU EditMenu
“ Edit” EditMenu TITLE
0 EDITID EditMenu BOUNDS
“ (Undo/Z;(-;Cut/K;Copy/C;Paste/V;Clear” 
 EditMenu ITEMS

NEW.MENU FontMenu
“ Font” FontMenu TITLE
0 FontID FontMenu BOUNDS
“  (Fonts<I;(-” FontMenu ITEMS

NEW.MENU SizeMenu
“ Size” SizeMenu TITLE
0 SizeID SizeMenu BOUNDS
“  9 Point; 10 Point; 12 Point; 14 Point; 18 Point; 20 Point; 24 Point” 

 SizeMenu ITEMS

CREATE SizeIDTable
0 , 0 , 0 c, \ no menu IDs for sizes 0 thru 8
1 c, 2 c, 0 c, 3 c, \  9,10,--,12
0 c, 4 c, 0 c, 0 c, \ --,14,--,--
0 c, 5 c, 0 c, 6 c, \ --,18,--,20
0 c, 0 c, 0 c, 7 c, \ --,--,--,24

CREATE SizeTable
0 c, 9 c, 10 c, 12 c, 14 c, 18 c, 20 c, 24 c,


NEW.MENU StyleMenu
“ Style” StyleMenu TITLE
0 StyleID StyleMenu BOUNDS
“  Plain/P; Bold/B<B; Italic/I<I; Underline/U<U; Outline<O; Shadow<S; 
Condense; Extend” 
 StyleMenu ITEMS

NEW.CONTROL Scroll
VSCROLLBAR VISIBLE 100 0 Scroll ITEMS
VARIABLE lastVs
400 CONSTANT maxVs

NEW.CONTROL hScroll
HSCROLLBAR VISIBLE 100 0 hScroll ITEMS
VARIABLE lastHs
100 CONSTANT maxHs

: CHECK  ( menuhandle item# flag -- )( checking a menu item )
 CALL CheckItem ;
 
: =string { aStr bStr | -- flag }
 aStr count 65536 * bStr count rot + swap
 call CmpString 0=
;

CODE @TEHandle
 MOVE.L TEHandle,-(A6)    RTS
END-CODE

: Shift?   (   -  f )   \ checks the event record to see if the
 \ shift key was pressed. 
 EVENT-RECORD Modifiers + W@ ShiftMask AND
 IF -1 ELSE 0 THEN  
;
 

: adjustFontMenu
\ adjust font menu and currentFont variable
 myStyle w@ ( font ID ) fontName call getFname
 #fonts @ 0 DO
 fontMenu @ i itemName call GetItem
 itemName fontName =string 
 IF  FontMenu @ currentFont @ 0 check 
 \ uncheck previous font selection 
     FontMenu @ i -1 check
     i currentFont !
     leave
 THEN
 LOOP
;

: adjustStyleMenu { | face - }
 myStyle tsFace + w@ -> face
 8 0 DO 
   1 i scale face and ( get style bit )
   if -1 else 0 then
   styleMenu @ i 2+ rot check 
 LOOP 
;
 
: adjustSizeMenu
 SizeMenu @ currentSize @ 0 check 
 myStyle tsSize + w@ ( size )
 SizeIDTable + c@ ( sizeID )
 dup currentSize !
 SizeMenu @ swap -1 check 
;

: getCurrentStyle { | LHite FAsc -- }
 ( updates variable currentFont )
 ( size and Face kept in myStyle )
 ( LHite and FAsc are currently not used )

 @TEHandle @ teselStart + w@ 
 \ get start of selection (or insertion point)
 ( offset ) myStyle ^ LHite ^ FAsc @TEHandle
 call TEGetStyle
 
 adjustFontMenu
 adjustStyleMenu
 adjustSizeMenu
;

: AdjustTERect
 \ adjust terect size for the presence of scrollbars
 portRect Editor + 4 + W@ ( get bottom coord )
 16 -   ( subtract 16 for height of scrollbar )
 teViewRect @TEHandle @ + 4 + W! \ store new coord back in text edit 
record 
   
 portRect Editor + 6 + W@ ( get right coord )
 16 -   ( subtract 16 for width of scrollbar )
 teViewRect @TEHandle @ + 6 + W!
;
 
: Visible? (   -  f  ) \ checks visible flag in window record
 Editor wVisible + C@  
;

\ ***** event handlers *****

: ACTIVATE-HANDLER
 RUN-ACTIVATE
 EVENT-RECORD Modifiers + W@( get modifiers word )
 1 AND IF 
 @TEHandle CALL TEActivate
 getCurrentStyle
 ELSE   
 @TEHandle CALL TEDeactivate
 THEN 
;

 
: UPDATE-HANDLER
 Editor CALL SetPort
 AdjustTERect
 Editor CALL BeginUpdate
    Editor CALL DrawControls
    Editor CALL DrawGrowIcon
    Editor portRect + @TEHandle CALL TEUpdate
 Editor CALL EndUpdate
;

: CONTENT-HANDLER { | theMouse -- }
 RUN-CONTENT
 Editor CALL SetPort

 ^ theMouse CALL GetMouse
 theMouse @TEHandle @ TEViewRect + 
 call PtInRect
 IF
 theMouse Shift? @TEHandle CALL TEClick
 getCurrentStyle 
 THEN
;

: CLOSEBOX-HANDLER
 Editor \ windowpointer 
 EVENT-RECORD Where + @ call TrackGoAway     IF Editor CALL HideWindow 
THEN
;


\ **** main editor example code *****

: POP-UP
 Editor CALL ShowWindow
 Editor CALL SelectWindow
 EditBar @ CALL SetMenuBar
 CALL DrawMenuBar 
;
 
: ShutDown
 Editor CALL HideWindow
 PAUSE  ( PAUSE so that the i/o task can 
 have a turn and handle the
 deactivate event generated by
  the closing of the window )
 MACH.MBAR( MACH menubar back on screen )
 @TEHandle CALL TEDispose   
;

: SetScrollLimits
 Scroll @ 0 CALL SetMinCtl
 Scroll @ maxVs CALL SetMaxCtl   
 Scroll @ 0 CALL SetCtlValue 
 0 lastVs !  
 hScroll @ 0 CALL SetMinCtl
 hScroll @ maxHs CALL SetMaxCtl   
 hScroll @ 0 CALL SetCtlValue 
 0 lastHs !  
;


: EditFile   {   | char exitflag --   }
 BEGIN
     Visible?
     IF
      ?TERMINAL IF
 KEY -> char( get the character )
      char 14 = IF
        0 -> exitflag ( if cmd ‘.’ exit )
 ELSE
 char @TEHandle CALL TEKey
 ( else insert )
 1 -> exitflag   ( char )
 THEN
 ELSE
        1 -> exitflag
 ( if no key pressed, keep looping )
      THEN
 
     ELSE
      0 -> exitflag
 ( if window’s been closed, exit )
     THEN
 exitflag ( check exit condition )
 WHILE
     @TEHandle CALL TEIdle
 REPEAT
;
 
 
: Open 
 Pop-Up
 Editor CALL SetPort
    
 TERect TERect CALL TEStyleNew TEHandle ! 
 \ get new style TE record 
 -1 teCROnly @TEHANDLE @ + W! ( no word wrap )
 -1 teCarAct @TEHandle @ + C! ( activate caret )
 -1 @TEHandle call TEAutoView
 \ enable auto scroll

 ( get the first 1K of text )
 0 VIRTUAL 1024 0 @TEHandle TEStylinsert
 0 0 @TEHandle CALL TESetSelect
 15 ( doAll ) myStyle -1 ( redraw) @TEHandle
 call TESetStyle 
 adjustFontMenu
 adjustStyleMenu
 adjustSizeMenu
    
 AdjustTERect  ( initialize the text )
 PortRect Editor + @TEHandle CALL TEUpdate 
 @TEHandle CALL TEDeactivate
 @TEHandle CALL TEActivate

 SetScrollLimits
 Editor CALL DrawControls Editor CALL DrawGrowIcon

 [‘] UPDATE-HANDLER UpdateHook !
 [‘] CONTENT-HANDLER ContentHook !
 [‘] ACTIVATE-HANDLER ActivateHook !    
 [‘] CLOSEBOX-HANDLER CloseBoxHook !  
;
    
 
\ ***** menu handlers *****

: HandleDeskAcc ( item# -  )
 APPLEMENU @ SWAP DESKNAME CALL GETITEM
 DESKNAME CALL OPENDESKACC
 DROP 
;

: DO-APPLE ( item# -  )
 dup 1 = IF
     ( AboutEdit ) ( About Editor ... )
     drop
 ELSE  HandleDeskAcc
 THEN 
;

: NewFile ;
: OpenFile ;
: CloseFile ;
: SaveFile ;
: SaveAs ;
: Revert ;

: DO-FILE ( item# -  )
 CASE
 1 OF NewFile    ENDOF
 2 OF   OpenFile ENDOF
 3 OF   CloseFileENDOF
 4 OF SaveFile   ENDOF
 5 OF SaveAsENDOF
 6 OF RevertENDOF
 ENDCASE 
;

: DO-EDIT ( item# - )
 CASE
 1 OF   ( TEUndo )   ENDOF
 3 OF   @TEHandle CALL TECut  ENDOF
 4 OF @TEHandle CALL TECopy ENDOF
 5 OF @TEHandle CALL TEStylPaste   ENDOF
 6 OF @TEHandle CALL TEDelete ENDOF
 ENDCASE  
;

: DO-Font { item# | fontID - }
 FontMenu @ item# Fontname call getitem
 Fontname ^ fontID call getFNum
 ^ fontID w@ myStyle w! 
 \ put into tsFont field of style record
 1 ( doFont) myStyle -1 ( redraw) @TEHandle
 call TESetStyle
 FontMenu @ currentFont @ 0 check 
 FontMenu @ item# -1 check
 item# currentFont !
;

: Do-Style { item# | facefield -- }
 myStyle tsFace + -> facefield
 item# CASE
 1 OF ( plain text ) 
   0 facefield w!
 ENDOF  

 facefield w@ 
 1 item# 2- scale xor 
 facefield w! \ flip bit
 ENDCASE

 2 ( doFace) myStyle -1 ( redraw) @TEHandle
 call TESetStyle
 adjustStyleMenu
;

 
: Do-Size  ( item# - ) 
 SizeTable + c@
 myStyle tsSize + w!
 4 ( doSize) myStyle -1 ( redraw) @TEHandle
 call TESetStyle
 adjustSizeMenu
;
 
: MBAR-HANDLER  ( item# menuID -  )
 CASE
 APPLEID OF DO-APPLE    ENDOF
 FILEID OF DO-FILE   ENDOF
 EDITID OF DO-EDIT ENDOF
 FontID OF DO-Font ENDOF
 SIZEID OF DO-Size ENDOF
 STYLEIDOF DO-StyleENDOF
 ENDCASE  
 0 CALL HILITEMENU  
;


\ ***** control action routines *****

\ A control action routine specifies what action should take 
\ place WHILE a control is being held down.

: ScrollText  { dv  dh  --   }
 dh dv @TEHandle CALL TEScroll   
;
 
: DO-Scroll { part-code  | ctlvalue  -  }
   part-code
   CASE
      inuparrow OF  Scroll @ CALL GetCtlValue  -> ctlvalue
        ctlvalue 0= NOT 
     IF
        Scroll @ ctlvalue 1- call SetCtlValue
 5 0  ScrollText
     THEN
 ENDOF
 
      indownarrow OF  Scroll @ call GetCtlValue  -> ctlvalue
 ctlvalue maxVs = NOT
     IF
 Scroll @ ctlvalue 1+ call SetCtlValue
 -5 0 ScrollText
     THEN
 ENDOF
 
      inpageup  OF  Scroll @ call GetCtlValue  -> ctlvalue
 ctlvalue 0= NOT 
     IF
 Scroll @ ctlvalue 5 - call SetCtlValue
 25 0  ScrollText
     THEN
 ENDOF
 
      inpagedown OF  Scroll @ call GetCtlValue   -> ctlvalue
 ctlvalue maxVs = NOT
      IF
        Scroll @ ctlvalue 5 + call SetCtlValue
 -25 0  ScrollText   
      THEN
 ENDOF
   ENDCASE  
   Scroll @ call GetCtlValue lastVs ! 
;

: DO-hScroll { part-code  | ctlvalue  -  }
   part-code
   CASE
      inuparrow OF hScroll @ call GetCtlValue  -> ctlvalue
        ctlvalue 0= NOT 
     IF
        hScroll @ ctlvalue 1- call SetCtlValue
 0 5 ScrollText
     THEN
 ENDOF
 
      indownarrow OF hScroll @ call GetCtlValue  -> ctlvalue
 ctlvalue maxHs = NOT
     IF
 hScroll @ ctlvalue 1+ call SetCtlValue
 0 -5 ScrollText
     THEN
 ENDOF
 
      inpageup  OF hScroll @ call GetCtlValue  -> ctlvalue
 ctlvalue 0= NOT 
     IF
 hScroll @ ctlvalue 5 - call SetCtlValue
 0 25 ScrollText
     THEN
 ENDOF
 
      inpagedown OF hScroll @ call GetCtlValue  -> ctlvalue
 ctlvalue maxHs = NOT
      IF
        hScroll @ ctlvalue 5 + call SetCtlValue
 0 -25 ScrollText   
      THEN
 ENDOF
   ENDCASE    
   hScroll @ call GetCtlValue lastHs ! 
;

: ControlAction  ( part-code  control-handle -  )
 CASE
  Scroll @ OF DO-Scroll   ENDOF
 hScroll @ OF DO-hScroll ENDOF
 swap drop
 ENDCASE
;


\ ***** scrollbar thumb control handler *****

: DO-vThumb { | ctlV }
 inThumb = IF
 scroll @ call getCtlValue -> ctlV
 lastVs @ ctlV - 5 * 0 scrollText
 ctlV lastVs !
 THEN
;

: DO-hThumb { | ctlV }
 inThumb = IF
 hscroll @ call getCtlValue -> ctlV
 0 lastHs @ ctlV - 5 * scrollText
 ctlV lastHs !
 THEN 
;
  
: ControlHandler  ( part-code  control-handle -  )
 CASE
  Scroll @ OF DO-vThumb   ENDOF
 hScroll @ OF DO-hThumb  ENDOF
 swap drop
 ENDCASE
;


\ ***** initialization *****

: INIT-MBAR
 EditBar ADD
 EditBar APPLEMENU ADD    
 APPLEMENU @ “drvr call addresmenu
 EditBar FileMenu  ADD
 EditBar EditMenu  ADD
 EditBar FontMenu  ADD  
 Fontmenu @ “font call addresmenu
 Fontmenu @ call countMItems #fonts !
 EditBar SizeMenu  ADD 
 EditBar StyleMenu ADD
;
 
: INIT-TASK
 Editor ADD ( make the Editor window )
 Editor Scroll ADD ( add vertical scroll bar )
 Editor hScroll ADD( add horizontal scroll bar )
 Editor EditTask BUILD 
;
 
: START-TASK
 ACTIVATE 
 [‘] ControlAction CAction !
 [‘] ControlHandler Control-Vector !
 [‘] MBAR-HANDLER MENU-VECTOR !  
 BEGIN
     STANDARD-GETFILE
     IF
 Open
 EditFile
 ShutDown
     THEN
     [‘] RUN-UPDATE UpdateHook !
     [‘] RUN-CONTENT ContentHook !
     [‘] RUN-ACTIVATE ActivateHook !
     [‘] RUN-CLOSEBOX CloseBoxHook !
     SLEEP STATUS W! ( put Editor task to sleep )
     PAUSE( exit this task )
 AGAIN 
;

: INIT-EDIT
 INIT-TASK
 INIT-MBAR
 EditBar EditTask MBAR>TASK 4 myStyle w!     \ default font, Monaco
 0 myStyle 2+ w! \ default face, plain text
 9 myStyle 4 + w! \ default size, 9 point
 0 myStyle 6 + ! \ RGBcolor = ...
 0 myStyle 10 + w! \ ...black 
 4   TERect     W! ( define the text edit rectangle )
 4   TERect 2+  W!
 288 TERect 4 + W!
 503 TERect 6 + W!
 EditTask START-TASK  
;


: EDIT  ( wakes up Editor task )
 EDITTASK @ 
 IFWAKE STATUS TASK-> EditTask W!
 ELSE INIT-EDIT
 THEN
;
 

Community Search:
MacTech Search:

Software Updates via MacUpdate

Posterino 4.4 - Create posters, collages...
Posterino offers enhanced customization and flexibility including a variety of new, stylish templates featuring grids of identical or odd-sized image boxes. You can customize the size and shape of... Read more
Chromium 119.0.6044.0 - Fast and stable...
Chromium is an open-source browser project that aims to build a safer, faster, and more stable way for all Internet users to experience the web. List of changes available here. Version for Apple... Read more
Spotify 1.2.21.1104 - Stream music, crea...
Spotify is a streaming music service that gives you on-demand access to millions of songs. Whether you like driving rock, silky R&B, or grandiose classical music, Spotify's massive catalogue puts... Read more
Tor Browser 12.5.5 - Anonymize Web brows...
Using Tor Browser you can protect yourself against tracking, surveillance, and censorship. Tor was originally designed, implemented, and deployed as a third-generation onion-routing project of the U.... Read more
Malwarebytes 4.21.9.5141 - Adware remova...
Malwarebytes (was AdwareMedic) helps you get your Mac experience back. Malwarebytes scans for and removes code that degrades system performance or attacks your system. Making your Mac once again your... Read more
TinkerTool 9.5 - Expanded preference set...
TinkerTool is an application that gives you access to additional preference settings Apple has built into Mac OS X. This allows to activate hidden features in the operating system and in some of the... Read more
Paragon NTFS 15.11.839 - Provides full r...
Paragon NTFS breaks down the barriers between Windows and macOS. Paragon NTFS effectively solves the communication problems between the Mac system and NTFS. Write, edit, copy, move, delete files on... Read more
Apple Safari 17 - Apple's Web brows...
Apple Safari is Apple's web browser that comes bundled with the most recent macOS. Safari is faster and more energy efficient than other browsers, so sites are more responsive and your notebook... Read more
Firefox 118.0 - Fast, safe Web browser.
Firefox offers a fast, safe Web browsing experience. Browse quickly, securely, and effortlessly. With its industry-leading features, Firefox is the choice of Web development professionals and casual... Read more
ClamXAV 3.6.1 - Virus checker based on C...
ClamXAV is a popular virus checker for OS X. Time to take control ClamXAV keeps threats at bay and puts you firmly in charge of your Mac’s security. Scan a specific file or your entire hard drive.... Read more

Latest Forum Discussions

See All

‘Monster Hunter Now’ October Events Incl...
Niantic and Capcom have just announced this month’s plans for the real world hunting action RPG Monster Hunter Now (Free) for iOS and Android. If you’ve not played it yet, read my launch week review of it here. | Read more »
Listener Emails and the iPhone 15! – The...
In this week’s episode of The TouchArcade Show we finally get to a backlog of emails that have been hanging out in our inbox for, oh, about a month or so. We love getting emails as they always lead to interesting discussion about a variety of topics... | Read more »
TouchArcade Game of the Week: ‘Cypher 00...
This doesn’t happen too often, but occasionally there will be an Apple Arcade game that I adore so much I just have to pick it as the Game of the Week. Well, here we are, and Cypher 007 is one of those games. The big key point here is that Cypher... | Read more »
SwitchArcade Round-Up: ‘EA Sports FC 24’...
Hello gentle readers, and welcome to the SwitchArcade Round-Up for September 29th, 2023. In today’s article, we’ve got a ton of news to go over. Just a lot going on today, I suppose. After that, there are quite a few new releases to look at... | Read more »
‘Storyteller’ Mobile Review – Perfect fo...
I first played Daniel Benmergui’s Storyteller (Free) through its Nintendo Switch and Steam releases. Read my original review of it here. Since then, a lot of friends who played the game enjoyed it, but thought it was overpriced given the short... | Read more »
An Interview with the Legendary Yu Suzuk...
One of the cool things about my job is that every once in a while, I get to talk to the people behind the games. It’s always a pleasure. Well, today we have a really special one for you, dear friends. Mr. Yu Suzuki of Ys Net, the force behind such... | Read more »
New ‘Marvel Snap’ Update Has Balance Adj...
As we wait for the information on the new season to drop, we shall have to content ourselves with looking at the latest update to Marvel Snap (Free). It’s just a balance update, but it makes some very big changes that combined with the arrival of... | Read more »
‘Honkai Star Rail’ Version 1.4 Update Re...
At Sony’s recently-aired presentation, HoYoverse announced the Honkai Star Rail (Free) PS5 release date. Most people speculated that the next major update would arrive alongside the PS5 release. | Read more »
‘Omniheroes’ Major Update “Tide’s Cadenc...
What secrets do the depths of the sea hold? Omniheroes is revealing the mysteries of the deep with its latest “Tide’s Cadence" update, where you can look forward to scoring a free Valkyrie and limited skin among other login rewards like the 2nd... | Read more »
Recruit yourself some run-and-gun royalt...
It is always nice to see the return of a series that has lost a bit of its global staying power, and thanks to Lilith Games' latest collaboration, Warpath will be playing host the the run-and-gun legend that is Metal Slug 3. [Read more] | Read more »

Price Scanner via MacPrices.net

Clearance M1 Max Mac Studio available today a...
Apple has clearance M1 Max Mac Studios available in their Certified Refurbished store for $270 off original MSRP. Each Mac Studio comes with Apple’s one-year warranty, and shipping is free: – Mac... Read more
Apple continues to offer 24-inch iMacs for up...
Apple has a full range of 24-inch M1 iMacs available today in their Certified Refurbished store. Models are available starting at only $1099 and range up to $260 off original MSRP. Each iMac is in... Read more
Final weekend for Apple’s 2023 Back to School...
This is the final weekend for Apple’s Back to School Promotion 2023. It remains active until Monday, October 2nd. Education customers receive a free $150 Apple Gift Card with the purchase of a new... Read more
Apple drops prices on refurbished 13-inch M2...
Apple has dropped prices on standard-configuration 13″ M2 MacBook Pros, Certified Refurbished, to as low as $1099 and ranging up to $230 off MSRP. These are the cheapest 13″ M2 MacBook Pros for sale... Read more
14-inch M2 Max MacBook Pro on sale for $300 o...
B&H Photo has the Space Gray 14″ 30-Core GPU M2 Max MacBook Pro in stock and on sale today for $2799 including free 1-2 day shipping. Their price is $300 off Apple’s MSRP, and it’s the lowest... Read more
Apple is now selling Certified Refurbished M2...
Apple has added a full line of standard-configuration M2 Max and M2 Ultra Mac Studios available in their Certified Refurbished section starting at only $1699 and ranging up to $600 off MSRP. Each Mac... Read more
New sale: 13-inch M2 MacBook Airs starting at...
B&H Photo has 13″ MacBook Airs with M2 CPUs in stock today and on sale for $200 off Apple’s MSRP with prices available starting at only $899. Free 1-2 day delivery is available to most US... Read more
Apple has all 15-inch M2 MacBook Airs in stoc...
Apple has Certified Refurbished 15″ M2 MacBook Airs in stock today starting at only $1099 and ranging up to $230 off MSRP. These are the cheapest M2-powered 15″ MacBook Airs for sale today at Apple.... Read more
In stock: Clearance M1 Ultra Mac Studios for...
Apple has clearance M1 Ultra Mac Studios available in their Certified Refurbished store for $540 off original MSRP. Each Mac Studio comes with Apple’s one-year warranty, and shipping is free: – Mac... Read more
Back on sale: Apple’s M2 Mac minis for $100 o...
B&H Photo has Apple’s M2-powered Mac minis back in stock and on sale today for $100 off MSRP. Free 1-2 day shipping is available for most US addresses: – Mac mini M2/256GB SSD: $499, save $100 –... Read more

Jobs Board

Licensed Dental Hygienist - *Apple* River -...
Park Dental Apple River in Somerset, WI is seeking a compassionate, professional Dental Hygienist to join our team-oriented practice. COMPETITIVE PAY AND SIGN-ON Read more
Sublease Associate Optometrist- *Apple* Val...
Sublease Associate Optometrist- Apple Valley, CA- Target Optical Date: Sep 30, 2023 Brand: Target Optical Location: Apple Valley, CA, US, 92307 **Requisition Read more
*Apple* / Mac Administrator - JAMF - Amentum...
Amentum is seeking an ** Apple / Mac Administrator - JAMF** to provide support with the Apple Ecosystem to include hardware and software to join our team and Read more
Child Care Teacher - Glenda Drive/ *Apple* V...
Child Care Teacher - Glenda Drive/ Apple ValleyTeacher Share by Email Share on LinkedIn Share on Twitter Read more
Cashier - *Apple* Blossom Mall - JCPenney (...
Cashier - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Blossom Mall Read more
All contents are Copyright 1984-2011 by Xplain Corporation. All rights reserved. Theme designed by Icreon.