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