menu.4th revision 280975
1\ Copyright (c) 2003 Scott Long <scottl@FreeBSD.org>
2\ Copyright (c) 2003 Aleksander Fafula <alex@fafula.com>
3\ Copyright (c) 2006-2015 Devin Teske <dteske@FreeBSD.org>
4\ All rights reserved.
5\ 
6\ Redistribution and use in source and binary forms, with or without
7\ modification, are permitted provided that the following conditions
8\ are met:
9\ 1. Redistributions of source code must retain the above copyright
10\    notice, this list of conditions and the following disclaimer.
11\ 2. Redistributions in binary form must reproduce the above copyright
12\    notice, this list of conditions and the following disclaimer in the
13\    documentation and/or other materials provided with the distribution.
14\ 
15\ THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16\ ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17\ IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18\ ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19\ FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20\ DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21\ OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22\ HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23\ LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24\ OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25\ SUCH DAMAGE.
26\ 
27\ $FreeBSD: head/sys/boot/forth/menu.4th 280975 2015-04-02 01:48:12Z dteske $
28
29marker task-menu.4th
30
31\ Frame drawing
32include /boot/frames.4th
33
34vocabulary menu-infrastructure
35vocabulary menu-namespace
36vocabulary menu-command-helpers
37
38only forth also menu-infrastructure definitions
39
40f_double        \ Set frames to double (see frames.4th). Replace with
41                \ f_single if you want single frames.
4246 constant dot \ ASCII definition of a period (in decimal)
43
44 5 constant menu_default_x         \ default column position of timeout
4510 constant menu_default_y         \ default row position of timeout msg
46 4 constant menu_timeout_default_x \ default column position of timeout
4723 constant menu_timeout_default_y \ default row position of timeout msg
4810 constant menu_timeout_default   \ default timeout (in seconds)
49
50\ Customize the following values with care
51
52  1 constant menu_start \ Numerical prefix of first menu item
53dot constant bullet     \ Menu bullet (appears after numerical prefix)
54  5 constant menu_x     \ Row position of the menu (from the top)
55 10 constant menu_y     \ Column position of the menu (from left side)
56
57\ Menu Appearance
58variable menuidx   \ Menu item stack for number prefixes
59variable menurow   \ Menu item stack for positioning
60variable menubllt  \ Menu item bullet
61
62\ Menu Positioning
63variable menuX     \ Menu X offset (columns)
64variable menuY     \ Menu Y offset (rows)
65
66\ Menu-item elements
67variable menurebootadded
68
69\ Parsing of kernels into menu-items
70variable kernidx
71variable kernlen
72variable kernmenuidx
73
74\ Menu timer [count-down] variables
75variable menu_timeout_enabled \ timeout state (internal use only)
76variable menu_time            \ variable for tracking the passage of time
77variable menu_timeout         \ determined configurable delay duration
78variable menu_timeout_x       \ column position of timeout message
79variable menu_timeout_y       \ row position of timeout message
80
81\ Containers for parsing kernels into menu-items
82create kerncapbuf 64 allot
83create kerndefault 64 allot
84create kernelsbuf 256 allot
85
86only forth also menu-namespace definitions
87
88\ Menu-item key association/detection
89variable menukey1
90variable menukey2
91variable menukey3
92variable menukey4
93variable menukey5
94variable menukey6
95variable menukey7
96variable menukey8
97variable menureboot
98variable menuacpi
99variable menuoptions
100variable menukernel
101
102\ Menu initialization status variables
103variable init_state1
104variable init_state2
105variable init_state3
106variable init_state4
107variable init_state5
108variable init_state6
109variable init_state7
110variable init_state8
111
112\ Boolean option status variables
113variable toggle_state1
114variable toggle_state2
115variable toggle_state3
116variable toggle_state4
117variable toggle_state5
118variable toggle_state6
119variable toggle_state7
120variable toggle_state8
121
122\ Array option status variables
123variable cycle_state1
124variable cycle_state2
125variable cycle_state3
126variable cycle_state4
127variable cycle_state5
128variable cycle_state6
129variable cycle_state7
130variable cycle_state8
131
132\ Containers for storing the initial caption text
133create init_text1 64 allot
134create init_text2 64 allot
135create init_text3 64 allot
136create init_text4 64 allot
137create init_text5 64 allot
138create init_text6 64 allot
139create init_text7 64 allot
140create init_text8 64 allot
141
142only forth definitions
143
144: arch-i386? ( -- BOOL ) \ Returns TRUE (-1) on i386, FALSE (0) otherwise.
145	s" arch-i386" environment? dup if
146		drop
147	then
148;
149
150: acpipresent? ( -- flag ) \ Returns TRUE if ACPI is present, FALSE otherwise
151	s" hint.acpi.0.rsdp" getenv
152	dup -1 = if
153		drop false exit
154	then
155	2drop
156	true
157;
158
159: acpienabled? ( -- flag ) \ Returns TRUE if ACPI is enabled, FALSE otherwise
160	s" hint.acpi.0.disabled" getenv
161	dup -1 <> if
162		s" 0" compare 0<> if
163			false exit
164		then
165	else
166		drop
167	then
168	true
169;
170
171: +c! ( N C-ADDR/U K -- C-ADDR/U )
172	3 pick 3 pick	( n c-addr/u k -- n c-addr/u k n c-addr )
173	rot + c!	( n c-addr/u k n c-addr -- n c-addr/u )
174	rot drop	( n c-addr/u -- c-addr/u )
175;
176
177only forth also menu-namespace definitions
178
179\ Forth variables
180: namespace     ( C-ADDR/U N -- ) also menu-namespace +c! evaluate previous ;
181: menukeyN      ( N -- ADDR )   s" menukeyN"       7 namespace ;
182: init_stateN   ( N -- ADDR )   s" init_stateN"   10 namespace ;
183: toggle_stateN ( N -- ADDR )   s" toggle_stateN" 12 namespace ;
184: cycle_stateN  ( N -- ADDR )   s" cycle_stateN"  11 namespace ;
185: init_textN    ( N -- C-ADDR ) s" init_textN"     9 namespace ;
186
187\ Environment variables
188: kernel[x]          ( N -- C-ADDR/U )   s" kernel[x]"           7 +c! ;
189: menu_init[x]       ( N -- C-ADDR/U )   s" menu_init[x]"       10 +c! ;
190: menu_command[x]    ( N -- C-ADDR/U )   s" menu_command[x]"    13 +c! ;
191: menu_caption[x]    ( N -- C-ADDR/U )   s" menu_caption[x]"    13 +c! ;
192: ansi_caption[x]    ( N -- C-ADDR/U )   s" ansi_caption[x]"    13 +c! ;
193: menu_keycode[x]    ( N -- C-ADDR/U )   s" menu_keycode[x]"    13 +c! ;
194: toggled_text[x]    ( N -- C-ADDR/U )   s" toggled_text[x]"    13 +c! ;
195: toggled_ansi[x]    ( N -- C-ADDR/U )   s" toggled_ansi[x]"    13 +c! ;
196: menu_caption[x][y] ( N M -- C-ADDR/U ) s" menu_caption[x][y]" 16 +c! 13 +c! ;
197: ansi_caption[x][y] ( N M -- C-ADDR/U ) s" ansi_caption[x][y]" 16 +c! 13 +c! ;
198
199also menu-infrastructure definitions
200
201\ This function prints a menu item at menuX (row) and menuY (column), returns
202\ the incremental decimal ASCII value associated with the menu item, and
203\ increments the cursor position to the next row for the creation of the next
204\ menu item. This function is called by the menu-create function. You need not
205\ call it directly.
206\ 
207: printmenuitem ( menu_item_str -- ascii_keycode )
208
209	menurow dup @ 1+ swap ! ( increment menurow )
210	menuidx dup @ 1+ swap ! ( increment menuidx )
211
212	\ Calculate the menuitem row position
213	menurow @ menuY @ +
214
215	\ Position the cursor at the menuitem position
216	dup menuX @ swap at-xy
217
218	\ Print the value of menuidx
219	loader_color? dup ( -- bool bool )
220	if b then
221	menuidx @ .
222	if me then
223
224	\ Move the cursor forward 1 column
225	dup menuX @ 1+ swap at-xy
226
227	menubllt @ emit	\ Print the menu bullet using the emit function
228
229	\ Move the cursor to the 3rd column from the current position
230	\ to allow for a space between the numerical prefix and the
231	\ text caption
232	menuX @ 3 + swap at-xy
233
234	\ Print the menu caption (we expect a string to be on the stack
235	\ prior to invoking this function)
236	type
237
238	\ Here we will add the ASCII decimal of the numerical prefix
239	\ to the stack (decimal ASCII for `1' is 49) as a "return value"
240	menuidx @ 48 +
241;
242
243\ This function prints the appropriate menuitem basename to the stack if an
244\ ACPI option is to be presented to the user, otherwise returns -1. Used
245\ internally by menu-create, you need not (nor should you) call this directly.
246\ 
247: acpimenuitem ( -- C-Addr/U | -1 )
248
249	arch-i386? if
250		acpipresent? if
251			acpienabled? if
252				loader_color? if
253					s" toggled_ansi[x]"
254				else
255					s" toggled_text[x]"
256				then
257			else
258				loader_color? if
259					s" ansi_caption[x]"
260				else
261					s" menu_caption[x]"
262				then
263			then
264		else
265			menuidx dup @ 1+ swap ! ( increment menuidx )
266			-1
267		then
268	else
269		-1
270	then
271;
272
273: delim? ( C -- BOOL )
274	dup  32 =		( c -- c bool )		\ [sp] space
275	over  9 = or		( c bool -- c bool )	\ [ht] horizontal tab
276	over 10 = or		( c bool -- c bool )	\ [nl] newline
277	over 13 = or		( c bool -- c bool )	\ [cr] carriage return
278	over [char] , =	or	( c bool -- c bool )	\ comma
279	swap drop		( c bool -- bool )	\ return boolean
280;
281
282\ This function parses $kernels into variables that are used by the menu to
283\ display wich kernel to boot when the [overloaded] `boot' word is interpreted.
284\ Used internally by menu-create, you need not (nor should you) call this
285\ directly.
286\ 
287: parse-kernels ( N -- ) \ kernidx
288	kernidx ! ( n -- )	\ store provided `x' value
289	[char] 0 kernmenuidx !	\ initialize `y' value for menu_caption[x][y]
290
291	\ Attempt to get a list of kernels, fall back to sensible default
292	s" kernels" getenv dup -1 = if
293		drop ( cruft )
294		s" kernel kernel.old"
295	then ( -- c-addr/u )
296
297	\ Check to see if the user has altered $kernel by comparing it against
298	\ $kernel[N] where N is kernel_state (the actively displayed kernel).
299	s" kernel_state" evaluate @ 48 + s" kernel[N]" 7 +c! getenv
300	dup -1 <> if
301		s" kernel" getenv dup -1 = if
302			drop ( cruft ) s" "
303		then
304		2swap 2over compare 0= if
305			2drop FALSE ( skip below conditional )
306		else \ User has changed $kernel
307			TRUE ( slurp in new value )
308		then
309	else \ We haven't yet parsed $kernels into $kernel[N]
310		drop ( getenv cruft )
311		s" kernel" getenv dup -1 = if
312			drop ( cruft ) s" "
313		then
314		TRUE ( slurp in initial value )
315	then ( c-addr/u -- c-addr/u c-addr/u,-1 | 0 )
316	if \ slurp new value into kerndefault
317		kerndefault 1+ 0 2swap strcat swap 1- c!
318	then
319
320	\ Clear out existing parsed-kernels
321	kernidx @ [char] 0
322	begin
323		dup kernel[x] unsetenv
324		2dup menu_caption[x][y] unsetenv
325		2dup ansi_caption[x][y] unsetenv
326		1+ dup [char] 8 >
327	until
328	2drop
329
330	\ Step through the string until we find the end
331	begin
332		0 kernlen ! \ initialize length of value
333
334		\ Skip leading whitespace and/or comma delimiters
335		begin
336			dup 0<> if
337				over c@ delim? ( c-addr/u -- c-addr/u bool )
338			else
339				false ( c-addr/u -- c-addr/u bool )
340			then
341		while
342			1- swap 1+ swap ( c-addr/u -- c-addr'/u' )
343		repeat
344		( c-addr/u -- c-addr'/u' )
345
346		dup 0= if \ end of string while eating whitespace
347			2drop ( c-addr/u -- )
348			kernmenuidx @ [char] 0 <> if \ found at least one
349				exit \ all done
350			then
351
352			\ No entries in $kernels; use $kernel instead
353			s" kernel" getenv dup -1 = if
354				drop ( cruft ) s" "
355			then ( -- c-addr/u )
356			dup kernlen ! \ store entire value length as kernlen
357		else
358			\ We're still within $kernels parsing toward the end;
359			\ find delimiter/end to determine kernlen
360			2dup ( c-addr/u -- c-addr/u c-addr/u )
361			begin dup 0<> while
362				over c@ delim? if
363					drop 0 ( break ) \ found delimiter
364				else
365					kernlen @ 1+ kernlen ! \ incrememnt
366					1- swap 1+ swap \ c-addr++ u--
367				then
368			repeat
369			2drop ( c-addr/u c-addr'/u' -- c-addr/u )
370
371			\ If this is the first entry, compare it to $kernel
372			\ If different, then insert $kernel beforehand
373			kernmenuidx @ [char] 0 = if
374				over kernlen @ kerndefault count compare if
375					kernelsbuf 0 kerndefault count strcat
376					s" ," strcat 2swap strcat
377					kerndefault count swap drop kernlen !
378				then
379			then
380		then
381		( c-addr/u -- c-addr'/u' )
382
383		\ At this point, we should have something on the stack to store
384		\ as the next kernel menu option; start assembling variables
385
386		over kernlen @ ( c-addr/u -- c-addr/u c-addr/u2 )
387
388		\ Assign first to kernel[x]
389		2dup kernmenuidx @ kernel[x] setenv
390
391		\ Assign second to menu_caption[x][y]
392		kerncapbuf 0 s" [K]ernel: " strcat
393		2over strcat
394		kernidx @ kernmenuidx @ menu_caption[x][y]
395		setenv
396
397		\ Assign third to ansi_caption[x][y]
398		kerncapbuf 0 s" @[1mK@[37mernel: " [char] @ escc! strcat
399		kernmenuidx @ [char] 0 = if
400			s" default/@[32m"
401		else
402			s" @[34;1m"
403		then
404		[char] @ escc! strcat
405		2over strcat
406		s" @[37m" [char] @ escc! strcat
407		kernidx @ kernmenuidx @ ansi_caption[x][y]
408		setenv
409
410		2drop ( c-addr/u c-addr/u2 -- c-addr/u )
411
412		kernmenuidx @ 1+ dup kernmenuidx ! [char] 8 > if
413			2drop ( c-addr/u -- ) exit
414		then
415
416		kernlen @ - swap kernlen @ + swap ( c-addr/u -- c-addr'/u' )
417	again
418;
419
420\ This function goes through the kernels that were discovered by the
421\ parse-kernels function [above], adding " (# of #)" text to the end of each
422\ caption.
423\ 
424: tag-kernels ( -- )
425	kernidx @ ( -- x ) dup 0= if exit then
426	[char] 0 s"  (Y of Z)" ( x -- x y c-addr/u )
427	kernmenuidx @ -rot 7 +c! \ Replace 'Z' with number of kernels parsed
428	begin
429		2 pick 1+ -rot 2 +c! \ Replace 'Y' with current ASCII num
430
431		2over menu_caption[x][y] getenv dup -1 <> if
432			2dup + 1- c@ [char] ) = if
433				2drop \ Already tagged
434			else
435				kerncapbuf 0 2swap strcat
436				2over strcat
437				5 pick 5 pick menu_caption[x][y] setenv
438			then
439		else
440			drop ( getenv cruft )
441		then
442
443		2over ansi_caption[x][y] getenv dup -1 <> if
444			2dup + 1- c@ [char] ) = if
445				2drop \ Already tagged
446			else
447				kerncapbuf 0 2swap strcat
448				2over strcat
449				5 pick 5 pick ansi_caption[x][y] setenv
450			then
451		else
452			drop ( getenv cruft )
453		then
454
455		rot 1+ dup [char] 8 > if
456			-rot 2drop TRUE ( break )
457		else
458			-rot FALSE
459		then
460	until
461	2drop ( x y -- )
462;
463
464\ This function creates the list of menu items. This function is called by the
465\ menu-display function. You need not call it directly.
466\ 
467: menu-create ( -- )
468
469	\ Print the frame caption at (x,y)
470	s" loader_menu_title" getenv dup -1 = if
471		drop s" Welcome to FreeBSD"
472	then
473	TRUE ( use default alignment )
474	s" loader_menu_title_align" getenv dup -1 <> if
475		2dup s" left" compare-insensitive 0= if ( 1 )
476			2drop ( c-addr/u ) drop ( bool )
477			menuX @ menuY @ 1-
478			FALSE ( don't use default alignment )
479		else ( 1 ) 2dup s" right" compare-insensitive 0= if ( 2 )
480			2drop ( c-addr/u ) drop ( bool )
481			menuX @ 42 + 4 - over - menuY @ 1-
482			FALSE ( don't use default alignment )
483		else ( 2 ) 2drop ( c-addr/u ) then ( 1 ) then
484	else
485		drop ( getenv cruft )
486	then
487	if ( use default center alignement? )
488		menuX @ 19 + over 2 / - menuY @ 1-
489	then
490	at-xy type 
491
492	\ If $menu_init is set, evaluate it (allowing for whole menus to be
493	\ constructed dynamically -- as this function could conceivably set
494	\ the remaining environment variables to construct the menu entirely).
495	\ 
496	s" menu_init" getenv dup -1 <> if
497		evaluate
498	else
499		drop
500	then
501
502	\ Print our menu options with respective key/variable associations.
503	\ `printmenuitem' ends by adding the decimal ASCII value for the
504	\ numerical prefix to the stack. We store the value left on the stack
505	\ to the key binding variable for later testing against a character
506	\ captured by the `getkey' function.
507
508	\ Note that any menu item beyond 9 will have a numerical prefix on the
509	\ screen consisting of the first digit (ie. 1 for the tenth menu item)
510	\ and the key required to activate that menu item will be the decimal
511	\ ASCII of 48 plus the menu item (ie. 58 for the tenth item, aka. `:')
512	\ which is misleading and not desirable.
513	\ 
514	\ Thus, we do not allow more than 8 configurable items on the menu
515	\ (with "Reboot" as the optional ninth and highest numbered item).
516
517	\ 
518	\ Initialize the ACPI option status.
519	\ 
520	0 menuacpi !
521	s" menu_acpi" getenv -1 <> if
522		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
523			menuacpi !
524			arch-i386? if acpipresent? if
525				\ 
526				\ Set menu toggle state to active state
527				\ (required by generic toggle_menuitem)
528				\ 
529				acpienabled? menuacpi @ toggle_stateN !
530			then then
531		else
532			drop
533		then
534	then
535
536	\ 
537	\ Initialize kernel captions after parsing $kernels
538	\ 
539	0 menukernel !
540	s" menu_kernel" getenv -1 <> if
541		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
542			dup menukernel !
543			dup parse-kernels tag-kernels
544
545			\ Get the current cycle state (entry to use)
546			s" kernel_state" evaluate @ 48 + ( n -- n y )
547
548			\ If state is invalid, reset
549			dup kernmenuidx @ 1- > if
550				drop [char] 0 ( n y -- n 48 )
551				0 s" kernel_state" evaluate !
552				over s" init_kernel" evaluate drop
553			then
554
555			\ Set the current non-ANSI caption
556			2dup swap dup ( n y -- n y y n n )
557			s" set menu_caption[x]=$menu_caption[x][y]"
558			17 +c! 34 +c! 37 +c! evaluate
559			( n y y n n c-addr/u -- n y  )
560
561			\ Set the current ANSI caption
562			2dup swap dup ( n y -- n y y n n )
563			s" set ansi_caption[x]=$ansi_caption[x][y]"
564			17 +c! 34 +c! 37 +c! evaluate
565			( n y y n n c-addr/u -- n y )
566
567			\ Initialize cycle state from stored value
568			48 - ( n y -- n k )
569			s" init_cyclestate" evaluate ( n k -- n )
570
571			\ Set $kernel to $kernel[y]
572			s" activate_kernel" evaluate ( n -- n )
573		then
574		drop
575	then
576
577	\ 
578	\ Initialize the menu_options visual separator.
579	\ 
580	0 menuoptions !
581	s" menu_options" getenv -1 <> if
582		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
583			menuoptions !
584		else
585			drop
586		then
587	then
588
589	\ Initialize "Reboot" menu state variable (prevents double-entry)
590	false menurebootadded !
591
592	menu_start
593	1- menuidx !    \ Initialize the starting index for the menu
594	0 menurow !     \ Initialize the starting position for the menu
595
596	49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
597	begin
598		\ If the "Options:" separator, print it.
599		dup menuoptions @ = if
600			\ Optionally add a reboot option to the menu
601			s" menu_reboot" getenv -1 <> if
602				drop
603				s" Reboot" printmenuitem menureboot !
604				true menurebootadded !
605			then
606
607			menuX @
608			menurow @ 2 + menurow !
609			menurow @ menuY @ +
610			at-xy
611			s" menu_optionstext" getenv dup -1 <> if
612				type
613			else
614				drop ." Options:"
615			then
616		then
617
618		\ If this is the ACPI menu option, act accordingly.
619		dup menuacpi @ = if
620			dup acpimenuitem ( n -- n n c-addr/u | n n -1 )
621			dup -1 <> if
622				13 +c! ( n n c-addr/u -- n c-addr/u )
623				       \ replace 'x' with n
624			else
625				swap drop ( n n -1 -- n -1 )
626				over menu_command[x] unsetenv
627			then
628		else
629			\ make sure we have not already initialized this item
630			dup init_stateN dup @ 0= if
631				1 swap !
632
633				\ If this menuitem has an initializer, run it
634				dup menu_init[x]
635				getenv dup -1 <> if
636					evaluate
637				else
638					drop
639				then
640			else
641				drop
642			then
643
644			dup
645			loader_color? if
646				ansi_caption[x]
647			else
648				menu_caption[x]
649			then
650		then
651
652		dup -1 <> if
653			\ test for environment variable
654			getenv dup -1 <> if
655				printmenuitem ( c-addr/u -- n )
656				dup menukeyN !
657			else
658				drop
659			then
660		else
661			drop
662		then
663
664		1+ dup 56 > \ add 1 to iterator, continue if less than 57
665	until
666	drop \ iterator
667
668	\ Optionally add a reboot option to the menu
669	menurebootadded @ true <> if
670		s" menu_reboot" getenv -1 <> if
671			drop       \ no need for the value
672			s" Reboot" \ menu caption (required by printmenuitem)
673
674			printmenuitem
675			menureboot !
676		else
677			0 menureboot !
678		then
679	then
680;
681
682\ Takes a single integer on the stack and updates the timeout display. The
683\ integer must be between 0 and 9 (we will only update a single digit in the
684\ source message).
685\ 
686: menu-timeout-update ( N -- )
687
688	\ Enforce minimum/maximum
689	dup 9 > if drop 9 then
690	dup 0 < if drop 0 then
691
692	s" Autoboot in N seconds. [Space] to pause" ( n -- n c-addr/u )
693
694	2 pick 0> if
695		rot 48 + -rot ( n c-addr/u -- n' c-addr/u ) \ convert to ASCII
696		12 +c!        ( n' c-addr/u -- c-addr/u )   \ replace 'N' above
697
698		menu_timeout_x @ menu_timeout_y @ at-xy \ position cursor
699		type ( c-addr/u -- ) \ print message
700	else
701		menu_timeout_x @ menu_timeout_y @ at-xy \ position cursor
702		spaces ( n c-addr/u -- n c-addr ) \ erase message
703		2drop ( n c-addr -- )
704	then
705
706	0 25 at-xy ( position cursor back at bottom-left )
707;
708
709\ This function blocks program flow (loops forever) until a key is pressed.
710\ The key that was pressed is added to the top of the stack in the form of its
711\ decimal ASCII representation. This function is called by the menu-display
712\ function. You need not call it directly.
713\ 
714: getkey ( -- ascii_keycode )
715
716	begin \ loop forever
717
718		menu_timeout_enabled @ 1 = if
719			( -- )
720			seconds ( get current time: -- N )
721			dup menu_time @ <> if ( has time elapsed?: N N N -- N )
722
723				\ At least 1 second has elapsed since last loop
724				\ so we will decrement our "timeout" (really a
725				\ counter, insuring that we do not proceed too
726				\ fast) and update our timeout display.
727
728				menu_time ! ( update time record: N -- )
729				menu_timeout @ ( "time" remaining: -- N )
730				dup 0> if ( greater than 0?: N N 0 -- N )
731					1- ( decrement counter: N -- N )
732					dup menu_timeout !
733						( re-assign: N N Addr -- N )
734				then
735				( -- N )
736
737				dup 0= swap 0< or if ( N <= 0?: N N -- )
738					\ halt the timer
739					0 menu_timeout ! ( 0 Addr -- )
740					0 menu_timeout_enabled ! ( 0 Addr -- )
741				then
742
743				\ update the timer display ( N -- )
744				menu_timeout @ menu-timeout-update
745
746				menu_timeout @ 0= if
747					\ We've reached the end of the timeout
748					\ (user did not cancel by pressing ANY
749					\ key)
750
751					s" menu_timeout_command"  getenv dup
752					-1 = if
753						drop \ clean-up
754					else
755						evaluate
756					then
757				then
758
759			else ( -- N )
760				\ No [detectable] time has elapsed (in seconds)
761				drop ( N -- )
762			then
763			( -- )
764		then
765
766		key? if \ Was a key pressed? (see loader(8))
767
768			\ An actual key was pressed (if the timeout is running,
769			\ kill it regardless of which key was pressed)
770			menu_timeout @ 0<> if
771				0 menu_timeout !
772				0 menu_timeout_enabled !
773
774				\ clear screen of timeout message
775				0 menu-timeout-update
776			then
777
778			\ get the key that was pressed and exit (if we
779			\ get a non-zero ASCII code)
780			key dup 0<> if
781				exit
782			else
783				drop
784			then
785		then
786		50 ms \ sleep for 50 milliseconds (see loader(8))
787
788	again
789;
790
791: menu-erase ( -- ) \ Erases menu and resets positioning variable to positon 1.
792
793	\ Clear the screen area associated with the interactive menu
794	menuX @ menuY @
795	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
796	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
797	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
798	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
799	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
800	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces
801	2drop
802
803	\ Reset the starting index and position for the menu
804	menu_start 1- menuidx !
805	0 menurow !
806;
807
808only forth
809also menu-infrastructure
810also menu-namespace
811also menu-command-helpers definitions
812
813: toggle_menuitem ( N -- N ) \ toggles caption text and internal menuitem state
814
815	\ ASCII numeral equal to user-selected menu item must be on the stack.
816	\ We do not modify the stack, so the ASCII numeral is left on top.
817
818	dup init_textN c@ 0= if
819		\ NOTE: no need to check toggle_stateN since the first time we
820		\ are called, we will populate init_textN. Further, we don't
821		\ need to test whether menu_caption[x] (ansi_caption[x] when
822		\ loader_color?=1) is available since we would not have been
823		\ called if the caption was NULL.
824
825		\ base name of environment variable
826		dup ( n -- n n ) \ key pressed
827		loader_color? if
828			ansi_caption[x]
829		else
830			menu_caption[x]
831		then	
832		getenv dup -1 <> if
833
834			2 pick ( n c-addr/u -- n c-addr/u n )
835			init_textN ( n c-addr/u n -- n c-addr/u c-addr )
836
837			\ now we have the buffer c-addr on top
838			\ ( followed by c-addr/u of current caption )
839
840			\ Copy the current caption into our buffer
841			2dup c! -rot \ store strlen at first byte
842			begin
843				rot 1+    \ bring alt addr to top and increment
844				-rot -rot \ bring buffer addr to top
845				2dup c@ swap c! \ copy current character
846				1+     \ increment buffer addr
847				rot 1- \ bring buffer len to top and decrement
848				dup 0= \ exit loop if buffer len is zero
849			until
850			2drop \ buffer len/addr
851			drop  \ alt addr
852
853		else
854			drop
855		then
856	then
857
858	\ Now we are certain to have init_textN populated with the initial
859	\ value of menu_caption[x] (ansi_caption[x] with loader_color enabled).
860	\ We can now use init_textN as the untoggled caption and
861	\ toggled_text[x] (toggled_ansi[x] with loader_color enabled) as the
862	\ toggled caption and store the appropriate value into menu_caption[x]
863	\ (again, ansi_caption[x] with loader_color enabled). Last, we'll
864	\ negate the toggled state so that we reverse the flow on subsequent
865	\ calls.
866
867	dup toggle_stateN @ 0= if
868		\ state is OFF, toggle to ON
869
870		dup ( n -- n n ) \ key pressed
871		loader_color? if
872			toggled_ansi[x]
873		else
874			toggled_text[x]
875		then
876		getenv dup -1 <> if
877			\ Assign toggled text to menu caption
878			2 pick ( n c-addr/u -- n c-addr/u n ) \ key pressed
879			loader_color? if
880				ansi_caption[x]
881			else
882				menu_caption[x]
883			then
884			setenv
885		else
886			\ No toggled text, keep the same caption
887			drop ( n -1 -- n ) \ getenv cruft
888		then
889
890		true \ new value of toggle state var (to be stored later)
891	else
892		\ state is ON, toggle to OFF
893
894		dup init_textN count ( n -- n c-addr/u )
895
896		\ Assign init_textN text to menu caption
897		2 pick ( n c-addr/u -- n c-addr/u n ) \ key pressed
898		loader_color? if
899			ansi_caption[x]
900		else
901			menu_caption[x]
902		then
903		setenv
904
905		false \ new value of toggle state var (to be stored below)
906	then
907
908	\ now we'll store the new toggle state (on top of stack)
909	over toggle_stateN !
910;
911
912: cycle_menuitem ( N -- N ) \ cycles through array of choices for a menuitem
913
914	\ ASCII numeral equal to user-selected menu item must be on the stack.
915	\ We do not modify the stack, so the ASCII numeral is left on top.
916
917	dup cycle_stateN dup @ 1+ \ get value and increment
918
919	\ Before assigning the (incremented) value back to the pointer,
920	\ let's test for the existence of this particular array element.
921	\ If the element exists, we'll store index value and move on.
922	\ Otherwise, we'll loop around to zero and store that.
923
924	dup 48 + ( n addr k -- n addr k k' )
925	         \ duplicate array index and convert to ASCII numeral
926
927	3 pick swap ( n addr k k' -- n addr k n k' ) \ (n,k') as (x,y)
928	loader_color? if
929		ansi_caption[x][y]
930	else
931		menu_caption[x][y]
932	then
933	( n addr k n k' -- n addr k c-addr/u )
934
935	\ Now test for the existence of our incremented array index in the
936	\ form of $menu_caption[x][y] ($ansi_caption[x][y] with loader_color
937	\ enabled) as set in loader.rc(5), et. al.
938
939	getenv dup -1 = if
940		\ No caption set for this array index. Loop back to zero.
941
942		drop ( n addr k -1 -- n addr k ) \ getenv cruft
943		drop 0 ( n addr k -- n addr 0 )  \ new value to store later
944
945		2 pick [char] 0 ( n addr 0 -- n addr 0 n 48 ) \ (n,48) as (x,y)
946		loader_color? if
947			ansi_caption[x][y]
948		else
949			menu_caption[x][y]
950		then
951		( n addr 0 n 48 -- n addr 0 c-addr/u )
952		getenv dup -1 = if
953			\ Highly unlikely to occur, but to ensure things move
954			\ along smoothly, allocate a temporary NULL string
955			drop ( cruft ) s" "
956		then
957	then
958
959	\ At this point, we should have the following on the stack (in order,
960	\ from bottom to top):
961	\ 
962	\    n        - Ascii numeral representing the menu choice (inherited)
963	\    addr     - address of our internal cycle_stateN variable
964	\    k        - zero-based number we intend to store to the above
965	\    c-addr/u - string value we intend to store to menu_caption[x]
966	\               (or ansi_caption[x] with loader_color enabled)
967	\ 
968	\ Let's perform what we need to with the above.
969
970	\ Assign array value text to menu caption
971	4 pick ( n addr k c-addr/u -- n addr k c-addr/u n )
972	loader_color? if
973		ansi_caption[x]
974	else
975		menu_caption[x]
976	then
977	setenv
978
979	swap ! ( n addr k -- n ) \ update array state variable
980;
981
982only forth definitions also menu-infrastructure
983
984\ Erase and redraw the menu. Useful if you change a caption and want to
985\ update the menu to reflect the new value.
986\ 
987: menu-redraw ( -- )
988	menu-erase
989	menu-create
990;
991
992\ This function initializes the menu. Call this from your `loader.rc' file
993\ before calling any other menu-related functions.
994\ 
995: menu-init ( -- )
996	menu_start
997	1- menuidx !    \ Initialize the starting index for the menu
998	0 menurow !     \ Initialize the starting position for the menu
999
1000	\ Assign configuration values
1001	s" loader_menu_y" getenv dup -1 = if
1002		drop \ no custom row position
1003		menu_default_y
1004	else
1005		\ make sure custom position is a number
1006		?number 0= if
1007			menu_default_y \ or use default
1008		then
1009	then
1010	menuY !
1011	s" loader_menu_x" getenv dup -1 = if
1012		drop \ no custom column position
1013		menu_default_x
1014	else
1015		\ make sure custom position is a number
1016		?number 0= if
1017			menu_default_x \ or use default
1018		then
1019	then
1020	menuX !
1021
1022	\ Interpret a custom frame type for the menu
1023	TRUE ( draw a box? default yes, but might be altered below )
1024	s" loader_menu_frame" getenv dup -1 = if ( 1 )
1025		drop \ no custom frame type
1026	else ( 1 )  2dup s" single" compare-insensitive 0= if ( 2 )
1027		f_single ( see frames.4th )
1028	else ( 2 )  2dup s" double" compare-insensitive 0= if ( 3 )
1029		f_double ( see frames.4th )
1030	else ( 3 ) s" none" compare-insensitive 0= if ( 4 )
1031		drop FALSE \ don't draw a box
1032	( 4 ) then ( 3 ) then ( 2 )  then ( 1 ) then
1033	if
1034		42 13 menuX @ 3 - menuY @ 1- box \ Draw frame (w,h,x,y)
1035	then
1036
1037	0 25 at-xy \ Move cursor to the bottom for output
1038;
1039
1040also menu-namespace
1041
1042\ Main function. Call this from your `loader.rc' file.
1043\ 
1044: menu-display ( -- )
1045
1046	0 menu_timeout_enabled ! \ start with automatic timeout disabled
1047
1048	\ check indication that automatic execution after delay is requested
1049	s" menu_timeout_command" getenv -1 <> if ( Addr C -1 -- | Addr )
1050		drop ( just testing existence right now: Addr -- )
1051
1052		\ initialize state variables
1053		seconds menu_time ! ( store the time we started )
1054		1 menu_timeout_enabled ! ( enable automatic timeout )
1055
1056		\ read custom time-duration (if set)
1057		s" autoboot_delay" getenv dup -1 = if
1058			drop \ no custom duration (remove dup'd bunk -1)
1059			menu_timeout_default \ use default setting
1060		else
1061			2dup ?number 0= if ( if not a number )
1062				\ disable timeout if "NO", else use default
1063				s" NO" compare-insensitive 0= if
1064					0 menu_timeout_enabled !
1065					0 ( assigned to menu_timeout below )
1066				else
1067					menu_timeout_default
1068				then
1069			else
1070				-rot 2drop
1071
1072				\ boot immediately if less than zero
1073				dup 0< if
1074					drop
1075					menu-create
1076					0 25 at-xy
1077					0 boot
1078				then
1079			then
1080		then
1081		menu_timeout ! ( store value on stack from above )
1082
1083		menu_timeout_enabled @ 1 = if
1084			\ read custom column position (if set)
1085			s" loader_menu_timeout_x" getenv dup -1 = if
1086				drop \ no custom column position
1087				menu_timeout_default_x \ use default setting
1088			else
1089				\ make sure custom position is a number
1090				?number 0= if
1091					menu_timeout_default_x \ or use default
1092				then
1093			then
1094			menu_timeout_x ! ( store value on stack from above )
1095        
1096			\ read custom row position (if set)
1097			s" loader_menu_timeout_y" getenv dup -1 = if
1098				drop \ no custom row position
1099				menu_timeout_default_y \ use default setting
1100			else
1101				\ make sure custom position is a number
1102				?number 0= if
1103					menu_timeout_default_y \ or use default
1104				then
1105			then
1106			menu_timeout_y ! ( store value on stack from above )
1107		then
1108	then
1109
1110	menu-create
1111
1112	begin \ Loop forever
1113
1114		0 25 at-xy \ Move cursor to the bottom for output
1115		getkey     \ Block here, waiting for a key to be pressed
1116
1117		dup -1 = if
1118			drop exit \ Caught abort (abnormal return)
1119		then
1120
1121		\ Boot if the user pressed Enter/Ctrl-M (13) or
1122		\ Ctrl-Enter/Ctrl-J (10)
1123		dup over 13 = swap 10 = or if
1124			drop ( no longer needed )
1125			s" boot" evaluate
1126			exit ( pedantic; never reached )
1127		then
1128
1129		dup menureboot @ = if 0 reboot then
1130
1131		\ Evaluate the decimal ASCII value against known menu item
1132		\ key associations and act accordingly
1133
1134		49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
1135		begin
1136			dup menukeyN @
1137			rot tuck = if
1138
1139				\ Adjust for missing ACPI menuitem on non-i386
1140				arch-i386? true <> menuacpi @ 0<> and if
1141					menuacpi @ over 2dup < -rot = or
1142					over 58 < and if
1143					( key >= menuacpi && key < 58: N -- N )
1144						1+
1145					then
1146				then
1147
1148				\ Test for the environment variable
1149				dup menu_command[x]
1150				getenv dup -1 <> if
1151					\ Execute the stored procedure
1152					evaluate
1153
1154					\ We expect there to be a non-zero
1155					\  value left on the stack after
1156					\ executing the stored procedure.
1157					\ If so, continue to run, else exit.
1158
1159					0= if
1160						drop \ key pressed
1161						drop \ loop iterator
1162						exit
1163					else
1164						swap \ need iterator on top
1165					then
1166				then
1167
1168				\ Re-adjust for missing ACPI menuitem
1169				arch-i386? true <> menuacpi @ 0<> and if
1170					swap
1171					menuacpi @ 1+ over 2dup < -rot = or
1172					over 59 < and if
1173						1-
1174					then
1175					swap
1176				then
1177			else
1178				swap \ need iterator on top
1179			then
1180
1181			\ 
1182			\ Check for menu keycode shortcut(s)
1183			\ 
1184			dup menu_keycode[x]
1185			getenv dup -1 = if
1186				drop
1187			else
1188				?number 0<> if
1189					rot tuck = if
1190						swap
1191						dup menu_command[x]
1192						getenv dup -1 <> if
1193							evaluate
1194							0= if
1195								2drop
1196								exit
1197							then
1198						else
1199							drop
1200						then
1201					else
1202						swap
1203					then
1204				then
1205			then
1206
1207			1+ dup 56 > \ increment iterator
1208			            \ continue if less than 57
1209		until
1210		drop \ loop iterator
1211		drop \ key pressed
1212
1213	again	\ Non-operational key was pressed; repeat
1214;
1215
1216\ This function unsets all the possible environment variables associated with
1217\ creating the interactive menu.
1218\ 
1219: menu-unset ( -- )
1220
1221	49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
1222	begin
1223		dup menu_init[x]    unsetenv	\ menu initializer
1224		dup menu_command[x] unsetenv	\ menu command
1225		dup menu_caption[x] unsetenv	\ menu caption
1226		dup ansi_caption[x] unsetenv	\ ANSI caption
1227		dup menu_keycode[x] unsetenv	\ menu keycode
1228		dup toggled_text[x] unsetenv	\ toggle_menuitem caption
1229		dup toggled_ansi[x] unsetenv	\ toggle_menuitem ANSI caption
1230
1231		48 \ Iterator start (inner range 48 to 57; ASCII '0' to '9')
1232		begin
1233			\ cycle_menuitem caption and ANSI caption
1234			2dup menu_caption[x][y] unsetenv
1235			2dup ansi_caption[x][y] unsetenv
1236			1+ dup 57 >
1237		until
1238		drop \ inner iterator
1239
1240		0 over menukeyN      !	\ used by menu-create, menu-display
1241		0 over init_stateN   !	\ used by menu-create
1242		0 over toggle_stateN !	\ used by toggle_menuitem
1243		0 over init_textN   c!	\ used by toggle_menuitem
1244		0 over cycle_stateN  !	\ used by cycle_menuitem
1245
1246		1+ dup 56 >	\ increment, continue if less than 57
1247	until
1248	drop \ iterator
1249
1250	s" menu_timeout_command" unsetenv	\ menu timeout command
1251	s" menu_reboot"          unsetenv	\ Reboot menu option flag
1252	s" menu_acpi"            unsetenv	\ ACPI menu option flag
1253	s" menu_kernel"          unsetenv	\ Kernel menu option flag
1254	s" menu_options"         unsetenv	\ Options separator flag
1255	s" menu_optionstext"     unsetenv	\ separator display text
1256	s" menu_init"            unsetenv	\ menu initializer
1257
1258	0 menureboot !
1259	0 menuacpi !
1260	0 menuoptions !
1261;
1262
1263only forth definitions also menu-infrastructure
1264
1265\ This function both unsets menu variables and visually erases the menu area
1266\ in-preparation for another menu.
1267\ 
1268: menu-clear ( -- )
1269	menu-unset
1270	menu-erase
1271;
1272
1273bullet menubllt !
1274
1275also menu-namespace
1276
1277\ Initialize our menu initialization state variables
12780 init_state1 !
12790 init_state2 !
12800 init_state3 !
12810 init_state4 !
12820 init_state5 !
12830 init_state6 !
12840 init_state7 !
12850 init_state8 !
1286
1287\ Initialize our boolean state variables
12880 toggle_state1 !
12890 toggle_state2 !
12900 toggle_state3 !
12910 toggle_state4 !
12920 toggle_state5 !
12930 toggle_state6 !
12940 toggle_state7 !
12950 toggle_state8 !
1296
1297\ Initialize our array state variables
12980 cycle_state1 !
12990 cycle_state2 !
13000 cycle_state3 !
13010 cycle_state4 !
13020 cycle_state5 !
13030 cycle_state6 !
13040 cycle_state7 !
13050 cycle_state8 !
1306
1307\ Initialize string containers
13080 init_text1 c!
13090 init_text2 c!
13100 init_text3 c!
13110 init_text4 c!
13120 init_text5 c!
13130 init_text6 c!
13140 init_text7 c!
13150 init_text8 c!
1316
1317only forth definitions
1318