1281843Sdteske\ Copyright (c) 2003 Scott Long <scottl@FreeBSD.org>
2222417Sjulian\ Copyright (c) 2003 Aleksander Fafula <alex@fafula.com>
3281843Sdteske\ Copyright (c) 2006-2015 Devin Teske <dteske@FreeBSD.org>
4222417Sjulian\ All rights reserved.
5222417Sjulian\ 
6222417Sjulian\ Redistribution and use in source and binary forms, with or without
7222417Sjulian\ modification, are permitted provided that the following conditions
8222417Sjulian\ are met:
9222417Sjulian\ 1. Redistributions of source code must retain the above copyright
10222417Sjulian\    notice, this list of conditions and the following disclaimer.
11222417Sjulian\ 2. Redistributions in binary form must reproduce the above copyright
12222417Sjulian\    notice, this list of conditions and the following disclaimer in the
13222417Sjulian\    documentation and/or other materials provided with the distribution.
14222417Sjulian\ 
15222417Sjulian\ THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16222417Sjulian\ ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17222417Sjulian\ IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18222417Sjulian\ ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19222417Sjulian\ FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20222417Sjulian\ DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21222417Sjulian\ OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22222417Sjulian\ HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23222417Sjulian\ LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24222417Sjulian\ OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25222417Sjulian\ SUCH DAMAGE.
26222417Sjulian\ 
27222417Sjulian\ $FreeBSD: releng/10.3/sys/boot/forth/menu.4th 281843 2015-04-22 01:08:40Z dteske $
28222417Sjulian
29222417Sjulianmarker task-menu.4th
30222417Sjulian
31222417Sjulian\ Frame drawing
32222417Sjulianinclude /boot/frames.4th
33222417Sjulian
34281843Sdteskevocabulary menu-infrastructure
35281843Sdteskevocabulary menu-namespace
36281843Sdteskevocabulary menu-command-helpers
37281843Sdteske
38281843Sdteskeonly forth also menu-infrastructure definitions
39281843Sdteske
40222417Sjulianf_double        \ Set frames to double (see frames.4th). Replace with
41222417Sjulian                \ f_single if you want single frames.
42222417Sjulian46 constant dot \ ASCII definition of a period (in decimal)
43222417Sjulian
44254108Sdteske 5 constant menu_default_x         \ default column position of timeout
45254108Sdteske10 constant menu_default_y         \ default row position of timeout msg
46222417Sjulian 4 constant menu_timeout_default_x \ default column position of timeout
47222417Sjulian23 constant menu_timeout_default_y \ default row position of timeout msg
48222417Sjulian10 constant menu_timeout_default   \ default timeout (in seconds)
49222417Sjulian
50222417Sjulian\ Customize the following values with care
51222417Sjulian
52222417Sjulian  1 constant menu_start \ Numerical prefix of first menu item
53222417Sjuliandot constant bullet     \ Menu bullet (appears after numerical prefix)
54222417Sjulian  5 constant menu_x     \ Row position of the menu (from the top)
55222417Sjulian 10 constant menu_y     \ Column position of the menu (from left side)
56222417Sjulian
57222417Sjulian\ Menu Appearance
58222417Sjulianvariable menuidx   \ Menu item stack for number prefixes
59222417Sjulianvariable menurow   \ Menu item stack for positioning
60222417Sjulianvariable menubllt  \ Menu item bullet
61222417Sjulian
62222417Sjulian\ Menu Positioning
63222417Sjulianvariable menuX     \ Menu X offset (columns)
64222417Sjulianvariable menuY     \ Menu Y offset (rows)
65222417Sjulian
66281843Sdteske\ Menu-item elements
67281843Sdteskevariable menurebootadded
68281843Sdteske
69281843Sdteske\ Parsing of kernels into menu-items
70281843Sdteskevariable kernidx
71281843Sdteskevariable kernlen
72281843Sdteskevariable kernmenuidx
73281843Sdteske
74281843Sdteske\ Menu timer [count-down] variables
75281843Sdteskevariable menu_timeout_enabled \ timeout state (internal use only)
76281843Sdteskevariable menu_time            \ variable for tracking the passage of time
77281843Sdteskevariable menu_timeout         \ determined configurable delay duration
78281843Sdteskevariable menu_timeout_x       \ column position of timeout message
79281843Sdteskevariable menu_timeout_y       \ row position of timeout message
80281843Sdteske
81281843Sdteske\ Containers for parsing kernels into menu-items
82281843Sdteskecreate kerncapbuf 64 allot
83281843Sdteskecreate kerndefault 64 allot
84281843Sdteskecreate kernelsbuf 256 allot
85281843Sdteske
86281843Sdteskeonly forth also menu-namespace definitions
87281843Sdteske
88222417Sjulian\ Menu-item key association/detection
89222417Sjulianvariable menukey1
90222417Sjulianvariable menukey2
91222417Sjulianvariable menukey3
92222417Sjulianvariable menukey4
93222417Sjulianvariable menukey5
94222417Sjulianvariable menukey6
95222417Sjulianvariable menukey7
96222417Sjulianvariable menukey8
97222417Sjulianvariable menureboot
98222417Sjulianvariable menuacpi
99222417Sjulianvariable menuoptions
100262701Sdteskevariable menukernel
101222417Sjulian
102241523Sdteske\ Menu initialization status variables
103241523Sdteskevariable init_state1
104241523Sdteskevariable init_state2
105241523Sdteskevariable init_state3
106241523Sdteskevariable init_state4
107241523Sdteskevariable init_state5
108241523Sdteskevariable init_state6
109241523Sdteskevariable init_state7
110241523Sdteskevariable init_state8
111241523Sdteske
112222417Sjulian\ Boolean option status variables
113222417Sjulianvariable toggle_state1
114222417Sjulianvariable toggle_state2
115222417Sjulianvariable toggle_state3
116222417Sjulianvariable toggle_state4
117222417Sjulianvariable toggle_state5
118222417Sjulianvariable toggle_state6
119222417Sjulianvariable toggle_state7
120222417Sjulianvariable toggle_state8
121222417Sjulian
122222417Sjulian\ Array option status variables
123222417Sjulianvariable cycle_state1
124222417Sjulianvariable cycle_state2
125222417Sjulianvariable cycle_state3
126222417Sjulianvariable cycle_state4
127222417Sjulianvariable cycle_state5
128222417Sjulianvariable cycle_state6
129222417Sjulianvariable cycle_state7
130222417Sjulianvariable cycle_state8
131222417Sjulian
132222417Sjulian\ Containers for storing the initial caption text
133262701Sdteskecreate init_text1 64 allot
134262701Sdteskecreate init_text2 64 allot
135262701Sdteskecreate init_text3 64 allot
136262701Sdteskecreate init_text4 64 allot
137262701Sdteskecreate init_text5 64 allot
138262701Sdteskecreate init_text6 64 allot
139262701Sdteskecreate init_text7 64 allot
140262701Sdteskecreate init_text8 64 allot
141222417Sjulian
142281843Sdteskeonly forth definitions
143262701Sdteske
144281843Sdteske: arch-i386? ( -- BOOL ) \ Returns TRUE (-1) on i386, FALSE (0) otherwise.
145281843Sdteske	s" arch-i386" environment? dup if
146281843Sdteske		drop
147281843Sdteske	then
148281843Sdteske;
149281843Sdteske
150281843Sdteske: acpipresent? ( -- flag ) \ Returns TRUE if ACPI is present, FALSE otherwise
151281843Sdteske	s" hint.acpi.0.rsdp" getenv
152281843Sdteske	dup -1 = if
153281843Sdteske		drop false exit
154281843Sdteske	then
155281843Sdteske	2drop
156281843Sdteske	true
157281843Sdteske;
158281843Sdteske
159281843Sdteske: acpienabled? ( -- flag ) \ Returns TRUE if ACPI is enabled, FALSE otherwise
160281843Sdteske	s" hint.acpi.0.disabled" getenv
161281843Sdteske	dup -1 <> if
162281843Sdteske		s" 0" compare 0<> if
163281843Sdteske			false exit
164281843Sdteske		then
165281843Sdteske	else
166281843Sdteske		drop
167281843Sdteske	then
168281843Sdteske	true
169281843Sdteske;
170281843Sdteske
171243114Sdteske: +c! ( N C-ADDR/U K -- C-ADDR/U )
172243114Sdteske	3 pick 3 pick	( n c-addr/u k -- n c-addr/u k n c-addr )
173243114Sdteske	rot + c!	( n c-addr/u k n c-addr -- n c-addr/u )
174243114Sdteske	rot drop	( n c-addr/u -- c-addr/u )
175243114Sdteske;
176243114Sdteske
177281843Sdteskeonly forth also menu-namespace definitions
178262701Sdteske
179281843Sdteske\ Forth variables
180281843Sdteske: namespace     ( C-ADDR/U N -- ) also menu-namespace +c! evaluate previous ;
181281843Sdteske: menukeyN      ( N -- ADDR )   s" menukeyN"       7 namespace ;
182281843Sdteske: init_stateN   ( N -- ADDR )   s" init_stateN"   10 namespace ;
183281843Sdteske: toggle_stateN ( N -- ADDR )   s" toggle_stateN" 12 namespace ;
184281843Sdteske: cycle_stateN  ( N -- ADDR )   s" cycle_stateN"  11 namespace ;
185281843Sdteske: init_textN    ( N -- C-ADDR ) s" init_textN"     9 namespace ;
186243114Sdteske
187281843Sdteske\ Environment variables
188262701Sdteske: kernel[x]          ( N -- C-ADDR/U )   s" kernel[x]"           7 +c! ;
189262701Sdteske: menu_init[x]       ( N -- C-ADDR/U )   s" menu_init[x]"       10 +c! ;
190262701Sdteske: menu_command[x]    ( N -- C-ADDR/U )   s" menu_command[x]"    13 +c! ;
191262701Sdteske: menu_caption[x]    ( N -- C-ADDR/U )   s" menu_caption[x]"    13 +c! ;
192262701Sdteske: ansi_caption[x]    ( N -- C-ADDR/U )   s" ansi_caption[x]"    13 +c! ;
193262701Sdteske: menu_keycode[x]    ( N -- C-ADDR/U )   s" menu_keycode[x]"    13 +c! ;
194262701Sdteske: toggled_text[x]    ( N -- C-ADDR/U )   s" toggled_text[x]"    13 +c! ;
195262701Sdteske: toggled_ansi[x]    ( N -- C-ADDR/U )   s" toggled_ansi[x]"    13 +c! ;
196262701Sdteske: menu_caption[x][y] ( N M -- C-ADDR/U ) s" menu_caption[x][y]" 16 +c! 13 +c! ;
197262701Sdteske: ansi_caption[x][y] ( N M -- C-ADDR/U ) s" ansi_caption[x][y]" 16 +c! 13 +c! ;
198243114Sdteske
199281843Sdteskealso menu-infrastructure definitions
200222417Sjulian
201222417Sjulian\ This function prints a menu item at menuX (row) and menuY (column), returns
202222417Sjulian\ the incremental decimal ASCII value associated with the menu item, and
203222417Sjulian\ increments the cursor position to the next row for the creation of the next
204222417Sjulian\ menu item. This function is called by the menu-create function. You need not
205222417Sjulian\ call it directly.
206222417Sjulian\ 
207222417Sjulian: printmenuitem ( menu_item_str -- ascii_keycode )
208222417Sjulian
209281843Sdteske	loader_color? if [char] ^ escc! then
210281843Sdteske
211222417Sjulian	menurow dup @ 1+ swap ! ( increment menurow )
212222417Sjulian	menuidx dup @ 1+ swap ! ( increment menuidx )
213222417Sjulian
214222417Sjulian	\ Calculate the menuitem row position
215222417Sjulian	menurow @ menuY @ +
216222417Sjulian
217222417Sjulian	\ Position the cursor at the menuitem position
218222417Sjulian	dup menuX @ swap at-xy
219222417Sjulian
220222417Sjulian	\ Print the value of menuidx
221281843Sdteske	loader_color? dup ( -- bool bool )
222281843Sdteske	if b then
223222417Sjulian	menuidx @ .
224281843Sdteske	if me then
225222417Sjulian
226222417Sjulian	\ Move the cursor forward 1 column
227222417Sjulian	dup menuX @ 1+ swap at-xy
228222417Sjulian
229222417Sjulian	menubllt @ emit	\ Print the menu bullet using the emit function
230222417Sjulian
231222417Sjulian	\ Move the cursor to the 3rd column from the current position
232222417Sjulian	\ to allow for a space between the numerical prefix and the
233222417Sjulian	\ text caption
234222417Sjulian	menuX @ 3 + swap at-xy
235222417Sjulian
236222417Sjulian	\ Print the menu caption (we expect a string to be on the stack
237222417Sjulian	\ prior to invoking this function)
238222417Sjulian	type
239222417Sjulian
240222417Sjulian	\ Here we will add the ASCII decimal of the numerical prefix
241222417Sjulian	\ to the stack (decimal ASCII for `1' is 49) as a "return value"
242222417Sjulian	menuidx @ 48 +
243222417Sjulian;
244222417Sjulian
245222417Sjulian\ This function prints the appropriate menuitem basename to the stack if an
246222417Sjulian\ ACPI option is to be presented to the user, otherwise returns -1. Used
247222417Sjulian\ internally by menu-create, you need not (nor should you) call this directly.
248222417Sjulian\ 
249241310Sdteske: acpimenuitem ( -- C-Addr/U | -1 )
250222417Sjulian
251222417Sjulian	arch-i386? if
252222417Sjulian		acpipresent? if
253222417Sjulian			acpienabled? if
254222417Sjulian				loader_color? if
255262701Sdteske					s" toggled_ansi[x]"
256222417Sjulian				else
257262701Sdteske					s" toggled_text[x]"
258222417Sjulian				then
259222417Sjulian			else
260222417Sjulian				loader_color? if
261262701Sdteske					s" ansi_caption[x]"
262222417Sjulian				else
263262701Sdteske					s" menu_caption[x]"
264222417Sjulian				then
265222417Sjulian			then
266222417Sjulian		else
267222417Sjulian			menuidx dup @ 1+ swap ! ( increment menuidx )
268222417Sjulian			-1
269222417Sjulian		then
270222417Sjulian	else
271222417Sjulian		-1
272222417Sjulian	then
273222417Sjulian;
274222417Sjulian
275281843Sdteske: delim? ( C -- BOOL )
276281843Sdteske	dup  32 =		( c -- c bool )		\ [sp] space
277281843Sdteske	over  9 = or		( c bool -- c bool )	\ [ht] horizontal tab
278281843Sdteske	over 10 = or		( c bool -- c bool )	\ [nl] newline
279281843Sdteske	over 13 = or		( c bool -- c bool )	\ [cr] carriage return
280281843Sdteske	over [char] , =	or	( c bool -- c bool )	\ comma
281281843Sdteske	swap drop		( c bool -- bool )	\ return boolean
282281843Sdteske;
283281843Sdteske
284262701Sdteske\ This function parses $kernels into variables that are used by the menu to
285262701Sdteske\ display wich kernel to boot when the [overloaded] `boot' word is interpreted.
286262701Sdteske\ Used internally by menu-create, you need not (nor should you) call this
287262701Sdteske\ directly.
288262701Sdteske\ 
289262701Sdteske: parse-kernels ( N -- ) \ kernidx
290262701Sdteske	kernidx ! ( n -- )	\ store provided `x' value
291262701Sdteske	[char] 0 kernmenuidx !	\ initialize `y' value for menu_caption[x][y]
292262701Sdteske
293262701Sdteske	\ Attempt to get a list of kernels, fall back to sensible default
294262701Sdteske	s" kernels" getenv dup -1 = if
295262701Sdteske		drop ( cruft )
296262701Sdteske		s" kernel kernel.old"
297262701Sdteske	then ( -- c-addr/u )
298262701Sdteske
299262701Sdteske	\ Check to see if the user has altered $kernel by comparing it against
300262701Sdteske	\ $kernel[N] where N is kernel_state (the actively displayed kernel).
301262701Sdteske	s" kernel_state" evaluate @ 48 + s" kernel[N]" 7 +c! getenv
302262701Sdteske	dup -1 <> if
303262701Sdteske		s" kernel" getenv dup -1 = if
304262701Sdteske			drop ( cruft ) s" "
305262701Sdteske		then
306262701Sdteske		2swap 2over compare 0= if
307262701Sdteske			2drop FALSE ( skip below conditional )
308262701Sdteske		else \ User has changed $kernel
309262701Sdteske			TRUE ( slurp in new value )
310262701Sdteske		then
311262701Sdteske	else \ We haven't yet parsed $kernels into $kernel[N]
312262701Sdteske		drop ( getenv cruft )
313262701Sdteske		s" kernel" getenv dup -1 = if
314262701Sdteske			drop ( cruft ) s" "
315262701Sdteske		then
316262701Sdteske		TRUE ( slurp in initial value )
317262701Sdteske	then ( c-addr/u -- c-addr/u c-addr/u,-1 | 0 )
318262701Sdteske	if \ slurp new value into kerndefault
319262701Sdteske		kerndefault 1+ 0 2swap strcat swap 1- c!
320262701Sdteske	then
321262701Sdteske
322262701Sdteske	\ Clear out existing parsed-kernels
323262701Sdteske	kernidx @ [char] 0
324262701Sdteske	begin
325262701Sdteske		dup kernel[x] unsetenv
326262701Sdteske		2dup menu_caption[x][y] unsetenv
327262701Sdteske		2dup ansi_caption[x][y] unsetenv
328262701Sdteske		1+ dup [char] 8 >
329262701Sdteske	until
330262701Sdteske	2drop
331262701Sdteske
332262701Sdteske	\ Step through the string until we find the end
333262701Sdteske	begin
334262701Sdteske		0 kernlen ! \ initialize length of value
335262701Sdteske
336262701Sdteske		\ Skip leading whitespace and/or comma delimiters
337262701Sdteske		begin
338262701Sdteske			dup 0<> if
339262701Sdteske				over c@ delim? ( c-addr/u -- c-addr/u bool )
340262701Sdteske			else
341262701Sdteske				false ( c-addr/u -- c-addr/u bool )
342262701Sdteske			then
343262701Sdteske		while
344262701Sdteske			1- swap 1+ swap ( c-addr/u -- c-addr'/u' )
345262701Sdteske		repeat
346262701Sdteske		( c-addr/u -- c-addr'/u' )
347262701Sdteske
348262701Sdteske		dup 0= if \ end of string while eating whitespace
349262701Sdteske			2drop ( c-addr/u -- )
350262701Sdteske			kernmenuidx @ [char] 0 <> if \ found at least one
351262701Sdteske				exit \ all done
352262701Sdteske			then
353262701Sdteske
354262701Sdteske			\ No entries in $kernels; use $kernel instead
355262701Sdteske			s" kernel" getenv dup -1 = if
356262701Sdteske				drop ( cruft ) s" "
357262701Sdteske			then ( -- c-addr/u )
358262701Sdteske			dup kernlen ! \ store entire value length as kernlen
359262701Sdteske		else
360262701Sdteske			\ We're still within $kernels parsing toward the end;
361262701Sdteske			\ find delimiter/end to determine kernlen
362262701Sdteske			2dup ( c-addr/u -- c-addr/u c-addr/u )
363262701Sdteske			begin dup 0<> while
364262701Sdteske				over c@ delim? if
365262701Sdteske					drop 0 ( break ) \ found delimiter
366262701Sdteske				else
367262701Sdteske					kernlen @ 1+ kernlen ! \ incrememnt
368262701Sdteske					1- swap 1+ swap \ c-addr++ u--
369262701Sdteske				then
370262701Sdteske			repeat
371262701Sdteske			2drop ( c-addr/u c-addr'/u' -- c-addr/u )
372262701Sdteske
373262701Sdteske			\ If this is the first entry, compare it to $kernel
374262701Sdteske			\ If different, then insert $kernel beforehand
375262701Sdteske			kernmenuidx @ [char] 0 = if
376262701Sdteske				over kernlen @ kerndefault count compare if
377262701Sdteske					kernelsbuf 0 kerndefault count strcat
378262701Sdteske					s" ," strcat 2swap strcat
379262701Sdteske					kerndefault count swap drop kernlen !
380262701Sdteske				then
381262701Sdteske			then
382262701Sdteske		then
383262701Sdteske		( c-addr/u -- c-addr'/u' )
384262701Sdteske
385262701Sdteske		\ At this point, we should have something on the stack to store
386262701Sdteske		\ as the next kernel menu option; start assembling variables
387262701Sdteske
388262701Sdteske		over kernlen @ ( c-addr/u -- c-addr/u c-addr/u2 )
389262701Sdteske
390262701Sdteske		\ Assign first to kernel[x]
391262701Sdteske		2dup kernmenuidx @ kernel[x] setenv
392262701Sdteske
393262701Sdteske		\ Assign second to menu_caption[x][y]
394262701Sdteske		kerncapbuf 0 s" [K]ernel: " strcat
395262701Sdteske		2over strcat
396262701Sdteske		kernidx @ kernmenuidx @ menu_caption[x][y]
397262701Sdteske		setenv
398262701Sdteske
399262701Sdteske		\ Assign third to ansi_caption[x][y]
400281843Sdteske		kerncapbuf 0 s" @[1mK@[37mernel: " [char] @ escc! strcat
401262701Sdteske		kernmenuidx @ [char] 0 = if
402281843Sdteske			s" default/@[32m"
403262701Sdteske		else
404281843Sdteske			s" @[34;1m"
405281843Sdteske		then
406281843Sdteske		[char] @ escc! strcat
407262701Sdteske		2over strcat
408281843Sdteske		s" @[37m" [char] @ escc! strcat
409262701Sdteske		kernidx @ kernmenuidx @ ansi_caption[x][y]
410262701Sdteske		setenv
411262701Sdteske
412262701Sdteske		2drop ( c-addr/u c-addr/u2 -- c-addr/u )
413262701Sdteske
414262701Sdteske		kernmenuidx @ 1+ dup kernmenuidx ! [char] 8 > if
415262701Sdteske			2drop ( c-addr/u -- ) exit
416262701Sdteske		then
417262701Sdteske
418262701Sdteske		kernlen @ - swap kernlen @ + swap ( c-addr/u -- c-addr'/u' )
419262701Sdteske	again
420262701Sdteske;
421262701Sdteske
422262701Sdteske\ This function goes through the kernels that were discovered by the
423262701Sdteske\ parse-kernels function [above], adding " (# of #)" text to the end of each
424262701Sdteske\ caption.
425262701Sdteske\ 
426262701Sdteske: tag-kernels ( -- )
427262701Sdteske	kernidx @ ( -- x ) dup 0= if exit then
428262701Sdteske	[char] 0 s"  (Y of Z)" ( x -- x y c-addr/u )
429262701Sdteske	kernmenuidx @ -rot 7 +c! \ Replace 'Z' with number of kernels parsed
430262701Sdteske	begin
431262701Sdteske		2 pick 1+ -rot 2 +c! \ Replace 'Y' with current ASCII num
432262701Sdteske
433262701Sdteske		2over menu_caption[x][y] getenv dup -1 <> if
434262701Sdteske			2dup + 1- c@ [char] ) = if
435262701Sdteske				2drop \ Already tagged
436262701Sdteske			else
437262701Sdteske				kerncapbuf 0 2swap strcat
438262701Sdteske				2over strcat
439262701Sdteske				5 pick 5 pick menu_caption[x][y] setenv
440262701Sdteske			then
441262701Sdteske		else
442262701Sdteske			drop ( getenv cruft )
443262701Sdteske		then
444262701Sdteske
445262701Sdteske		2over ansi_caption[x][y] getenv dup -1 <> if
446262701Sdteske			2dup + 1- c@ [char] ) = if
447262701Sdteske				2drop \ Already tagged
448262701Sdteske			else
449262701Sdteske				kerncapbuf 0 2swap strcat
450262701Sdteske				2over strcat
451262701Sdteske				5 pick 5 pick ansi_caption[x][y] setenv
452262701Sdteske			then
453262701Sdteske		else
454262701Sdteske			drop ( getenv cruft )
455262701Sdteske		then
456262701Sdteske
457262701Sdteske		rot 1+ dup [char] 8 > if
458262701Sdteske			-rot 2drop TRUE ( break )
459262701Sdteske		else
460262701Sdteske			-rot FALSE
461262701Sdteske		then
462262701Sdteske	until
463262701Sdteske	2drop ( x y -- )
464262701Sdteske;
465262701Sdteske
466222417Sjulian\ This function creates the list of menu items. This function is called by the
467281843Sdteske\ menu-display function. You need not call it directly.
468222417Sjulian\ 
469222417Sjulian: menu-create ( -- )
470222417Sjulian
471222417Sjulian	\ Print the frame caption at (x,y)
472262701Sdteske	s" loader_menu_title" getenv dup -1 = if
473222417Sjulian		drop s" Welcome to FreeBSD"
474222417Sjulian	then
475254108Sdteske	TRUE ( use default alignment )
476262701Sdteske	s" loader_menu_title_align" getenv dup -1 <> if
477254108Sdteske		2dup s" left" compare-insensitive 0= if ( 1 )
478254108Sdteske			2drop ( c-addr/u ) drop ( bool )
479254108Sdteske			menuX @ menuY @ 1-
480254108Sdteske			FALSE ( don't use default alignment )
481254108Sdteske		else ( 1 ) 2dup s" right" compare-insensitive 0= if ( 2 )
482254108Sdteske			2drop ( c-addr/u ) drop ( bool )
483254108Sdteske			menuX @ 42 + 4 - over - menuY @ 1-
484254108Sdteske			FALSE ( don't use default alignment )
485254108Sdteske		else ( 2 ) 2drop ( c-addr/u ) then ( 1 ) then
486254108Sdteske	else
487254108Sdteske		drop ( getenv cruft )
488254108Sdteske	then
489254108Sdteske	if ( use default center alignement? )
490254108Sdteske		menuX @ 19 + over 2 / - menuY @ 1-
491254108Sdteske	then
492254108Sdteske	at-xy type 
493222417Sjulian
494241523Sdteske	\ If $menu_init is set, evaluate it (allowing for whole menus to be
495241523Sdteske	\ constructed dynamically -- as this function could conceivably set
496241523Sdteske	\ the remaining environment variables to construct the menu entirely).
497241523Sdteske	\ 
498262701Sdteske	s" menu_init" getenv dup -1 <> if
499241523Sdteske		evaluate
500241523Sdteske	else
501241523Sdteske		drop
502241523Sdteske	then
503241523Sdteske
504222417Sjulian	\ Print our menu options with respective key/variable associations.
505222417Sjulian	\ `printmenuitem' ends by adding the decimal ASCII value for the
506222417Sjulian	\ numerical prefix to the stack. We store the value left on the stack
507222417Sjulian	\ to the key binding variable for later testing against a character
508222417Sjulian	\ captured by the `getkey' function.
509222417Sjulian
510222417Sjulian	\ Note that any menu item beyond 9 will have a numerical prefix on the
511222417Sjulian	\ screen consisting of the first digit (ie. 1 for the tenth menu item)
512222417Sjulian	\ and the key required to activate that menu item will be the decimal
513222417Sjulian	\ ASCII of 48 plus the menu item (ie. 58 for the tenth item, aka. `:')
514222417Sjulian	\ which is misleading and not desirable.
515222417Sjulian	\ 
516222417Sjulian	\ Thus, we do not allow more than 8 configurable items on the menu
517222417Sjulian	\ (with "Reboot" as the optional ninth and highest numbered item).
518222417Sjulian
519222417Sjulian	\ 
520222417Sjulian	\ Initialize the ACPI option status.
521222417Sjulian	\ 
522222417Sjulian	0 menuacpi !
523262701Sdteske	s" menu_acpi" getenv -1 <> if
524222417Sjulian		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
525222417Sjulian			menuacpi !
526222417Sjulian			arch-i386? if acpipresent? if
527222417Sjulian				\ 
528222417Sjulian				\ Set menu toggle state to active state
529222417Sjulian				\ (required by generic toggle_menuitem)
530222417Sjulian				\ 
531243114Sdteske				acpienabled? menuacpi @ toggle_stateN !
532222417Sjulian			then then
533222417Sjulian		else
534222417Sjulian			drop
535222417Sjulian		then
536222417Sjulian	then
537222417Sjulian
538222417Sjulian	\ 
539262701Sdteske	\ Initialize kernel captions after parsing $kernels
540262701Sdteske	\ 
541262701Sdteske	0 menukernel !
542262701Sdteske	s" menu_kernel" getenv -1 <> if
543262701Sdteske		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
544262701Sdteske			dup menukernel !
545262701Sdteske			dup parse-kernels tag-kernels
546262701Sdteske
547262701Sdteske			\ Get the current cycle state (entry to use)
548262701Sdteske			s" kernel_state" evaluate @ 48 + ( n -- n y )
549262701Sdteske
550262701Sdteske			\ If state is invalid, reset
551262701Sdteske			dup kernmenuidx @ 1- > if
552262701Sdteske				drop [char] 0 ( n y -- n 48 )
553262701Sdteske				0 s" kernel_state" evaluate !
554262701Sdteske				over s" init_kernel" evaluate drop
555262701Sdteske			then
556262701Sdteske
557262701Sdteske			\ Set the current non-ANSI caption
558262701Sdteske			2dup swap dup ( n y -- n y y n n )
559262701Sdteske			s" set menu_caption[x]=$menu_caption[x][y]"
560262701Sdteske			17 +c! 34 +c! 37 +c! evaluate
561262701Sdteske			( n y y n n c-addr/u -- n y  )
562262701Sdteske
563262701Sdteske			\ Set the current ANSI caption
564262701Sdteske			2dup swap dup ( n y -- n y y n n )
565262701Sdteske			s" set ansi_caption[x]=$ansi_caption[x][y]"
566262701Sdteske			17 +c! 34 +c! 37 +c! evaluate
567262701Sdteske			( n y y n n c-addr/u -- n y )
568262701Sdteske
569262701Sdteske			\ Initialize cycle state from stored value
570262701Sdteske			48 - ( n y -- n k )
571262701Sdteske			s" init_cyclestate" evaluate ( n k -- n )
572262701Sdteske
573262701Sdteske			\ Set $kernel to $kernel[y]
574262701Sdteske			s" activate_kernel" evaluate ( n -- n )
575262701Sdteske		then
576262701Sdteske		drop
577262701Sdteske	then
578262701Sdteske
579262701Sdteske	\ 
580222417Sjulian	\ Initialize the menu_options visual separator.
581222417Sjulian	\ 
582222417Sjulian	0 menuoptions !
583262701Sdteske	s" menu_options" getenv -1 <> if
584222417Sjulian		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
585222417Sjulian			menuoptions !
586222417Sjulian		else
587222417Sjulian			drop
588222417Sjulian		then
589222417Sjulian	then
590222417Sjulian
591222417Sjulian	\ Initialize "Reboot" menu state variable (prevents double-entry)
592222417Sjulian	false menurebootadded !
593222417Sjulian
594242667Sdteske	menu_start
595242667Sdteske	1- menuidx !    \ Initialize the starting index for the menu
596242667Sdteske	0 menurow !     \ Initialize the starting position for the menu
597242667Sdteske
598222417Sjulian	49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
599222417Sjulian	begin
600222417Sjulian		\ If the "Options:" separator, print it.
601222417Sjulian		dup menuoptions @ = if
602222417Sjulian			\ Optionally add a reboot option to the menu
603262701Sdteske			s" menu_reboot" getenv -1 <> if
604222417Sjulian				drop
605222417Sjulian				s" Reboot" printmenuitem menureboot !
606222417Sjulian				true menurebootadded !
607222417Sjulian			then
608222417Sjulian
609222417Sjulian			menuX @
610222417Sjulian			menurow @ 2 + menurow !
611222417Sjulian			menurow @ menuY @ +
612222417Sjulian			at-xy
613262701Sdteske			s" menu_optionstext" getenv dup -1 <> if
614241363Sdteske				type
615241363Sdteske			else
616241363Sdteske				drop ." Options:"
617241363Sdteske			then
618222417Sjulian		then
619222417Sjulian
620222417Sjulian		\ If this is the ACPI menu option, act accordingly.
621222417Sjulian		dup menuacpi @ = if
622243114Sdteske			dup acpimenuitem ( n -- n n c-addr/u | n n -1 )
623243114Sdteske			dup -1 <> if
624243114Sdteske				13 +c! ( n n c-addr/u -- n c-addr/u )
625243114Sdteske				       \ replace 'x' with n
626243114Sdteske			else
627243114Sdteske				swap drop ( n n -1 -- n -1 )
628243114Sdteske				over menu_command[x] unsetenv
629243114Sdteske			then
630222417Sjulian		else
631241523Sdteske			\ make sure we have not already initialized this item
632243114Sdteske			dup init_stateN dup @ 0= if
633241523Sdteske				1 swap !
634241523Sdteske
635241523Sdteske				\ If this menuitem has an initializer, run it
636243114Sdteske				dup menu_init[x]
637241523Sdteske				getenv dup -1 <> if
638241523Sdteske					evaluate
639241523Sdteske				else
640241523Sdteske					drop
641241523Sdteske				then
642241523Sdteske			else
643241523Sdteske				drop
644241523Sdteske			then
645241523Sdteske
646243114Sdteske			dup
647222417Sjulian			loader_color? if
648243114Sdteske				ansi_caption[x]
649222417Sjulian			else
650243114Sdteske				menu_caption[x]
651222417Sjulian			then
652222417Sjulian		then
653222417Sjulian
654222417Sjulian		dup -1 <> if
655222417Sjulian			\ test for environment variable
656222417Sjulian			getenv dup -1 <> if
657243114Sdteske				printmenuitem ( c-addr/u -- n )
658243114Sdteske				dup menukeyN !
659222417Sjulian			else
660222417Sjulian				drop
661222417Sjulian			then
662222417Sjulian		else
663222417Sjulian			drop
664222417Sjulian		then
665222417Sjulian
666222417Sjulian		1+ dup 56 > \ add 1 to iterator, continue if less than 57
667222417Sjulian	until
668222417Sjulian	drop \ iterator
669222417Sjulian
670222417Sjulian	\ Optionally add a reboot option to the menu
671222417Sjulian	menurebootadded @ true <> if
672262701Sdteske		s" menu_reboot" getenv -1 <> if
673222417Sjulian			drop       \ no need for the value
674222417Sjulian			s" Reboot" \ menu caption (required by printmenuitem)
675222417Sjulian
676222417Sjulian			printmenuitem
677222417Sjulian			menureboot !
678222417Sjulian		else
679222417Sjulian			0 menureboot !
680222417Sjulian		then
681222417Sjulian	then
682222417Sjulian;
683222417Sjulian
684222417Sjulian\ Takes a single integer on the stack and updates the timeout display. The
685222417Sjulian\ integer must be between 0 and 9 (we will only update a single digit in the
686222417Sjulian\ source message).
687222417Sjulian\ 
688222417Sjulian: menu-timeout-update ( N -- )
689222417Sjulian
690243114Sdteske	\ Enforce minimum/maximum
691243114Sdteske	dup 9 > if drop 9 then
692243114Sdteske	dup 0 < if drop 0 then
693222417Sjulian
694243114Sdteske	s" Autoboot in N seconds. [Space] to pause" ( n -- n c-addr/u )
695222417Sjulian
696243114Sdteske	2 pick 0> if
697243114Sdteske		rot 48 + -rot ( n c-addr/u -- n' c-addr/u ) \ convert to ASCII
698243114Sdteske		12 +c!        ( n' c-addr/u -- c-addr/u )   \ replace 'N' above
699222417Sjulian
700243114Sdteske		menu_timeout_x @ menu_timeout_y @ at-xy \ position cursor
701243114Sdteske		type ( c-addr/u -- ) \ print message
702243114Sdteske	else
703243114Sdteske		menu_timeout_x @ menu_timeout_y @ at-xy \ position cursor
704243114Sdteske		spaces ( n c-addr/u -- n c-addr ) \ erase message
705243114Sdteske		2drop ( n c-addr -- )
706222417Sjulian	then
707222417Sjulian
708222417Sjulian	0 25 at-xy ( position cursor back at bottom-left )
709222417Sjulian;
710222417Sjulian
711222417Sjulian\ This function blocks program flow (loops forever) until a key is pressed.
712222417Sjulian\ The key that was pressed is added to the top of the stack in the form of its
713222417Sjulian\ decimal ASCII representation. This function is called by the menu-display
714222417Sjulian\ function. You need not call it directly.
715222417Sjulian\ 
716222417Sjulian: getkey ( -- ascii_keycode )
717222417Sjulian
718222417Sjulian	begin \ loop forever
719222417Sjulian
720222417Sjulian		menu_timeout_enabled @ 1 = if
721222417Sjulian			( -- )
722222417Sjulian			seconds ( get current time: -- N )
723222417Sjulian			dup menu_time @ <> if ( has time elapsed?: N N N -- N )
724222417Sjulian
725222417Sjulian				\ At least 1 second has elapsed since last loop
726222417Sjulian				\ so we will decrement our "timeout" (really a
727222417Sjulian				\ counter, insuring that we do not proceed too
728222417Sjulian				\ fast) and update our timeout display.
729222417Sjulian
730222417Sjulian				menu_time ! ( update time record: N -- )
731222417Sjulian				menu_timeout @ ( "time" remaining: -- N )
732222417Sjulian				dup 0> if ( greater than 0?: N N 0 -- N )
733222417Sjulian					1- ( decrement counter: N -- N )
734222417Sjulian					dup menu_timeout !
735222417Sjulian						( re-assign: N N Addr -- N )
736222417Sjulian				then
737222417Sjulian				( -- N )
738222417Sjulian
739222417Sjulian				dup 0= swap 0< or if ( N <= 0?: N N -- )
740222417Sjulian					\ halt the timer
741222417Sjulian					0 menu_timeout ! ( 0 Addr -- )
742222417Sjulian					0 menu_timeout_enabled ! ( 0 Addr -- )
743222417Sjulian				then
744222417Sjulian
745222417Sjulian				\ update the timer display ( N -- )
746222417Sjulian				menu_timeout @ menu-timeout-update
747222417Sjulian
748222417Sjulian				menu_timeout @ 0= if
749222417Sjulian					\ We've reached the end of the timeout
750222417Sjulian					\ (user did not cancel by pressing ANY
751222417Sjulian					\ key)
752222417Sjulian
753262701Sdteske					s" menu_timeout_command"  getenv dup
754222417Sjulian					-1 = if
755222417Sjulian						drop \ clean-up
756222417Sjulian					else
757222417Sjulian						evaluate
758222417Sjulian					then
759222417Sjulian				then
760222417Sjulian
761222417Sjulian			else ( -- N )
762222417Sjulian				\ No [detectable] time has elapsed (in seconds)
763222417Sjulian				drop ( N -- )
764222417Sjulian			then
765222417Sjulian			( -- )
766222417Sjulian		then
767222417Sjulian
768222417Sjulian		key? if \ Was a key pressed? (see loader(8))
769222417Sjulian
770222417Sjulian			\ An actual key was pressed (if the timeout is running,
771222417Sjulian			\ kill it regardless of which key was pressed)
772222417Sjulian			menu_timeout @ 0<> if
773222417Sjulian				0 menu_timeout !
774222417Sjulian				0 menu_timeout_enabled !
775222417Sjulian
776222417Sjulian				\ clear screen of timeout message
777222417Sjulian				0 menu-timeout-update
778222417Sjulian			then
779222417Sjulian
780222417Sjulian			\ get the key that was pressed and exit (if we
781222417Sjulian			\ get a non-zero ASCII code)
782222417Sjulian			key dup 0<> if
783222417Sjulian				exit
784222417Sjulian			else
785222417Sjulian				drop
786222417Sjulian			then
787222417Sjulian		then
788222417Sjulian		50 ms \ sleep for 50 milliseconds (see loader(8))
789222417Sjulian
790222417Sjulian	again
791222417Sjulian;
792222417Sjulian
793222417Sjulian: menu-erase ( -- ) \ Erases menu and resets positioning variable to positon 1.
794222417Sjulian
795222417Sjulian	\ Clear the screen area associated with the interactive menu
796222417Sjulian	menuX @ menuY @
797222417Sjulian	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
798222417Sjulian	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
799222417Sjulian	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
800222417Sjulian	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
801222417Sjulian	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
802222417Sjulian	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces
803222417Sjulian	2drop
804222417Sjulian
805222417Sjulian	\ Reset the starting index and position for the menu
806222417Sjulian	menu_start 1- menuidx !
807222417Sjulian	0 menurow !
808222417Sjulian;
809222417Sjulian
810281843Sdteskeonly forth
811281843Sdteskealso menu-infrastructure
812281843Sdteskealso menu-namespace
813281843Sdteskealso menu-command-helpers definitions
814281843Sdteske
815281843Sdteske: toggle_menuitem ( N -- N ) \ toggles caption text and internal menuitem state
816281843Sdteske
817281843Sdteske	\ ASCII numeral equal to user-selected menu item must be on the stack.
818281843Sdteske	\ We do not modify the stack, so the ASCII numeral is left on top.
819281843Sdteske
820281843Sdteske	dup init_textN c@ 0= if
821281843Sdteske		\ NOTE: no need to check toggle_stateN since the first time we
822281843Sdteske		\ are called, we will populate init_textN. Further, we don't
823281843Sdteske		\ need to test whether menu_caption[x] (ansi_caption[x] when
824281843Sdteske		\ loader_color?=1) is available since we would not have been
825281843Sdteske		\ called if the caption was NULL.
826281843Sdteske
827281843Sdteske		\ base name of environment variable
828281843Sdteske		dup ( n -- n n ) \ key pressed
829281843Sdteske		loader_color? if
830281843Sdteske			ansi_caption[x]
831281843Sdteske		else
832281843Sdteske			menu_caption[x]
833281843Sdteske		then	
834281843Sdteske		getenv dup -1 <> if
835281843Sdteske
836281843Sdteske			2 pick ( n c-addr/u -- n c-addr/u n )
837281843Sdteske			init_textN ( n c-addr/u n -- n c-addr/u c-addr )
838281843Sdteske
839281843Sdteske			\ now we have the buffer c-addr on top
840281843Sdteske			\ ( followed by c-addr/u of current caption )
841281843Sdteske
842281843Sdteske			\ Copy the current caption into our buffer
843281843Sdteske			2dup c! -rot \ store strlen at first byte
844281843Sdteske			begin
845281843Sdteske				rot 1+    \ bring alt addr to top and increment
846281843Sdteske				-rot -rot \ bring buffer addr to top
847281843Sdteske				2dup c@ swap c! \ copy current character
848281843Sdteske				1+     \ increment buffer addr
849281843Sdteske				rot 1- \ bring buffer len to top and decrement
850281843Sdteske				dup 0= \ exit loop if buffer len is zero
851281843Sdteske			until
852281843Sdteske			2drop \ buffer len/addr
853281843Sdteske			drop  \ alt addr
854281843Sdteske
855281843Sdteske		else
856281843Sdteske			drop
857281843Sdteske		then
858281843Sdteske	then
859281843Sdteske
860281843Sdteske	\ Now we are certain to have init_textN populated with the initial
861281843Sdteske	\ value of menu_caption[x] (ansi_caption[x] with loader_color enabled).
862281843Sdteske	\ We can now use init_textN as the untoggled caption and
863281843Sdteske	\ toggled_text[x] (toggled_ansi[x] with loader_color enabled) as the
864281843Sdteske	\ toggled caption and store the appropriate value into menu_caption[x]
865281843Sdteske	\ (again, ansi_caption[x] with loader_color enabled). Last, we'll
866281843Sdteske	\ negate the toggled state so that we reverse the flow on subsequent
867281843Sdteske	\ calls.
868281843Sdteske
869281843Sdteske	dup toggle_stateN @ 0= if
870281843Sdteske		\ state is OFF, toggle to ON
871281843Sdteske
872281843Sdteske		dup ( n -- n n ) \ key pressed
873281843Sdteske		loader_color? if
874281843Sdteske			toggled_ansi[x]
875281843Sdteske		else
876281843Sdteske			toggled_text[x]
877281843Sdteske		then
878281843Sdteske		getenv dup -1 <> if
879281843Sdteske			\ Assign toggled text to menu caption
880281843Sdteske			2 pick ( n c-addr/u -- n c-addr/u n ) \ key pressed
881281843Sdteske			loader_color? if
882281843Sdteske				ansi_caption[x]
883281843Sdteske			else
884281843Sdteske				menu_caption[x]
885281843Sdteske			then
886281843Sdteske			setenv
887281843Sdteske		else
888281843Sdteske			\ No toggled text, keep the same caption
889281843Sdteske			drop ( n -1 -- n ) \ getenv cruft
890281843Sdteske		then
891281843Sdteske
892281843Sdteske		true \ new value of toggle state var (to be stored later)
893281843Sdteske	else
894281843Sdteske		\ state is ON, toggle to OFF
895281843Sdteske
896281843Sdteske		dup init_textN count ( n -- n c-addr/u )
897281843Sdteske
898281843Sdteske		\ Assign init_textN text to menu caption
899281843Sdteske		2 pick ( n c-addr/u -- n c-addr/u n ) \ key pressed
900281843Sdteske		loader_color? if
901281843Sdteske			ansi_caption[x]
902281843Sdteske		else
903281843Sdteske			menu_caption[x]
904281843Sdteske		then
905281843Sdteske		setenv
906281843Sdteske
907281843Sdteske		false \ new value of toggle state var (to be stored below)
908281843Sdteske	then
909281843Sdteske
910281843Sdteske	\ now we'll store the new toggle state (on top of stack)
911281843Sdteske	over toggle_stateN !
912281843Sdteske;
913281843Sdteske
914281843Sdteske: cycle_menuitem ( N -- N ) \ cycles through array of choices for a menuitem
915281843Sdteske
916281843Sdteske	\ ASCII numeral equal to user-selected menu item must be on the stack.
917281843Sdteske	\ We do not modify the stack, so the ASCII numeral is left on top.
918281843Sdteske
919281843Sdteske	dup cycle_stateN dup @ 1+ \ get value and increment
920281843Sdteske
921281843Sdteske	\ Before assigning the (incremented) value back to the pointer,
922281843Sdteske	\ let's test for the existence of this particular array element.
923281843Sdteske	\ If the element exists, we'll store index value and move on.
924281843Sdteske	\ Otherwise, we'll loop around to zero and store that.
925281843Sdteske
926281843Sdteske	dup 48 + ( n addr k -- n addr k k' )
927281843Sdteske	         \ duplicate array index and convert to ASCII numeral
928281843Sdteske
929281843Sdteske	3 pick swap ( n addr k k' -- n addr k n k' ) \ (n,k') as (x,y)
930281843Sdteske	loader_color? if
931281843Sdteske		ansi_caption[x][y]
932281843Sdteske	else
933281843Sdteske		menu_caption[x][y]
934281843Sdteske	then
935281843Sdteske	( n addr k n k' -- n addr k c-addr/u )
936281843Sdteske
937281843Sdteske	\ Now test for the existence of our incremented array index in the
938281843Sdteske	\ form of $menu_caption[x][y] ($ansi_caption[x][y] with loader_color
939281843Sdteske	\ enabled) as set in loader.rc(5), et. al.
940281843Sdteske
941281843Sdteske	getenv dup -1 = if
942281843Sdteske		\ No caption set for this array index. Loop back to zero.
943281843Sdteske
944281843Sdteske		drop ( n addr k -1 -- n addr k ) \ getenv cruft
945281843Sdteske		drop 0 ( n addr k -- n addr 0 )  \ new value to store later
946281843Sdteske
947281843Sdteske		2 pick [char] 0 ( n addr 0 -- n addr 0 n 48 ) \ (n,48) as (x,y)
948281843Sdteske		loader_color? if
949281843Sdteske			ansi_caption[x][y]
950281843Sdteske		else
951281843Sdteske			menu_caption[x][y]
952281843Sdteske		then
953281843Sdteske		( n addr 0 n 48 -- n addr 0 c-addr/u )
954281843Sdteske		getenv dup -1 = if
955281843Sdteske			\ Highly unlikely to occur, but to ensure things move
956281843Sdteske			\ along smoothly, allocate a temporary NULL string
957281843Sdteske			drop ( cruft ) s" "
958281843Sdteske		then
959281843Sdteske	then
960281843Sdteske
961281843Sdteske	\ At this point, we should have the following on the stack (in order,
962281843Sdteske	\ from bottom to top):
963281843Sdteske	\ 
964281843Sdteske	\    n        - Ascii numeral representing the menu choice (inherited)
965281843Sdteske	\    addr     - address of our internal cycle_stateN variable
966281843Sdteske	\    k        - zero-based number we intend to store to the above
967281843Sdteske	\    c-addr/u - string value we intend to store to menu_caption[x]
968281843Sdteske	\               (or ansi_caption[x] with loader_color enabled)
969281843Sdteske	\ 
970281843Sdteske	\ Let's perform what we need to with the above.
971281843Sdteske
972281843Sdteske	\ Assign array value text to menu caption
973281843Sdteske	4 pick ( n addr k c-addr/u -- n addr k c-addr/u n )
974281843Sdteske	loader_color? if
975281843Sdteske		ansi_caption[x]
976281843Sdteske	else
977281843Sdteske		menu_caption[x]
978281843Sdteske	then
979281843Sdteske	setenv
980281843Sdteske
981281843Sdteske	swap ! ( n addr k -- n ) \ update array state variable
982281843Sdteske;
983281843Sdteske
984281843Sdteskeonly forth definitions also menu-infrastructure
985281843Sdteske
986222417Sjulian\ Erase and redraw the menu. Useful if you change a caption and want to
987222417Sjulian\ update the menu to reflect the new value.
988222417Sjulian\ 
989222417Sjulian: menu-redraw ( -- )
990222417Sjulian	menu-erase
991222417Sjulian	menu-create
992222417Sjulian;
993222417Sjulian
994222417Sjulian\ This function initializes the menu. Call this from your `loader.rc' file
995222417Sjulian\ before calling any other menu-related functions.
996222417Sjulian\ 
997222417Sjulian: menu-init ( -- )
998222417Sjulian	menu_start
999222417Sjulian	1- menuidx !    \ Initialize the starting index for the menu
1000222417Sjulian	0 menurow !     \ Initialize the starting position for the menu
1001254108Sdteske
1002254108Sdteske	\ Assign configuration values
1003262701Sdteske	s" loader_menu_y" getenv dup -1 = if
1004254108Sdteske		drop \ no custom row position
1005254108Sdteske		menu_default_y
1006254108Sdteske	else
1007254108Sdteske		\ make sure custom position is a number
1008254108Sdteske		?number 0= if
1009254108Sdteske			menu_default_y \ or use default
1010254108Sdteske		then
1011254108Sdteske	then
1012254108Sdteske	menuY !
1013262701Sdteske	s" loader_menu_x" getenv dup -1 = if
1014254108Sdteske		drop \ no custom column position
1015254108Sdteske		menu_default_x
1016254108Sdteske	else
1017254108Sdteske		\ make sure custom position is a number
1018254108Sdteske		?number 0= if
1019254108Sdteske			menu_default_x \ or use default
1020254108Sdteske		then
1021254108Sdteske	then
1022254108Sdteske	menuX !
1023254108Sdteske
1024254108Sdteske	\ Interpret a custom frame type for the menu
1025254108Sdteske	TRUE ( draw a box? default yes, but might be altered below )
1026262701Sdteske	s" loader_menu_frame" getenv dup -1 = if ( 1 )
1027254108Sdteske		drop \ no custom frame type
1028254108Sdteske	else ( 1 )  2dup s" single" compare-insensitive 0= if ( 2 )
1029254108Sdteske		f_single ( see frames.4th )
1030254108Sdteske	else ( 2 )  2dup s" double" compare-insensitive 0= if ( 3 )
1031254108Sdteske		f_double ( see frames.4th )
1032254108Sdteske	else ( 3 ) s" none" compare-insensitive 0= if ( 4 )
1033254108Sdteske		drop FALSE \ don't draw a box
1034254108Sdteske	( 4 ) then ( 3 ) then ( 2 )  then ( 1 ) then
1035254108Sdteske	if
1036254108Sdteske		42 13 menuX @ 3 - menuY @ 1- box \ Draw frame (w,h,x,y)
1037254108Sdteske	then
1038254108Sdteske
1039254108Sdteske	0 25 at-xy \ Move cursor to the bottom for output
1040222417Sjulian;
1041222417Sjulian
1042281843Sdteskealso menu-namespace
1043281843Sdteske
1044222417Sjulian\ Main function. Call this from your `loader.rc' file.
1045222417Sjulian\ 
1046222417Sjulian: menu-display ( -- )
1047222417Sjulian
1048222417Sjulian	0 menu_timeout_enabled ! \ start with automatic timeout disabled
1049222417Sjulian
1050222417Sjulian	\ check indication that automatic execution after delay is requested
1051262701Sdteske	s" menu_timeout_command" getenv -1 <> if ( Addr C -1 -- | Addr )
1052222417Sjulian		drop ( just testing existence right now: Addr -- )
1053222417Sjulian
1054222417Sjulian		\ initialize state variables
1055222417Sjulian		seconds menu_time ! ( store the time we started )
1056222417Sjulian		1 menu_timeout_enabled ! ( enable automatic timeout )
1057222417Sjulian
1058222417Sjulian		\ read custom time-duration (if set)
1059222417Sjulian		s" autoboot_delay" getenv dup -1 = if
1060222417Sjulian			drop \ no custom duration (remove dup'd bunk -1)
1061222417Sjulian			menu_timeout_default \ use default setting
1062222417Sjulian		else
1063222417Sjulian			2dup ?number 0= if ( if not a number )
1064222417Sjulian				\ disable timeout if "NO", else use default
1065222417Sjulian				s" NO" compare-insensitive 0= if
1066222417Sjulian					0 menu_timeout_enabled !
1067222417Sjulian					0 ( assigned to menu_timeout below )
1068222417Sjulian				else
1069222417Sjulian					menu_timeout_default
1070222417Sjulian				then
1071222417Sjulian			else
1072222417Sjulian				-rot 2drop
1073222417Sjulian
1074225353Sjh				\ boot immediately if less than zero
1075222417Sjulian				dup 0< if
1076222417Sjulian					drop
1077225353Sjh					menu-create
1078225353Sjh					0 25 at-xy
1079225353Sjh					0 boot
1080222417Sjulian				then
1081222417Sjulian			then
1082222417Sjulian		then
1083222417Sjulian		menu_timeout ! ( store value on stack from above )
1084222417Sjulian
1085222417Sjulian		menu_timeout_enabled @ 1 = if
1086222417Sjulian			\ read custom column position (if set)
1087262701Sdteske			s" loader_menu_timeout_x" getenv dup -1 = if
1088222417Sjulian				drop \ no custom column position
1089222417Sjulian				menu_timeout_default_x \ use default setting
1090222417Sjulian			else
1091222417Sjulian				\ make sure custom position is a number
1092222417Sjulian				?number 0= if
1093222417Sjulian					menu_timeout_default_x \ or use default
1094222417Sjulian				then
1095222417Sjulian			then
1096222417Sjulian			menu_timeout_x ! ( store value on stack from above )
1097222417Sjulian        
1098222417Sjulian			\ read custom row position (if set)
1099262701Sdteske			s" loader_menu_timeout_y" getenv dup -1 = if
1100222417Sjulian				drop \ no custom row position
1101222417Sjulian				menu_timeout_default_y \ use default setting
1102222417Sjulian			else
1103222417Sjulian				\ make sure custom position is a number
1104222417Sjulian				?number 0= if
1105222417Sjulian					menu_timeout_default_y \ or use default
1106222417Sjulian				then
1107222417Sjulian			then
1108222417Sjulian			menu_timeout_y ! ( store value on stack from above )
1109222417Sjulian		then
1110222417Sjulian	then
1111222417Sjulian
1112222417Sjulian	menu-create
1113222417Sjulian
1114222417Sjulian	begin \ Loop forever
1115222417Sjulian
1116222417Sjulian		0 25 at-xy \ Move cursor to the bottom for output
1117222417Sjulian		getkey     \ Block here, waiting for a key to be pressed
1118222417Sjulian
1119222417Sjulian		dup -1 = if
1120222417Sjulian			drop exit \ Caught abort (abnormal return)
1121222417Sjulian		then
1122222417Sjulian
1123222417Sjulian		\ Boot if the user pressed Enter/Ctrl-M (13) or
1124222417Sjulian		\ Ctrl-Enter/Ctrl-J (10)
1125222417Sjulian		dup over 13 = swap 10 = or if
1126222417Sjulian			drop ( no longer needed )
1127222417Sjulian			s" boot" evaluate
1128222417Sjulian			exit ( pedantic; never reached )
1129222417Sjulian		then
1130222417Sjulian
1131242667Sdteske		dup menureboot @ = if 0 reboot then
1132242667Sdteske
1133222417Sjulian		\ Evaluate the decimal ASCII value against known menu item
1134222417Sjulian		\ key associations and act accordingly
1135222417Sjulian
1136222417Sjulian		49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
1137222417Sjulian		begin
1138243114Sdteske			dup menukeyN @
1139243114Sdteske			rot tuck = if
1140222417Sjulian
1141222417Sjulian				\ Adjust for missing ACPI menuitem on non-i386
1142222417Sjulian				arch-i386? true <> menuacpi @ 0<> and if
1143222417Sjulian					menuacpi @ over 2dup < -rot = or
1144222417Sjulian					over 58 < and if
1145222417Sjulian					( key >= menuacpi && key < 58: N -- N )
1146222417Sjulian						1+
1147222417Sjulian					then
1148222417Sjulian				then
1149222417Sjulian
1150222417Sjulian				\ Test for the environment variable
1151243114Sdteske				dup menu_command[x]
1152222417Sjulian				getenv dup -1 <> if
1153222417Sjulian					\ Execute the stored procedure
1154222417Sjulian					evaluate
1155222417Sjulian
1156222417Sjulian					\ We expect there to be a non-zero
1157222417Sjulian					\  value left on the stack after
1158222417Sjulian					\ executing the stored procedure.
1159222417Sjulian					\ If so, continue to run, else exit.
1160222417Sjulian
1161222417Sjulian					0= if
1162222417Sjulian						drop \ key pressed
1163222417Sjulian						drop \ loop iterator
1164222417Sjulian						exit
1165222417Sjulian					else
1166222417Sjulian						swap \ need iterator on top
1167222417Sjulian					then
1168222417Sjulian				then
1169222417Sjulian
1170222417Sjulian				\ Re-adjust for missing ACPI menuitem
1171222417Sjulian				arch-i386? true <> menuacpi @ 0<> and if
1172222417Sjulian					swap
1173222417Sjulian					menuacpi @ 1+ over 2dup < -rot = or
1174222417Sjulian					over 59 < and if
1175222417Sjulian						1-
1176222417Sjulian					then
1177222417Sjulian					swap
1178222417Sjulian				then
1179222417Sjulian			else
1180222417Sjulian				swap \ need iterator on top
1181222417Sjulian			then
1182222417Sjulian
1183222417Sjulian			\ 
1184222417Sjulian			\ Check for menu keycode shortcut(s)
1185222417Sjulian			\ 
1186243114Sdteske			dup menu_keycode[x]
1187222417Sjulian			getenv dup -1 = if
1188222417Sjulian				drop
1189222417Sjulian			else
1190222417Sjulian				?number 0<> if
1191222417Sjulian					rot tuck = if
1192222417Sjulian						swap
1193243114Sdteske						dup menu_command[x]
1194222417Sjulian						getenv dup -1 <> if
1195222417Sjulian							evaluate
1196222417Sjulian							0= if
1197222417Sjulian								2drop
1198222417Sjulian								exit
1199222417Sjulian							then
1200222417Sjulian						else
1201222417Sjulian							drop
1202222417Sjulian						then
1203222417Sjulian					else
1204222417Sjulian						swap
1205222417Sjulian					then
1206222417Sjulian				then
1207222417Sjulian			then
1208222417Sjulian
1209222417Sjulian			1+ dup 56 > \ increment iterator
1210222417Sjulian			            \ continue if less than 57
1211222417Sjulian		until
1212222417Sjulian		drop \ loop iterator
1213242667Sdteske		drop \ key pressed
1214222417Sjulian
1215222417Sjulian	again	\ Non-operational key was pressed; repeat
1216222417Sjulian;
1217222417Sjulian
1218222417Sjulian\ This function unsets all the possible environment variables associated with
1219228985Spluknet\ creating the interactive menu.
1220222417Sjulian\ 
1221228985Spluknet: menu-unset ( -- )
1222222417Sjulian
1223222417Sjulian	49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
1224222417Sjulian	begin
1225243114Sdteske		dup menu_init[x]    unsetenv	\ menu initializer
1226243114Sdteske		dup menu_command[x] unsetenv	\ menu command
1227243114Sdteske		dup menu_caption[x] unsetenv	\ menu caption
1228243114Sdteske		dup ansi_caption[x] unsetenv	\ ANSI caption
1229243114Sdteske		dup menu_keycode[x] unsetenv	\ menu keycode
1230243114Sdteske		dup toggled_text[x] unsetenv	\ toggle_menuitem caption
1231243114Sdteske		dup toggled_ansi[x] unsetenv	\ toggle_menuitem ANSI caption
1232228985Spluknet
1233243114Sdteske		48 \ Iterator start (inner range 48 to 57; ASCII '0' to '9')
1234228985Spluknet		begin
1235243114Sdteske			\ cycle_menuitem caption and ANSI caption
1236243114Sdteske			2dup menu_caption[x][y] unsetenv
1237243114Sdteske			2dup ansi_caption[x][y] unsetenv
1238243114Sdteske			1+ dup 57 >
1239228985Spluknet		until
1240243114Sdteske		drop \ inner iterator
1241228985Spluknet
1242243114Sdteske		0 over menukeyN      !	\ used by menu-create, menu-display
1243243114Sdteske		0 over init_stateN   !	\ used by menu-create
1244243114Sdteske		0 over toggle_stateN !	\ used by toggle_menuitem
1245243114Sdteske		0 over init_textN   c!	\ used by toggle_menuitem
1246243114Sdteske		0 over cycle_stateN  !	\ used by cycle_menuitem
1247228985Spluknet
1248222417Sjulian		1+ dup 56 >	\ increment, continue if less than 57
1249222417Sjulian	until
1250222417Sjulian	drop \ iterator
1251222417Sjulian
1252262701Sdteske	s" menu_timeout_command" unsetenv	\ menu timeout command
1253262701Sdteske	s" menu_reboot"          unsetenv	\ Reboot menu option flag
1254262701Sdteske	s" menu_acpi"            unsetenv	\ ACPI menu option flag
1255262701Sdteske	s" menu_kernel"          unsetenv	\ Kernel menu option flag
1256262701Sdteske	s" menu_options"         unsetenv	\ Options separator flag
1257262701Sdteske	s" menu_optionstext"     unsetenv	\ separator display text
1258262701Sdteske	s" menu_init"            unsetenv	\ menu initializer
1259228985Spluknet
1260222417Sjulian	0 menureboot !
1261222417Sjulian	0 menuacpi !
1262222417Sjulian	0 menuoptions !
1263228985Spluknet;
1264228985Spluknet
1265281843Sdteskeonly forth definitions also menu-infrastructure
1266281843Sdteske
1267228985Spluknet\ This function both unsets menu variables and visually erases the menu area
1268228985Spluknet\ in-preparation for another menu.
1269228985Spluknet\ 
1270228985Spluknet: menu-clear ( -- )
1271228985Spluknet	menu-unset
1272222417Sjulian	menu-erase
1273222417Sjulian;
1274222417Sjulian
1275222417Sjulianbullet menubllt !
1276222417Sjulian
1277281843Sdteskealso menu-namespace
1278281843Sdteske
1279241523Sdteske\ Initialize our menu initialization state variables
1280241523Sdteske0 init_state1 !
1281241523Sdteske0 init_state2 !
1282241523Sdteske0 init_state3 !
1283241523Sdteske0 init_state4 !
1284241523Sdteske0 init_state5 !
1285241523Sdteske0 init_state6 !
1286241523Sdteske0 init_state7 !
1287241523Sdteske0 init_state8 !
1288241523Sdteske
1289222417Sjulian\ Initialize our boolean state variables
1290222417Sjulian0 toggle_state1 !
1291222417Sjulian0 toggle_state2 !
1292222417Sjulian0 toggle_state3 !
1293222417Sjulian0 toggle_state4 !
1294222417Sjulian0 toggle_state5 !
1295222417Sjulian0 toggle_state6 !
1296222417Sjulian0 toggle_state7 !
1297222417Sjulian0 toggle_state8 !
1298222417Sjulian
1299222417Sjulian\ Initialize our array state variables
1300222417Sjulian0 cycle_state1 !
1301222417Sjulian0 cycle_state2 !
1302222417Sjulian0 cycle_state3 !
1303222417Sjulian0 cycle_state4 !
1304222417Sjulian0 cycle_state5 !
1305222417Sjulian0 cycle_state6 !
1306222417Sjulian0 cycle_state7 !
1307222417Sjulian0 cycle_state8 !
1308222417Sjulian
1309222417Sjulian\ Initialize string containers
1310222417Sjulian0 init_text1 c!
1311222417Sjulian0 init_text2 c!
1312222417Sjulian0 init_text3 c!
1313222417Sjulian0 init_text4 c!
1314222417Sjulian0 init_text5 c!
1315222417Sjulian0 init_text6 c!
1316222417Sjulian0 init_text7 c!
1317222417Sjulian0 init_text8 c!
1318281843Sdteske
1319281843Sdteskeonly forth definitions
1320