1128709Sru/*
2128709Sru * Copyright (c) 1998 Robert Nordier
3128709Sru * All rights reserved.
4128709Sru *
5128709Sru * Redistribution and use in source and binary forms are freely
6128709Sru * permitted provided that the above copyright notice and this
7128709Sru * paragraph and the following disclaimer are duplicated in all
8128709Sru * such forms.
9128709Sru *
10128709Sru * This software is provided "AS IS" and without any express or
11128709Sru * implied warranties, including, without limitation, the implied
12128709Sru * warranties of merchantability and fitness for a particular
13128709Sru * purpose.
14128709Sru *
15128709Sru * $FreeBSD$
16128709Sru */
1739091Srnordier
18237756Savg#include <bootargs.h>
19237756Savg
20185779Ssobomax#define	RBX_MUTE	0x10	/* -m */
21185779Ssobomax#define	OPT_SET(opt)	(1 << (opt))
22185779Ssobomax
23128709Sru/*
24128709Sru * Prototype BTX loader program, written in a couple of hours.  The
25128709Sru * real thing should probably be more flexible, and in C.
26128709Sru */
2739091Srnordier
28128709Sru/*
29128709Sru * Memory locations.
30128709Sru */
31129240Sru		.set MEM_STUB,0x600		# Real mode stub
32129240Sru		.set MEM_ESP,0x1000		# New stack pointer
33129240Sru		.set MEM_TBL,0x5000		# BTX page tables
34129240Sru		.set MEM_ENTRY,0x9010		# BTX entry point
35129240Sru		.set MEM_DATA,start+0x1000	# Data segment
36128709Sru/*
37128709Sru * Segment selectors.
38128709Sru */
39129240Sru		.set SEL_SCODE,0x8		# 4GB code
40129240Sru		.set SEL_SDATA,0x10		# 4GB data
41129240Sru		.set SEL_RCODE,0x18		# 64K code
42129240Sru		.set SEL_RDATA,0x20		# 64K data
43128709Sru/*
44128709Sru * Paging constants.
45128709Sru */
46129240Sru		.set PAG_SIZ,0x1000		# Page size
47129240Sru		.set PAG_ENT,0x4		# Page entry size
48128709Sru/*
49128709Sru * Screen constants.
50128709Sru */
51129240Sru		.set SCR_MAT,0x7		# Mode/attribute
52129240Sru		.set SCR_COL,0x50		# Columns per row
53129240Sru		.set SCR_ROW,0x19		# Rows per screen
54128709Sru/*
55128709Sru * BIOS Data Area locations.
56128709Sru */
57129240Sru		.set BDA_MEM,0x413		# Free memory
58129240Sru		.set BDA_SCR,0x449		# Video mode
59129240Sru		.set BDA_POS,0x450		# Cursor position
60128709Sru/*
61128709Sru * Required by aout gas inadequacy.
62128709Sru */
63129240Sru		.set SIZ_STUB,0x1a		# Size of stub
64128709Sru/*
65128709Sru * We expect to be loaded by boot2 at the origin defined in ./Makefile.
66128709Sru */
6739091Srnordier		.globl start
68128709Sru/*
69128709Sru * BTX program loader for ELF clients.
70128709Sru */
71129240Srustart:		cld				# String ops inc
72185780Ssobomax		testl $OPT_SET(RBX_MUTE), 4(%esp) # Check first argument
73185780Ssobomax		setnz muted			#  for RBX_MUTE, set flag
74129240Sru		movl $m_logo,%esi		# Identify
75129240Sru		call putstr			#  ourselves
76129240Sru		movzwl BDA_MEM,%eax		# Get base memory
77129240Sru		shll $0xa,%eax			#  in bytes
78129240Sru		movl %eax,%ebp			# Base of user stack
79125693Sru#ifdef BTXLDR_VERBOSE
80129240Sru		movl $m_mem,%esi		# Display
81129240Sru		call hexout			#  amount of
82129240Sru		call putstr			#  base memory
83125693Sru#endif
84129240Sru		lgdt gdtdesc			# Load new GDT
85128709Sru/*
86128709Sru * Relocate caller's arguments.
87128709Sru */
88125693Sru#ifdef BTXLDR_VERBOSE
89129240Sru		movl $m_esp,%esi		# Display
90129240Sru		movl %esp,%eax			#  caller
91129240Sru		call hexout			#  stack
92129240Sru		call putstr			#  pointer
93129240Sru		movl $m_args,%esi		# Format string
94237756Savg		leal 0x4(%esp),%ebx		# First argument
95129240Sru		movl $0x6,%ecx			# Count
96129240Srustart.1:	movl (%ebx),%eax		# Get argument and
97129240Sru		addl $0x4,%ebx			#  bump pointer
98129240Sru		call hexout			# Display it
99129240Sru		loop start.1			# Till done
100129240Sru		call putstr			# End message
101125693Sru#endif
102237756Savg		movl BA_BOOTINFO+4(%esp),%esi	# Source: bootinfo
103129240Sru		cmpl $0x0, %esi			# If the bootinfo pointer
104129240Sru		je start_null_bi		#  is null, don't copy it
105237756Savg		movl BI_SIZE(%esi),%ecx 	# Allocate space
106237756Savg		subl %ecx,%ebp			#  for bootinfo
107129240Sru		movl %ebp,%edi			# Destination
108129240Sru		rep				# Copy
109129240Sru		movsb				#  it
110237756Savg		movl %ebp,BA_BOOTINFO+4(%esp)	# Update pointer
111237756Savg		movl %edi,%ebp			# Restore base pointer
112125693Sru#ifdef BTXLDR_VERBOSE
113129240Sru		movl $m_rel_bi,%esi		# Display
114129240Sru		movl %ebp,%eax			#  bootinfo
115129240Sru		call hexout			#  relocation
116129240Sru		call putstr			#  message
117125693Sru#endif
118237756Savgstart_null_bi:	movl $BOOTARGS_SIZE,%ecx 	# Fixed size of arguments
119237756Savg		testl $KARGS_FLAGS_EXTARG, BA_BOOTFLAGS+4(%esp) # Check for extra data
120237756Savg		jz start_fixed			# Skip if the flag is not set
121237756Savg		addl BOOTARGS_SIZE+4(%esp),%ecx	# Add size of variable args
122237756Savgstart_fixed:	subl $ARGOFF,%ebp		# Place args at fixed offset
123237756Savg		leal 0x4(%esp),%esi		# Source
124129240Sru		movl %ebp,%edi			# Destination
125129240Sru		rep				# Copy
126129240Sru		movsb				#  them
127125693Sru#ifdef BTXLDR_VERBOSE
128129240Sru		movl $m_rel_args,%esi		# Display
129129240Sru		movl %ebp,%eax			#  argument
130129240Sru		call hexout			#  relocation
131129240Sru		call putstr			#  message
132125693Sru#endif
133128709Sru/*
134128709Sru * Set up BTX kernel.
135128709Sru */
136129240Sru		movl $MEM_ESP,%esp		# Set up new stack
137129240Sru		movl $MEM_DATA,%ebx		# Data segment
138129240Sru		movl $m_vers,%esi		# Display BTX
139129240Sru		call putstr			#  version message
140129240Sru		movb 0x5(%ebx),%al		# Get major version
141129240Sru		addb $'0',%al			# Display
142129240Sru		call putchr			#  it
143129240Sru		movb $'.',%al			# And a
144129240Sru		call putchr			#  dot
145129240Sru		movb 0x6(%ebx),%al		# Get minor
146129240Sru		xorb %ah,%ah			#  version
147129240Sru		movb $0xa,%dl			# Divide
148129240Sru		divb %dl,%al			#  by 10
149129240Sru		addb $'0',%al			# Display
150129240Sru		call putchr			#  tens
151129240Sru		movb %ah,%al			# Get units
152129240Sru		addb $'0',%al			# Display
153129240Sru		call putchr			#  units
154129240Sru		call putstr			# End message
155129240Sru		movl %ebx,%esi			# BTX image
156129240Sru		movzwl 0x8(%ebx),%edi		# Compute
157129240Sru		orl $PAG_SIZ/PAG_ENT-1,%edi	#  the
158129240Sru		incl %edi			#  BTX
159129240Sru		shll $0x2,%edi			#  load
160129240Sru		addl $MEM_TBL,%edi		#  address
161129240Sru		pushl %edi			# Save load address
162129240Sru		movzwl 0xa(%ebx),%ecx		# Image size
163125693Sru#ifdef BTXLDR_VERBOSE
164129240Sru		pushl %ecx			# Save image size
165125693Sru#endif
166129240Sru		rep				# Relocate
167129240Sru		movsb				#  BTX
168129240Sru		movl %esi,%ebx			# Keep place
169125693Sru#ifdef BTXLDR_VERBOSE
170129240Sru		movl $m_rel_btx,%esi		# Restore
171129240Sru		popl %eax			#  parameters
172129240Sru		call hexout			#  and
173125693Sru#endif
174129240Sru		popl %ebp			#  display
175125693Sru#ifdef BTXLDR_VERBOSE
176129240Sru		movl %ebp,%eax			#  the
177129240Sru		call hexout			#  relocation
178129240Sru		call putstr			#  message
179125693Sru#endif
180129240Sru		addl $PAG_SIZ,%ebp		# Display
181125693Sru#ifdef BTXLDR_VERBOSE
182129240Sru		movl $m_base,%esi		#  the
183129240Sru		movl %ebp,%eax			#  user
184129240Sru		call hexout			#  base
185129240Sru		call putstr			#  address
186125693Sru#endif
187128709Sru/*
188128709Sru * Set up ELF-format client program.
189128709Sru */
190129240Sru		cmpl $0x464c457f,(%ebx) 	# ELF magic number?
191129240Sru		je start.3			# Yes
192129240Sru		movl $e_fmt,%esi		# Display error
193129240Sru		call putstr			#  message
194129240Srustart.2:	jmp start.2			# Hang
19558713Sjhbstart.3:
196125693Sru#ifdef BTXLDR_VERBOSE
197129240Sru		movl $m_elf,%esi		# Display ELF
198129240Sru		call putstr			#  message
199129240Sru		movl $m_segs,%esi		# Format string
200125693Sru#endif
201129240Sru		movl $0x2,%edi			# Segment count
202129240Sru		movl 0x1c(%ebx),%edx		# Get e_phoff
203129240Sru		addl %ebx,%edx			# To pointer
204129240Sru		movzwl 0x2c(%ebx),%ecx		# Get e_phnum
205129240Srustart.4:	cmpl $0x1,(%edx)		# Is p_type PT_LOAD?
206129240Sru		jne start.6			# No
207125693Sru#ifdef BTXLDR_VERBOSE
208129240Sru		movl 0x4(%edx),%eax		# Display
209129240Sru		call hexout			#  p_offset
210129240Sru		movl 0x8(%edx),%eax		# Display
211129240Sru		call hexout			#  p_vaddr
212129240Sru		movl 0x10(%edx),%eax		# Display
213129240Sru		call hexout			#  p_filesz
214129240Sru		movl 0x14(%edx),%eax		# Display
215129240Sru		call hexout			#  p_memsz
216129240Sru		call putstr			# End message
217125693Sru#endif
218129240Sru		pushl %esi			# Save
219129240Sru		pushl %edi			#  working
220129240Sru		pushl %ecx			#  registers
221129240Sru		movl 0x4(%edx),%esi		# Get p_offset
222129240Sru		addl %ebx,%esi			#  as pointer
223129240Sru		movl 0x8(%edx),%edi		# Get p_vaddr
224129240Sru		addl %ebp,%edi			#  as pointer
225129240Sru		movl 0x10(%edx),%ecx		# Get p_filesz
226129240Sru		rep				# Set up
227129240Sru		movsb				#  segment
228129240Sru		movl 0x14(%edx),%ecx		# Any bytes
229129240Sru		subl 0x10(%edx),%ecx		#  to zero?
230129240Sru		jz start.5			# No
231129240Sru		xorb %al,%al			# Then
232129240Sru		rep				#  zero
233129240Sru		stosb				#  them
234129240Srustart.5:	popl %ecx			# Restore
235129240Sru		popl %edi			#  working
236129240Sru		popl %esi			#  registers
237129240Sru		decl %edi			# Segments to do
238129240Sru		je start.7			# If none
239129240Srustart.6:	addl $0x20,%edx 		# To next entry
240129240Sru		loop start.4			# Till done
24158713Sjhbstart.7:
242125693Sru#ifdef BTXLDR_VERBOSE
243129240Sru		movl $m_done,%esi		# Display done
244129240Sru		call putstr			#  message
245125693Sru#endif
246129240Sru		movl $start.8,%esi		# Real mode stub
247129240Sru		movl $MEM_STUB,%edi		# Destination
248129240Sru		movl $start.9-start.8,%ecx	# Size
249129240Sru		rep				# Relocate
250129240Sru		movsb				#  it
251129240Sru		ljmp $SEL_RCODE,$MEM_STUB	# To 16-bit code
25260846Sjhb		.code16
253129240Srustart.8:	xorw %ax,%ax			# Data
254129240Sru		movb $SEL_RDATA,%al		#  selector
255129240Sru		movw %ax,%ss			# Reload SS
256129240Sru		movw %ax,%ds			# Reset
257129240Sru		movw %ax,%es			#  other
258129240Sru		movw %ax,%fs			#  segment
259129240Sru		movw %ax,%gs			#  limits
260129240Sru		movl %cr0,%eax			# Switch to
261129240Sru		decw %ax			#  real
262129240Sru		movl %eax,%cr0			#  mode
263129240Sru		ljmp $0,$MEM_ENTRY		# Jump to BTX entry point
26439091Srnordierstart.9:
26560846Sjhb		.code32
266128709Sru/*
267128709Sru * Output message [ESI] followed by EAX in hex.
268128709Sru */
269129240Sruhexout: 	pushl %eax			# Save
270129240Sru		call putstr			# Display message
271129240Sru		popl %eax			# Restore
272129240Sru		pushl %esi			# Save
273129240Sru		pushl %edi			#  caller's
274129240Sru		movl $buf,%edi			# Buffer
275129240Sru		pushl %edi			# Save
276129240Sru		call hex32			# To hex
277129240Sru		xorb %al,%al			# Terminate
278129240Sru		stosb				#  string
279129240Sru		popl %esi			# Restore
280129240Sruhexout.1:	lodsb				# Get a char
281129240Sru		cmpb $'0',%al			# Leading zero?
282129240Sru		je hexout.1			# Yes
283129240Sru		testb %al,%al			# End of string?
284129240Sru		jne hexout.2			# No
285129240Sru		decl %esi			# Undo
286129240Sruhexout.2:	decl %esi			# Adjust for inc
287129240Sru		call putstr			# Display hex
288129240Sru		popl %edi			# Restore
289129240Sru		popl %esi			#  caller's
290129240Sru		ret				# To caller
291128709Sru/*
292128709Sru * Output zero-terminated string [ESI] to the console.
293128709Sru */
294129240Sruputstr.0:	call putchr			# Output char
295129240Sruputstr: 	lodsb				# Load char
296129240Sru		testb %al,%al			# End of string?
297129240Sru		jne putstr.0			# No
298129240Sru		ret				# To caller
299128709Sru/*
300128709Sru * Output character AL to the console.
301128709Sru */
302185780Ssobomaxputchr:		testb $1,muted			# Check muted
303185780Ssobomax		jnz putchr.5			#  do a nop
304185781Ssobomax		pusha				# Save
305129240Sru		xorl %ecx,%ecx			# Zero for loops
306129240Sru		movb $SCR_MAT,%ah		# Mode/attribute
307129240Sru		movl $BDA_POS,%ebx		# BDA pointer
308129240Sru		movw (%ebx),%dx 		# Cursor position
309129240Sru		movl $0xb8000,%edi		# Regen buffer (color)
310129240Sru		cmpb %ah,BDA_SCR-BDA_POS(%ebx)	# Mono mode?
311129240Sru		jne putchr.1			# No
312129240Sru		xorw %di,%di			# Regen buffer (mono)
313129240Sruputchr.1:	cmpb $0xa,%al			# New line?
314129240Sru		je putchr.2			# Yes
315129240Sru		xchgl %eax,%ecx 		# Save char
316129240Sru		movb $SCR_COL,%al		# Columns per row
317129240Sru		mulb %dh			#  * row position
318129240Sru		addb %dl,%al			#  + column
319129240Sru		adcb $0x0,%ah			#  position
320129240Sru		shll %eax			#  * 2
321129240Sru		xchgl %eax,%ecx 		# Swap char, offset
322129240Sru		movw %ax,(%edi,%ecx,1)		# Write attr:char
323129240Sru		incl %edx			# Bump cursor
324129240Sru		cmpb $SCR_COL,%dl		# Beyond row?
325129240Sru		jb putchr.3			# No
326129240Sruputchr.2:	xorb %dl,%dl			# Zero column
327129240Sru		incb %dh			# Bump row
328129240Sruputchr.3:	cmpb $SCR_ROW,%dh		# Beyond screen?
329129240Sru		jb putchr.4			# No
330129240Sru		leal 2*SCR_COL(%edi),%esi	# New top line
331129240Sru		movw $(SCR_ROW-1)*SCR_COL/2,%cx # Words to move
332129240Sru		rep				# Scroll
333129240Sru		movsl				#  screen
334129240Sru		movb $' ',%al			# Space
335129240Sru		movb $SCR_COL,%cl		# Columns to clear
336129240Sru		rep				# Clear
337129240Sru		stosw				#  line
338129240Sru		movb $SCR_ROW-1,%dh		# Bottom line
339129240Sruputchr.4:	movw %dx,(%ebx) 		# Update position
340129240Sru		popa				# Restore
341185780Ssobomaxputchr.5:	ret				# To caller
342128709Sru/*
343128709Sru * Convert EAX, AX, or AL to hex, saving the result to [EDI].
344128709Sru */
345129240Sruhex32:		pushl %eax			# Save
346129240Sru		shrl $0x10,%eax 		# Do upper
347129240Sru		call hex16			#  16
348129240Sru		popl %eax			# Restore
349129240Sruhex16:		call hex16.1			# Do upper 8
350129240Sruhex16.1:	xchgb %ah,%al			# Save/restore
351129240Sruhex8:		pushl %eax			# Save
352129240Sru		shrb $0x4,%al			# Do upper
353129240Sru		call hex8.1			#  4
354129240Sru		popl %eax			# Restore
355129240Sruhex8.1: 	andb $0xf,%al			# Get lower 4
356129240Sru		cmpb $0xa,%al			# Convert
357129240Sru		sbbb $0x69,%al			#  to hex
358129240Sru		das				#  digit
359129240Sru		orb $0x20,%al			# To lower case
360129240Sru		stosb				# Save char
361129240Sru		ret				# (Recursive)
36239091Srnordier
36339091Srnordier		.data
36439091Srnordier		.p2align 4
365128709Sru/*
366128709Sru * Global descriptor table.
367128709Sru */
368129240Srugdt:		.word 0x0,0x0,0x0,0x0		# Null entry
369129240Sru		.word 0xffff,0x0,0x9a00,0xcf	# SEL_SCODE
370129240Sru		.word 0xffff,0x0,0x9200,0xcf	# SEL_SDATA
371129240Sru		.word 0xffff,0x0,0x9a00,0x0	# SEL_RCODE
372129240Sru		.word 0xffff,0x0,0x9200,0x0	# SEL_RDATA
37339091Srnordiergdt.1:
374129240Srugdtdesc:	.word gdt.1-gdt-1		# Limit
375129240Sru		.long gdt			# Base
376128709Sru/*
377128709Sru * Messages.
378128709Sru */
37952148Sbrianm_logo: 	.asciz " \nBTX loader 1.00  "
38040745Smsmithm_vers: 	.asciz "BTX version is \0\n"
38140745Smsmithe_fmt:		.asciz "Error: Client format not supported\n"
382125693Sru#ifdef BTXLDR_VERBOSE
38339091Srnordierm_mem:		.asciz "Starting in protected mode (base mem=\0)\n"
38439091Srnordierm_esp:		.asciz "Arguments passed (esp=\0):\n"
38539091Srnordierm_args: 	.asciz"<howto="
38639091Srnordier		.asciz" bootdev="
38739091Srnordier		.asciz" junk="
38839091Srnordier		.asciz" "
38939091Srnordier		.asciz" "
39039091Srnordier		.asciz" bootinfo=\0>\n"
39139091Srnordierm_rel_bi:	.asciz "Relocated bootinfo (size=48) to \0\n"
39239091Srnordierm_rel_args:	.asciz "Relocated arguments (size=18) to \0\n"
39339091Srnordierm_rel_btx:	.asciz "Relocated kernel (size=\0) to \0\n"
39439091Srnordierm_base: 	.asciz "Client base address is \0\n"
39539091Srnordierm_elf:		.asciz "Client format is ELF\n"
39639091Srnordierm_segs: 	.asciz "text segment: offset="
39739091Srnordier		.asciz " vaddr="
39839091Srnordier		.asciz " filesz="
39939091Srnordier		.asciz " memsz=\0\n"
40039091Srnordier		.asciz "data segment: offset="
40139091Srnordier		.asciz " vaddr="
40239091Srnordier		.asciz " filesz="
40339091Srnordier		.asciz " memsz=\0\n"
40439091Srnordierm_done: 	.asciz "Loading complete\n"
405125693Sru#endif
406185779Ssobomax
407128709Sru/*
408185779Ssobomax * Flags
409185779Ssobomax */
410185779Ssobomaxmuted:		.byte 0x0
411185779Ssobomax
412185779Ssobomax/*
413128709Sru * Uninitialized data area.
414128709Sru */
415129240Srubuf:						# Scratch buffer
416