xref: /netbsd/sys/arch/i386/bioscall/biostramp.S (revision 6550d01e)
1/*	$NetBSD: biostramp.S,v 1.14 2008/04/28 20:23:23 martin Exp $	*/
2
3/*-
4 * Copyright (c) 1996 The NetBSD Foundation, Inc.
5 * All rights reserved.
6 *
7 * This code is derived from software contributed to The NetBSD Foundation
8 * by John Kohl.
9 *
10 * Redistribution and use in source and binary forms, with or without
11 * modification, are permitted provided that the following conditions
12 * are met:
13 * 1. Redistributions of source code must retain the above copyright
14 *    notice, this list of conditions and the following disclaimer.
15 * 2. Redistributions in binary form must reproduce the above copyright
16 *    notice, this list of conditions and the following disclaimer in the
17 *    documentation and/or other materials provided with the distribution.
18 *
19 * THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
20 * ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
21 * TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
22 * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE FOUNDATION OR CONTRIBUTORS
23 * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
24 * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
25 * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
26 * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
27 * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
28 * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
29 * POSSIBILITY OF SUCH DAMAGE.
30 */
31
32/*
33 * biostramp.S:		provide a means for NetBSD to call BIOS interrupts
34 *			by switching to real mode, calling it, and switching
35 *			back to protected & paging mode.
36 */
37
38/*
39 * Micro$haft's book on i386/i486 programming says you should do the following
40 * to return to real mode from protected mode:
41 *
42 * 1) disable paging, by jumping to code with identical virtual and physical
43 * addresses, clearing PG in CR0, and zeroing CR3 (PDBR).
44 *
45 * 2) segment descriptors must be byte-granular with limit 64k-1, def32 = 0,
46 * (i.e. 16-bit data accesses and/or 80286 instructions)
47 * CS must be executable; DS,ES,FS,GS should be writable
48 *
49 * 3) disable interrupts, load IDTR with original value (base 0, limit 1023)
50 *
51 * 4) clear PE in CR0, execute FAR jump to load CS.
52 *
53 * 5) load SP, and off you go
54 *
55 */
56
57#include "assym.h"
58
59#include <i386/include/param.h>
60#include <i386/include/specialreg.h>
61#include <i386/include/segments.h>
62#include <i386/include/apmvar.h>
63#include <i386/include/psl.h>
64#include <i386/include/asm.h>
65
66#define	addr32	.byte 0x67
67#define	data32	.byte 0x66
68
69	.set MYBASE,NBPG
70	.set MYSCRATCH,NBPG*2
71	.set CR3_ADDR,(MYSCRATCH-4)
72	.set IDTR_SAVE_ADDR,CR3_ADDR-6
73	.set GDTR_SAVE_ADDR,IDTR_SAVE_ADDR-6
74	.set GDTR_LOCAL_ADDR,GDTR_SAVE_ADDR-6
75	.set STACK_PTR_ADDR,GDTR_LOCAL_ADDR-4
76	.set BASE_PTR_ADDR,STACK_PTR_ADDR-4
77	.set FUNCTION_ADDR,(BASE_PTR_ADDR-2)
78	.set GDT_COPY_ADDR,(FUNCTION_ADDR-NGDT*8)
79	.set EAX_REGADDR,(GDT_COPY_ADDR-4)
80	.set EBX_REGADDR,(EAX_REGADDR-4)
81	.set ECX_REGADDR,(EBX_REGADDR-4)
82	.set EDX_REGADDR,(ECX_REGADDR-4)
83	.set ESI_REGADDR,(EDX_REGADDR-4)
84	.set EDI_REGADDR,(ESI_REGADDR-4)
85	.set EFLAGS_REGADDR,(EDI_REGADDR-4)
86	.set ES_REGADDR, (EFLAGS_REGADDR-4)
87	.set ENDREGADDR,(ES_REGADDR-4)
88
89	.set REALSTACK,ENDREGADDR-20		# leave a red zone?
90
91#define COPY_FLAGS (PSL_C|PSL_PF|PSL_AF|PSL_Z|PSL_N|PSL_D|PSL_V)
92
93/*
94 * do_bios_call(int function, struct bioscall *regs)
95 */
96
97ENTRY(do_bios_call)
98	pushl	%ebp
99	movl	%esp,%ebp		/* set up frame ptr */
100	pushl	%esi
101	pushl	%edi
102	pushl	%ebx
103	pushl	%ds
104	pushl	%es
105	pushl	%fs
106	pushl	%gs
107
108	# copy data to where the real-mode hook can handle it
109	movl 8(%ebp),%eax
110	movw %ax,FUNCTION_ADDR
111	movl 12(%ebp),%ebx
112	movl BIOSCALLREG_EAX(%ebx),%eax
113	movl %eax,EAX_REGADDR
114	movl BIOSCALLREG_EBX(%ebx),%eax
115	movl %eax,EBX_REGADDR
116	movl BIOSCALLREG_ECX(%ebx),%eax
117	movl %eax,ECX_REGADDR
118	movl BIOSCALLREG_EDX(%ebx),%eax
119	movl %eax,EDX_REGADDR
120	movl BIOSCALLREG_ESI(%ebx),%eax
121	movl %eax,ESI_REGADDR
122	movl BIOSCALLREG_EDI(%ebx),%eax
123	movl %eax,EDI_REGADDR
124	# merge current flags with certain provided flags
125	movl BIOSCALLREG_EFLAGS(%ebx),%ecx
126	pushfl
127	popl %eax
128	andl $~(COPY_FLAGS|PSL_I),%eax
129	andl $COPY_FLAGS,%ecx
130	orl %ecx,%eax
131	movl %eax,EFLAGS_REGADDR
132	movl $0, ES_REGADDR
133
134	# save flags, disable interrupts, do real mode stuff
135	pushfl
136
137	# save GDT
138	sgdt GDTR_SAVE_ADDR
139
140	# copy the GDT to local area
141	movl GDTR_SAVE_ADDR+2,%esi
142	movl $GDT_COPY_ADDR,%edi
143	movl $(NGDT*8),%ecx
144	cld
145	rep
146	movsb
147	movw $(NGDT*8)-1,GDTR_LOCAL_ADDR
148	movl $GDT_COPY_ADDR,GDTR_LOCAL_ADDR+2
149
150	# install GDT copy
151	lgdt GDTR_LOCAL_ADDR
152
153	cli
154
155	# save IDT
156	sidt IDTR_SAVE_ADDR
157
158	# set up new stack: save old ones, create new segs
159	movl %esp,STACK_PTR_ADDR
160	movl %ebp,BASE_PTR_ADDR
161	movl $REALSTACK,%esp
162	movl $0,%ebp		# leave no trace, there is none.
163
164	# save CR3
165	movl %cr3,%eax
166	movl %eax,CR3_ADDR
167
168	# turn off paging
169	movl %cr0,%eax
170	andl $~(CR0_PG),%eax
171	movl %eax,%cr0
172
173	# flush TLB, drop PDBR
174	xorl %eax,%eax
175	movl %eax,%cr3
176
177	## load 16-bit segment descriptors
178	movw $GSEL(GBIOSDATA_SEL,SEL_KPL),%bx
179	movw %bx,%ds
180	movw %bx,%es
181	movw %bx,%fs
182	movw %bx,%gs
183
184	ljmp $GSEL(GBIOSCODE_SEL,SEL_KPL),$x16+MYBASE
185
186x16:
187	# turn off protected mode--yikes!
188	mov	%cr0,%eax
189	data32
190	and	$~CR0_PE,%eax
191	mov	%eax,%cr0
192
193	# need inter-segment jump to reload real-mode CS
194	data32
195	ljmp $(MYBASE>>4),$xreal
196
197xreal:	# really in real mode now
198	# set up segment selectors.  Note: everything is now relative
199	# to zero-base in this file, except %ss.
200	# data items in our scratch area need to reflect MYADDR
201	xorl %eax,%eax
202	movw %ax,%ss
203
204	movw %cs,%ax
205	movw %ax,%es
206	movw %ax,%fs
207	movw %ax,%gs
208	movw %ax,%ds
209
210	## load IDT, now that we are here.
211	addr32
212	lidt IDT_bios
213
214	# Don't forget that we're in real mode, with 16-bit default data.
215	# all these movl's are really movw's, and movw's are movl's!
216	addr32
217	movw EDI_REGADDR-MYBASE,%di
218	addr32
219	movw ESI_REGADDR-MYBASE,%si
220	addr32
221	movw EDX_REGADDR-MYBASE,%dx
222	addr32
223	movw ECX_REGADDR-MYBASE,%cx
224	addr32
225	movw EBX_REGADDR-MYBASE,%bx
226	addr32
227	movb FUNCTION_ADDR-MYBASE,%al
228	addr32
229	movb %al,intaddr+1	# self modifying code, yuck. no indirect interrupt instruction!
230	# long jump to flush processor cache to reflect code modification
231	data32
232	ljmp $(MYBASE>>4),$flushit
233flushit:
234	addr32
235	movw EFLAGS_REGADDR-MYBASE,%ax
236	pushl %eax
237	popfl
238	addr32
239	movw EAX_REGADDR-MYBASE,%ax
240
241intaddr:
242	int $0xff
243
244	# save results
245	pushf
246	addr32
247	movw %ax,EAX_REGADDR-MYBASE
248	addr32
249	movw %bx,EBX_REGADDR-MYBASE
250	addr32
251	movw %cx,ECX_REGADDR-MYBASE
252	addr32
253	movw %dx,EDX_REGADDR-MYBASE
254	addr32
255	movw %si,ESI_REGADDR-MYBASE
256	addr32
257	movw %di,EDI_REGADDR-MYBASE
258	pop %ax
259	addr32
260	movw %ax,EFLAGS_REGADDR-MYBASE
261	addr32
262	movw %es,ES_REGADDR-MYBASE
263
264	# and return to protected mode
265	cli	# just to be sure
266
267	mov %cr0,%eax
268	data32
269	or $CR0_PE,%eax
270	mov %eax,%cr0
271
272	# long jump to 32-bit code segment
273	data32
274	ljmp $GSEL(GCODE_SEL,SEL_KPL),$x32+MYBASE
275x32:
276	#back in 32-bit mode/protected mode (but not paging yet).
277	# Reload the segment registers & IDT
278
279	movw $GSEL(GDATA_SEL,SEL_KPL),%bx
280	movw %bx,%ds
281	movw %bx,%ss
282	movw %bx,%es
283
284	# reload PDBR
285	movl CR3_ADDR,%eax
286	movl %eax,%cr3
287	movl %cr0,%eax
288	orl $CR0_PG,%eax
289	movl %eax,%cr0
290
291	# reload system copy of GDT
292	lgdt GDTR_SAVE_ADDR
293
294	# restore protected-mode stack
295	movl STACK_PTR_ADDR,%esp
296	movl BASE_PTR_ADDR,%ebp
297
298	#restore protected-mode IDT
299	lidt IDTR_SAVE_ADDR
300
301	# copy back arguments from holding pen
302
303	movl 12(%ebp),%ebx
304	movl EAX_REGADDR,%eax
305	movl %eax,BIOSCALLREG_EAX(%ebx)
306	movl EBX_REGADDR,%eax
307	movl %eax,BIOSCALLREG_EBX(%ebx)
308	movl ECX_REGADDR,%eax
309	movl %eax,BIOSCALLREG_ECX(%ebx)
310	movl EDX_REGADDR,%eax
311	movl %eax,BIOSCALLREG_EDX(%ebx)
312	movl ESI_REGADDR,%eax
313	movl %eax,BIOSCALLREG_ESI(%ebx)
314	movl EDI_REGADDR,%eax
315	movl %eax,BIOSCALLREG_EDI(%ebx)
316	movl EFLAGS_REGADDR,%eax
317	movl %eax,BIOSCALLREG_EFLAGS(%ebx)
318	movl ES_REGADDR, %eax
319	movl %eax,BIOSCALLREG_ES(%ebx)
320
321	# finish up, restore registers, and return
322	popfl
323	popl	%gs
324	popl	%fs
325	popl	%es
326	popl	%ds		# see above
327	popl	%ebx
328	popl	%edi
329	popl	%esi
330	leave
331	ret
332
333#ifdef __ELF__
334	.align 16
335#else
336	.align 4
337#endif
338IDT_bios:			# BIOS IDT descriptor (real-mode)
339	.word 1023
340	.long 0
341