menu.4th revision 280974
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 280974 2015-04-02 01:46:17Z 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: " strcat
399		kernmenuidx @ [char] 0 = if
400			s" default/[32m"
401		else
402			s" [34;1m"
403		then strcat
404		2over strcat
405		s" [37m" strcat
406		kernidx @ kernmenuidx @ ansi_caption[x][y]
407		setenv
408
409		2drop ( c-addr/u c-addr/u2 -- c-addr/u )
410
411		kernmenuidx @ 1+ dup kernmenuidx ! [char] 8 > if
412			2drop ( c-addr/u -- ) exit
413		then
414
415		kernlen @ - swap kernlen @ + swap ( c-addr/u -- c-addr'/u' )
416	again
417;
418
419\ This function goes through the kernels that were discovered by the
420\ parse-kernels function [above], adding " (# of #)" text to the end of each
421\ caption.
422\ 
423: tag-kernels ( -- )
424	kernidx @ ( -- x ) dup 0= if exit then
425	[char] 0 s"  (Y of Z)" ( x -- x y c-addr/u )
426	kernmenuidx @ -rot 7 +c! \ Replace 'Z' with number of kernels parsed
427	begin
428		2 pick 1+ -rot 2 +c! \ Replace 'Y' with current ASCII num
429
430		2over menu_caption[x][y] getenv dup -1 <> if
431			2dup + 1- c@ [char] ) = if
432				2drop \ Already tagged
433			else
434				kerncapbuf 0 2swap strcat
435				2over strcat
436				5 pick 5 pick menu_caption[x][y] setenv
437			then
438		else
439			drop ( getenv cruft )
440		then
441
442		2over ansi_caption[x][y] getenv dup -1 <> if
443			2dup + 1- c@ [char] ) = if
444				2drop \ Already tagged
445			else
446				kerncapbuf 0 2swap strcat
447				2over strcat
448				5 pick 5 pick ansi_caption[x][y] setenv
449			then
450		else
451			drop ( getenv cruft )
452		then
453
454		rot 1+ dup [char] 8 > if
455			-rot 2drop TRUE ( break )
456		else
457			-rot FALSE
458		then
459	until
460	2drop ( x y -- )
461;
462
463\ This function creates the list of menu items. This function is called by the
464\ menu-display function. You need not call it directly.
465\ 
466: menu-create ( -- )
467
468	\ Print the frame caption at (x,y)
469	s" loader_menu_title" getenv dup -1 = if
470		drop s" Welcome to FreeBSD"
471	then
472	TRUE ( use default alignment )
473	s" loader_menu_title_align" getenv dup -1 <> if
474		2dup s" left" compare-insensitive 0= if ( 1 )
475			2drop ( c-addr/u ) drop ( bool )
476			menuX @ menuY @ 1-
477			FALSE ( don't use default alignment )
478		else ( 1 ) 2dup s" right" compare-insensitive 0= if ( 2 )
479			2drop ( c-addr/u ) drop ( bool )
480			menuX @ 42 + 4 - over - menuY @ 1-
481			FALSE ( don't use default alignment )
482		else ( 2 ) 2drop ( c-addr/u ) then ( 1 ) then
483	else
484		drop ( getenv cruft )
485	then
486	if ( use default center alignement? )
487		menuX @ 19 + over 2 / - menuY @ 1-
488	then
489	at-xy type 
490
491	\ If $menu_init is set, evaluate it (allowing for whole menus to be
492	\ constructed dynamically -- as this function could conceivably set
493	\ the remaining environment variables to construct the menu entirely).
494	\ 
495	s" menu_init" getenv dup -1 <> if
496		evaluate
497	else
498		drop
499	then
500
501	\ Print our menu options with respective key/variable associations.
502	\ `printmenuitem' ends by adding the decimal ASCII value for the
503	\ numerical prefix to the stack. We store the value left on the stack
504	\ to the key binding variable for later testing against a character
505	\ captured by the `getkey' function.
506
507	\ Note that any menu item beyond 9 will have a numerical prefix on the
508	\ screen consisting of the first digit (ie. 1 for the tenth menu item)
509	\ and the key required to activate that menu item will be the decimal
510	\ ASCII of 48 plus the menu item (ie. 58 for the tenth item, aka. `:')
511	\ which is misleading and not desirable.
512	\ 
513	\ Thus, we do not allow more than 8 configurable items on the menu
514	\ (with "Reboot" as the optional ninth and highest numbered item).
515
516	\ 
517	\ Initialize the ACPI option status.
518	\ 
519	0 menuacpi !
520	s" menu_acpi" getenv -1 <> if
521		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
522			menuacpi !
523			arch-i386? if acpipresent? if
524				\ 
525				\ Set menu toggle state to active state
526				\ (required by generic toggle_menuitem)
527				\ 
528				acpienabled? menuacpi @ toggle_stateN !
529			then then
530		else
531			drop
532		then
533	then
534
535	\ 
536	\ Initialize kernel captions after parsing $kernels
537	\ 
538	0 menukernel !
539	s" menu_kernel" getenv -1 <> if
540		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
541			dup menukernel !
542			dup parse-kernels tag-kernels
543
544			\ Get the current cycle state (entry to use)
545			s" kernel_state" evaluate @ 48 + ( n -- n y )
546
547			\ If state is invalid, reset
548			dup kernmenuidx @ 1- > if
549				drop [char] 0 ( n y -- n 48 )
550				0 s" kernel_state" evaluate !
551				over s" init_kernel" evaluate drop
552			then
553
554			\ Set the current non-ANSI caption
555			2dup swap dup ( n y -- n y y n n )
556			s" set menu_caption[x]=$menu_caption[x][y]"
557			17 +c! 34 +c! 37 +c! evaluate
558			( n y y n n c-addr/u -- n y  )
559
560			\ Set the current ANSI caption
561			2dup swap dup ( n y -- n y y n n )
562			s" set ansi_caption[x]=$ansi_caption[x][y]"
563			17 +c! 34 +c! 37 +c! evaluate
564			( n y y n n c-addr/u -- n y )
565
566			\ Initialize cycle state from stored value
567			48 - ( n y -- n k )
568			s" init_cyclestate" evaluate ( n k -- n )
569
570			\ Set $kernel to $kernel[y]
571			s" activate_kernel" evaluate ( n -- n )
572		then
573		drop
574	then
575
576	\ 
577	\ Initialize the menu_options visual separator.
578	\ 
579	0 menuoptions !
580	s" menu_options" getenv -1 <> if
581		c@ dup 48 > over 57 < and if ( '1' <= c1 <= '8' )
582			menuoptions !
583		else
584			drop
585		then
586	then
587
588	\ Initialize "Reboot" menu state variable (prevents double-entry)
589	false menurebootadded !
590
591	menu_start
592	1- menuidx !    \ Initialize the starting index for the menu
593	0 menurow !     \ Initialize the starting position for the menu
594
595	49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
596	begin
597		\ If the "Options:" separator, print it.
598		dup menuoptions @ = if
599			\ Optionally add a reboot option to the menu
600			s" menu_reboot" getenv -1 <> if
601				drop
602				s" Reboot" printmenuitem menureboot !
603				true menurebootadded !
604			then
605
606			menuX @
607			menurow @ 2 + menurow !
608			menurow @ menuY @ +
609			at-xy
610			s" menu_optionstext" getenv dup -1 <> if
611				type
612			else
613				drop ." Options:"
614			then
615		then
616
617		\ If this is the ACPI menu option, act accordingly.
618		dup menuacpi @ = if
619			dup acpimenuitem ( n -- n n c-addr/u | n n -1 )
620			dup -1 <> if
621				13 +c! ( n n c-addr/u -- n c-addr/u )
622				       \ replace 'x' with n
623			else
624				swap drop ( n n -1 -- n -1 )
625				over menu_command[x] unsetenv
626			then
627		else
628			\ make sure we have not already initialized this item
629			dup init_stateN dup @ 0= if
630				1 swap !
631
632				\ If this menuitem has an initializer, run it
633				dup menu_init[x]
634				getenv dup -1 <> if
635					evaluate
636				else
637					drop
638				then
639			else
640				drop
641			then
642
643			dup
644			loader_color? if
645				ansi_caption[x]
646			else
647				menu_caption[x]
648			then
649		then
650
651		dup -1 <> if
652			\ test for environment variable
653			getenv dup -1 <> if
654				printmenuitem ( c-addr/u -- n )
655				dup menukeyN !
656			else
657				drop
658			then
659		else
660			drop
661		then
662
663		1+ dup 56 > \ add 1 to iterator, continue if less than 57
664	until
665	drop \ iterator
666
667	\ Optionally add a reboot option to the menu
668	menurebootadded @ true <> if
669		s" menu_reboot" getenv -1 <> if
670			drop       \ no need for the value
671			s" Reboot" \ menu caption (required by printmenuitem)
672
673			printmenuitem
674			menureboot !
675		else
676			0 menureboot !
677		then
678	then
679;
680
681\ Takes a single integer on the stack and updates the timeout display. The
682\ integer must be between 0 and 9 (we will only update a single digit in the
683\ source message).
684\ 
685: menu-timeout-update ( N -- )
686
687	\ Enforce minimum/maximum
688	dup 9 > if drop 9 then
689	dup 0 < if drop 0 then
690
691	s" Autoboot in N seconds. [Space] to pause" ( n -- n c-addr/u )
692
693	2 pick 0> if
694		rot 48 + -rot ( n c-addr/u -- n' c-addr/u ) \ convert to ASCII
695		12 +c!        ( n' c-addr/u -- c-addr/u )   \ replace 'N' above
696
697		menu_timeout_x @ menu_timeout_y @ at-xy \ position cursor
698		type ( c-addr/u -- ) \ print message
699	else
700		menu_timeout_x @ menu_timeout_y @ at-xy \ position cursor
701		spaces ( n c-addr/u -- n c-addr ) \ erase message
702		2drop ( n c-addr -- )
703	then
704
705	0 25 at-xy ( position cursor back at bottom-left )
706;
707
708\ This function blocks program flow (loops forever) until a key is pressed.
709\ The key that was pressed is added to the top of the stack in the form of its
710\ decimal ASCII representation. This function is called by the menu-display
711\ function. You need not call it directly.
712\ 
713: getkey ( -- ascii_keycode )
714
715	begin \ loop forever
716
717		menu_timeout_enabled @ 1 = if
718			( -- )
719			seconds ( get current time: -- N )
720			dup menu_time @ <> if ( has time elapsed?: N N N -- N )
721
722				\ At least 1 second has elapsed since last loop
723				\ so we will decrement our "timeout" (really a
724				\ counter, insuring that we do not proceed too
725				\ fast) and update our timeout display.
726
727				menu_time ! ( update time record: N -- )
728				menu_timeout @ ( "time" remaining: -- N )
729				dup 0> if ( greater than 0?: N N 0 -- N )
730					1- ( decrement counter: N -- N )
731					dup menu_timeout !
732						( re-assign: N N Addr -- N )
733				then
734				( -- N )
735
736				dup 0= swap 0< or if ( N <= 0?: N N -- )
737					\ halt the timer
738					0 menu_timeout ! ( 0 Addr -- )
739					0 menu_timeout_enabled ! ( 0 Addr -- )
740				then
741
742				\ update the timer display ( N -- )
743				menu_timeout @ menu-timeout-update
744
745				menu_timeout @ 0= if
746					\ We've reached the end of the timeout
747					\ (user did not cancel by pressing ANY
748					\ key)
749
750					s" menu_timeout_command"  getenv dup
751					-1 = if
752						drop \ clean-up
753					else
754						evaluate
755					then
756				then
757
758			else ( -- N )
759				\ No [detectable] time has elapsed (in seconds)
760				drop ( N -- )
761			then
762			( -- )
763		then
764
765		key? if \ Was a key pressed? (see loader(8))
766
767			\ An actual key was pressed (if the timeout is running,
768			\ kill it regardless of which key was pressed)
769			menu_timeout @ 0<> if
770				0 menu_timeout !
771				0 menu_timeout_enabled !
772
773				\ clear screen of timeout message
774				0 menu-timeout-update
775			then
776
777			\ get the key that was pressed and exit (if we
778			\ get a non-zero ASCII code)
779			key dup 0<> if
780				exit
781			else
782				drop
783			then
784		then
785		50 ms \ sleep for 50 milliseconds (see loader(8))
786
787	again
788;
789
790: menu-erase ( -- ) \ Erases menu and resets positioning variable to positon 1.
791
792	\ Clear the screen area associated with the interactive menu
793	menuX @ menuY @
794	2dup at-xy 38 spaces 1+		2dup at-xy 38 spaces 1+
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
800	2drop
801
802	\ Reset the starting index and position for the menu
803	menu_start 1- menuidx !
804	0 menurow !
805;
806
807only forth
808also menu-infrastructure
809also menu-namespace
810also menu-command-helpers definitions
811
812: toggle_menuitem ( N -- N ) \ toggles caption text and internal menuitem state
813
814	\ ASCII numeral equal to user-selected menu item must be on the stack.
815	\ We do not modify the stack, so the ASCII numeral is left on top.
816
817	dup init_textN c@ 0= if
818		\ NOTE: no need to check toggle_stateN since the first time we
819		\ are called, we will populate init_textN. Further, we don't
820		\ need to test whether menu_caption[x] (ansi_caption[x] when
821		\ loader_color?=1) is available since we would not have been
822		\ called if the caption was NULL.
823
824		\ base name of environment variable
825		dup ( n -- n n ) \ key pressed
826		loader_color? if
827			ansi_caption[x]
828		else
829			menu_caption[x]
830		then	
831		getenv dup -1 <> if
832
833			2 pick ( n c-addr/u -- n c-addr/u n )
834			init_textN ( n c-addr/u n -- n c-addr/u c-addr )
835
836			\ now we have the buffer c-addr on top
837			\ ( followed by c-addr/u of current caption )
838
839			\ Copy the current caption into our buffer
840			2dup c! -rot \ store strlen at first byte
841			begin
842				rot 1+    \ bring alt addr to top and increment
843				-rot -rot \ bring buffer addr to top
844				2dup c@ swap c! \ copy current character
845				1+     \ increment buffer addr
846				rot 1- \ bring buffer len to top and decrement
847				dup 0= \ exit loop if buffer len is zero
848			until
849			2drop \ buffer len/addr
850			drop  \ alt addr
851
852		else
853			drop
854		then
855	then
856
857	\ Now we are certain to have init_textN populated with the initial
858	\ value of menu_caption[x] (ansi_caption[x] with loader_color enabled).
859	\ We can now use init_textN as the untoggled caption and
860	\ toggled_text[x] (toggled_ansi[x] with loader_color enabled) as the
861	\ toggled caption and store the appropriate value into menu_caption[x]
862	\ (again, ansi_caption[x] with loader_color enabled). Last, we'll
863	\ negate the toggled state so that we reverse the flow on subsequent
864	\ calls.
865
866	dup toggle_stateN @ 0= if
867		\ state is OFF, toggle to ON
868
869		dup ( n -- n n ) \ key pressed
870		loader_color? if
871			toggled_ansi[x]
872		else
873			toggled_text[x]
874		then
875		getenv dup -1 <> if
876			\ Assign toggled text to menu caption
877			2 pick ( n c-addr/u -- n c-addr/u n ) \ key pressed
878			loader_color? if
879				ansi_caption[x]
880			else
881				menu_caption[x]
882			then
883			setenv
884		else
885			\ No toggled text, keep the same caption
886			drop ( n -1 -- n ) \ getenv cruft
887		then
888
889		true \ new value of toggle state var (to be stored later)
890	else
891		\ state is ON, toggle to OFF
892
893		dup init_textN count ( n -- n c-addr/u )
894
895		\ Assign init_textN text to menu caption
896		2 pick ( n c-addr/u -- n c-addr/u n ) \ key pressed
897		loader_color? if
898			ansi_caption[x]
899		else
900			menu_caption[x]
901		then
902		setenv
903
904		false \ new value of toggle state var (to be stored below)
905	then
906
907	\ now we'll store the new toggle state (on top of stack)
908	over toggle_stateN !
909;
910
911: cycle_menuitem ( N -- N ) \ cycles through array of choices for a menuitem
912
913	\ ASCII numeral equal to user-selected menu item must be on the stack.
914	\ We do not modify the stack, so the ASCII numeral is left on top.
915
916	dup cycle_stateN dup @ 1+ \ get value and increment
917
918	\ Before assigning the (incremented) value back to the pointer,
919	\ let's test for the existence of this particular array element.
920	\ If the element exists, we'll store index value and move on.
921	\ Otherwise, we'll loop around to zero and store that.
922
923	dup 48 + ( n addr k -- n addr k k' )
924	         \ duplicate array index and convert to ASCII numeral
925
926	3 pick swap ( n addr k k' -- n addr k n k' ) \ (n,k') as (x,y)
927	loader_color? if
928		ansi_caption[x][y]
929	else
930		menu_caption[x][y]
931	then
932	( n addr k n k' -- n addr k c-addr/u )
933
934	\ Now test for the existence of our incremented array index in the
935	\ form of $menu_caption[x][y] ($ansi_caption[x][y] with loader_color
936	\ enabled) as set in loader.rc(5), et. al.
937
938	getenv dup -1 = if
939		\ No caption set for this array index. Loop back to zero.
940
941		drop ( n addr k -1 -- n addr k ) \ getenv cruft
942		drop 0 ( n addr k -- n addr 0 )  \ new value to store later
943
944		2 pick [char] 0 ( n addr 0 -- n addr 0 n 48 ) \ (n,48) as (x,y)
945		loader_color? if
946			ansi_caption[x][y]
947		else
948			menu_caption[x][y]
949		then
950		( n addr 0 n 48 -- n addr 0 c-addr/u )
951		getenv dup -1 = if
952			\ Highly unlikely to occur, but to ensure things move
953			\ along smoothly, allocate a temporary NULL string
954			drop ( cruft ) s" "
955		then
956	then
957
958	\ At this point, we should have the following on the stack (in order,
959	\ from bottom to top):
960	\ 
961	\    n        - Ascii numeral representing the menu choice (inherited)
962	\    addr     - address of our internal cycle_stateN variable
963	\    k        - zero-based number we intend to store to the above
964	\    c-addr/u - string value we intend to store to menu_caption[x]
965	\               (or ansi_caption[x] with loader_color enabled)
966	\ 
967	\ Let's perform what we need to with the above.
968
969	\ Assign array value text to menu caption
970	4 pick ( n addr k c-addr/u -- n addr k c-addr/u n )
971	loader_color? if
972		ansi_caption[x]
973	else
974		menu_caption[x]
975	then
976	setenv
977
978	swap ! ( n addr k -- n ) \ update array state variable
979;
980
981only forth definitions also menu-infrastructure
982
983\ Erase and redraw the menu. Useful if you change a caption and want to
984\ update the menu to reflect the new value.
985\ 
986: menu-redraw ( -- )
987	menu-erase
988	menu-create
989;
990
991\ This function initializes the menu. Call this from your `loader.rc' file
992\ before calling any other menu-related functions.
993\ 
994: menu-init ( -- )
995	menu_start
996	1- menuidx !    \ Initialize the starting index for the menu
997	0 menurow !     \ Initialize the starting position for the menu
998
999	\ Assign configuration values
1000	s" loader_menu_y" getenv dup -1 = if
1001		drop \ no custom row position
1002		menu_default_y
1003	else
1004		\ make sure custom position is a number
1005		?number 0= if
1006			menu_default_y \ or use default
1007		then
1008	then
1009	menuY !
1010	s" loader_menu_x" getenv dup -1 = if
1011		drop \ no custom column position
1012		menu_default_x
1013	else
1014		\ make sure custom position is a number
1015		?number 0= if
1016			menu_default_x \ or use default
1017		then
1018	then
1019	menuX !
1020
1021	\ Interpret a custom frame type for the menu
1022	TRUE ( draw a box? default yes, but might be altered below )
1023	s" loader_menu_frame" getenv dup -1 = if ( 1 )
1024		drop \ no custom frame type
1025	else ( 1 )  2dup s" single" compare-insensitive 0= if ( 2 )
1026		f_single ( see frames.4th )
1027	else ( 2 )  2dup s" double" compare-insensitive 0= if ( 3 )
1028		f_double ( see frames.4th )
1029	else ( 3 ) s" none" compare-insensitive 0= if ( 4 )
1030		drop FALSE \ don't draw a box
1031	( 4 ) then ( 3 ) then ( 2 )  then ( 1 ) then
1032	if
1033		42 13 menuX @ 3 - menuY @ 1- box \ Draw frame (w,h,x,y)
1034	then
1035
1036	0 25 at-xy \ Move cursor to the bottom for output
1037;
1038
1039also menu-namespace
1040
1041\ Main function. Call this from your `loader.rc' file.
1042\ 
1043: menu-display ( -- )
1044
1045	0 menu_timeout_enabled ! \ start with automatic timeout disabled
1046
1047	\ check indication that automatic execution after delay is requested
1048	s" menu_timeout_command" getenv -1 <> if ( Addr C -1 -- | Addr )
1049		drop ( just testing existence right now: Addr -- )
1050
1051		\ initialize state variables
1052		seconds menu_time ! ( store the time we started )
1053		1 menu_timeout_enabled ! ( enable automatic timeout )
1054
1055		\ read custom time-duration (if set)
1056		s" autoboot_delay" getenv dup -1 = if
1057			drop \ no custom duration (remove dup'd bunk -1)
1058			menu_timeout_default \ use default setting
1059		else
1060			2dup ?number 0= if ( if not a number )
1061				\ disable timeout if "NO", else use default
1062				s" NO" compare-insensitive 0= if
1063					0 menu_timeout_enabled !
1064					0 ( assigned to menu_timeout below )
1065				else
1066					menu_timeout_default
1067				then
1068			else
1069				-rot 2drop
1070
1071				\ boot immediately if less than zero
1072				dup 0< if
1073					drop
1074					menu-create
1075					0 25 at-xy
1076					0 boot
1077				then
1078			then
1079		then
1080		menu_timeout ! ( store value on stack from above )
1081
1082		menu_timeout_enabled @ 1 = if
1083			\ read custom column position (if set)
1084			s" loader_menu_timeout_x" getenv dup -1 = if
1085				drop \ no custom column position
1086				menu_timeout_default_x \ use default setting
1087			else
1088				\ make sure custom position is a number
1089				?number 0= if
1090					menu_timeout_default_x \ or use default
1091				then
1092			then
1093			menu_timeout_x ! ( store value on stack from above )
1094        
1095			\ read custom row position (if set)
1096			s" loader_menu_timeout_y" getenv dup -1 = if
1097				drop \ no custom row position
1098				menu_timeout_default_y \ use default setting
1099			else
1100				\ make sure custom position is a number
1101				?number 0= if
1102					menu_timeout_default_y \ or use default
1103				then
1104			then
1105			menu_timeout_y ! ( store value on stack from above )
1106		then
1107	then
1108
1109	menu-create
1110
1111	begin \ Loop forever
1112
1113		0 25 at-xy \ Move cursor to the bottom for output
1114		getkey     \ Block here, waiting for a key to be pressed
1115
1116		dup -1 = if
1117			drop exit \ Caught abort (abnormal return)
1118		then
1119
1120		\ Boot if the user pressed Enter/Ctrl-M (13) or
1121		\ Ctrl-Enter/Ctrl-J (10)
1122		dup over 13 = swap 10 = or if
1123			drop ( no longer needed )
1124			s" boot" evaluate
1125			exit ( pedantic; never reached )
1126		then
1127
1128		dup menureboot @ = if 0 reboot then
1129
1130		\ Evaluate the decimal ASCII value against known menu item
1131		\ key associations and act accordingly
1132
1133		49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
1134		begin
1135			dup menukeyN @
1136			rot tuck = if
1137
1138				\ Adjust for missing ACPI menuitem on non-i386
1139				arch-i386? true <> menuacpi @ 0<> and if
1140					menuacpi @ over 2dup < -rot = or
1141					over 58 < and if
1142					( key >= menuacpi && key < 58: N -- N )
1143						1+
1144					then
1145				then
1146
1147				\ Test for the environment variable
1148				dup menu_command[x]
1149				getenv dup -1 <> if
1150					\ Execute the stored procedure
1151					evaluate
1152
1153					\ We expect there to be a non-zero
1154					\  value left on the stack after
1155					\ executing the stored procedure.
1156					\ If so, continue to run, else exit.
1157
1158					0= if
1159						drop \ key pressed
1160						drop \ loop iterator
1161						exit
1162					else
1163						swap \ need iterator on top
1164					then
1165				then
1166
1167				\ Re-adjust for missing ACPI menuitem
1168				arch-i386? true <> menuacpi @ 0<> and if
1169					swap
1170					menuacpi @ 1+ over 2dup < -rot = or
1171					over 59 < and if
1172						1-
1173					then
1174					swap
1175				then
1176			else
1177				swap \ need iterator on top
1178			then
1179
1180			\ 
1181			\ Check for menu keycode shortcut(s)
1182			\ 
1183			dup menu_keycode[x]
1184			getenv dup -1 = if
1185				drop
1186			else
1187				?number 0<> if
1188					rot tuck = if
1189						swap
1190						dup menu_command[x]
1191						getenv dup -1 <> if
1192							evaluate
1193							0= if
1194								2drop
1195								exit
1196							then
1197						else
1198							drop
1199						then
1200					else
1201						swap
1202					then
1203				then
1204			then
1205
1206			1+ dup 56 > \ increment iterator
1207			            \ continue if less than 57
1208		until
1209		drop \ loop iterator
1210		drop \ key pressed
1211
1212	again	\ Non-operational key was pressed; repeat
1213;
1214
1215\ This function unsets all the possible environment variables associated with
1216\ creating the interactive menu.
1217\ 
1218: menu-unset ( -- )
1219
1220	49 \ Iterator start (loop range 49 to 56; ASCII '1' to '8')
1221	begin
1222		dup menu_init[x]    unsetenv	\ menu initializer
1223		dup menu_command[x] unsetenv	\ menu command
1224		dup menu_caption[x] unsetenv	\ menu caption
1225		dup ansi_caption[x] unsetenv	\ ANSI caption
1226		dup menu_keycode[x] unsetenv	\ menu keycode
1227		dup toggled_text[x] unsetenv	\ toggle_menuitem caption
1228		dup toggled_ansi[x] unsetenv	\ toggle_menuitem ANSI caption
1229
1230		48 \ Iterator start (inner range 48 to 57; ASCII '0' to '9')
1231		begin
1232			\ cycle_menuitem caption and ANSI caption
1233			2dup menu_caption[x][y] unsetenv
1234			2dup ansi_caption[x][y] unsetenv
1235			1+ dup 57 >
1236		until
1237		drop \ inner iterator
1238
1239		0 over menukeyN      !	\ used by menu-create, menu-display
1240		0 over init_stateN   !	\ used by menu-create
1241		0 over toggle_stateN !	\ used by toggle_menuitem
1242		0 over init_textN   c!	\ used by toggle_menuitem
1243		0 over cycle_stateN  !	\ used by cycle_menuitem
1244
1245		1+ dup 56 >	\ increment, continue if less than 57
1246	until
1247	drop \ iterator
1248
1249	s" menu_timeout_command" unsetenv	\ menu timeout command
1250	s" menu_reboot"          unsetenv	\ Reboot menu option flag
1251	s" menu_acpi"            unsetenv	\ ACPI menu option flag
1252	s" menu_kernel"          unsetenv	\ Kernel menu option flag
1253	s" menu_options"         unsetenv	\ Options separator flag
1254	s" menu_optionstext"     unsetenv	\ separator display text
1255	s" menu_init"            unsetenv	\ menu initializer
1256
1257	0 menureboot !
1258	0 menuacpi !
1259	0 menuoptions !
1260;
1261
1262only forth definitions also menu-infrastructure
1263
1264\ This function both unsets menu variables and visually erases the menu area
1265\ in-preparation for another menu.
1266\ 
1267: menu-clear ( -- )
1268	menu-unset
1269	menu-erase
1270;
1271
1272bullet menubllt !
1273
1274also menu-namespace
1275
1276\ Initialize our menu initialization state variables
12770 init_state1 !
12780 init_state2 !
12790 init_state3 !
12800 init_state4 !
12810 init_state5 !
12820 init_state6 !
12830 init_state7 !
12840 init_state8 !
1285
1286\ Initialize our boolean state variables
12870 toggle_state1 !
12880 toggle_state2 !
12890 toggle_state3 !
12900 toggle_state4 !
12910 toggle_state5 !
12920 toggle_state6 !
12930 toggle_state7 !
12940 toggle_state8 !
1295
1296\ Initialize our array state variables
12970 cycle_state1 !
12980 cycle_state2 !
12990 cycle_state3 !
13000 cycle_state4 !
13010 cycle_state5 !
13020 cycle_state6 !
13030 cycle_state7 !
13040 cycle_state8 !
1305
1306\ Initialize string containers
13070 init_text1 c!
13080 init_text2 c!
13090 init_text3 c!
13100 init_text4 c!
13110 init_text5 c!
13120 init_text6 c!
13130 init_text7 c!
13140 init_text8 c!
1315
1316only forth definitions
1317