xref: /netbsd-src/sys/arch/i386/bioscall/biostramp.S (revision 84d0ab551791493d2630bbef27063a9d514b9108)
1/*	$NetBSD: biostramp.S,v 1.6 1997/10/09 08:55:29 jtc 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 AX_REGADDR,(GDT_COPY_ADDR-2)
87	.set BX_REGADDR,(AX_REGADDR-2)
88	.set CX_REGADDR,(BX_REGADDR-2)
89	.set DX_REGADDR,(CX_REGADDR-2)
90	.set SI_REGADDR,(DX_REGADDR-2)
91	.set DI_REGADDR,(SI_REGADDR-2)
92	.set FLAGS_REGADDR,(DI_REGADDR-2)
93	.set ENDREGADDR,(FLAGS_REGADDR-2)
94
95	.set REALSTACK,ENDREGADDR-16		# leave a red zone?
96
97#define COPY_FLAGS (PSL_C|PSL_PF|PSL_AF|PSL_Z|PSL_N|PSL_D|PSL_V)
98
99/*
100 * do_bios_call(int function, struct apmregs *regs)
101 */
102
103ENTRY(do_bios_call)
104	pushl	%ebp
105	movl	%esp,%ebp		/* set up frame ptr */
106	pushl	%esi
107	pushl	%edi
108	pushl	%ebx
109	pushl	%ds
110	pushl	%es
111	pushl	%fs
112	pushl	%gs
113
114	# copy data to where the real-mode hook can handle it
115	movl 8(%ebp),%eax
116	movw %ax,FUNCTION_ADDR
117	movl 12(%ebp),%ebx
118	movw APMREG_AX(%ebx),%ax
119	movw %ax,AX_REGADDR
120	movw APMREG_BX(%ebx),%ax
121	movw %ax,BX_REGADDR
122	movw APMREG_CX(%ebx),%ax
123	movw %ax,CX_REGADDR
124	movw APMREG_DX(%ebx),%ax
125	movw %ax,DX_REGADDR
126	movw APMREG_SI(%ebx),%ax
127	movw %ax,SI_REGADDR
128	movw APMREG_DI(%ebx),%ax
129	movw %ax,DI_REGADDR
130	# merge current flags with certain provided flags
131	movw APMREG_FLAGS(%ebx),%cx
132	pushfl
133	popl %eax
134	andl $~(COPY_FLAGS|PSL_I),%eax
135	andl $COPY_FLAGS,%ecx
136	orl %ecx,%eax
137	movw %ax,FLAGS_REGADDR
138
139	# save flags, disable interrupts, do real mode stuff
140	pushfl
141
142	# save GDT
143	sgdt GDTR_SAVE_ADDR
144
145	# copy the GDT to local area
146	movl GDTR_SAVE_ADDR+2,%esi
147	movl $GDT_COPY_ADDR,%edi
148	movl $(NGDT*8),%ecx
149	cld
150	rep
151	movsb
152	movw $(NGDT*8)-1,GDTR_LOCAL_ADDR
153	movl $GDT_COPY_ADDR,GDTR_LOCAL_ADDR+2
154
155	# install GDT copy
156	lgdt GDTR_LOCAL_ADDR
157
158	cli
159
160	# save IDT
161	sidt IDTR_SAVE_ADDR
162
163	# set up new stack: save old ones, create new segs
164	movl %esp,STACK_PTR_ADDR
165	movl %ebp,BASE_PTR_ADDR
166	movl $REALSTACK,%esp
167	movl $0,%ebp		# leave no trace, there is none.
168
169	# save CR3
170	movl %cr3,%eax
171	movl %eax,CR3_ADDR
172
173	# turn off paging
174	movl %cr0,%eax
175	andl $~(CR0_PG),%eax
176	movl %eax,%cr0
177
178	# flush TLB, drop PDBR
179	xorl %eax,%eax
180	movl %eax,%cr3
181
182	## load 16-bit segment descriptors
183	movw $GSEL(GBIOSDATA_SEL,SEL_KPL),%bx
184	movw %bx,%ds
185	movw %bx,%es
186	movw %bx,%fs
187	movw %bx,%gs
188
189	ljmp $GSEL(GBIOSCODE_SEL,SEL_KPL),$x16+MYBASE
190
191x16:
192	# turn off protected mode--yikes!
193	mov	%cr0,%eax
194	data32
195	and	$~CR0_PE,%eax
196	mov	%eax,%cr0
197
198	# need inter-segment jump to reload real-mode CS
199	data32
200	ljmp $(MYBASE>>4),$xreal
201
202xreal:	# really in real mode now
203	# set up segment selectors.  Note: everything is now relative
204	# to zero-base in this file, except %ss.
205	# data items in our scratch area need to reflect MYADDR
206	xorl %ax,%ax
207	movw %ax,%ss
208
209	movw %cs,%ax
210	movw %ax,%es
211	movw %ax,%fs
212	movw %ax,%gs
213	movw %ax,%ds
214
215	## load IDT, now that we are here.
216	addr32
217	lidt IDT_bios
218
219	# Don't forget that we're in real mode, with 16-bit default data.
220	# all these movl's are really movw's !
221	addr32
222	movl DI_REGADDR-MYBASE,%edi
223	addr32
224	movl SI_REGADDR-MYBASE,%esi
225	addr32
226	movl DX_REGADDR-MYBASE,%edx
227	addr32
228	movl CX_REGADDR-MYBASE,%ecx
229	addr32
230	movl BX_REGADDR-MYBASE,%ebx
231	addr32
232	movb FUNCTION_ADDR-MYBASE,%al
233	addr32
234	movb %al,intaddr+1	# self modifying code, yuck. no indirect interrupt instruction!
235	# long jump to flush processor cache to reflect code modification
236	data32
237	ljmp $(MYBASE>>4),$flushit
238flushit:
239	addr32
240	movl FLAGS_REGADDR-MYBASE,%eax
241	pushl %eax
242	popfl
243	addr32
244	movl AX_REGADDR-MYBASE,%eax
245
246intaddr:
247	int $0xff
248
249	# save results
250	pushf
251	addr32
252	movl %eax,AX_REGADDR-MYBASE
253	addr32
254	movl %ebx,BX_REGADDR-MYBASE
255	addr32
256	movl %ecx,CX_REGADDR-MYBASE
257	addr32
258	movl %edx,DX_REGADDR-MYBASE
259	addr32
260	movl %esi,SI_REGADDR-MYBASE
261	addr32
262	movl %edi,DI_REGADDR-MYBASE
263	pop %eax
264	addr32
265	movl %eax,FLAGS_REGADDR-MYBASE
266
267	# and return to protected mode
268	cli	# just to be sure
269
270	mov %cr0,%eax
271	data32
272	or $CR0_PE,%eax
273	mov %eax,%cr0
274
275	# long jump to 32-bit code segment
276	data32
277	ljmp $GSEL(GCODE_SEL,SEL_KPL),$x32+MYBASE
278x32:
279	#back in 32-bit mode/protected mode (but not paging yet).
280	# Reload the segment registers & IDT
281
282	movw $GSEL(GDATA_SEL,SEL_KPL),%bx
283	movw %bx,%ds
284	movw %bx,%ss
285	movw %bx,%es
286
287	# reload PDBR
288	movl CR3_ADDR,%eax
289	movl %eax,%cr3
290	movl %cr0,%eax
291	orl $CR0_PG,%eax
292	movl %eax,%cr0
293
294	# reload system copy of GDT
295	lgdt GDTR_SAVE_ADDR
296
297	# restore protected-mode stack
298	movl STACK_PTR_ADDR,%esp
299	movl BASE_PTR_ADDR,%ebp
300
301	#restore protected-mode IDT
302	lidt IDTR_SAVE_ADDR
303
304	# copy back arguments from holding pen
305
306	movl 12(%ebp),%ebx
307	movw AX_REGADDR,%ax
308	movw %ax,APMREG_AX(%ebx)
309	movw BX_REGADDR,%ax
310	movw %ax,APMREG_BX(%ebx)
311	movw CX_REGADDR,%ax
312	movw %ax,APMREG_CX(%ebx)
313	movw DX_REGADDR,%ax
314	movw %ax,APMREG_DX(%ebx)
315	movw SI_REGADDR,%ax
316	movw %ax,APMREG_SI(%ebx)
317	movw DI_REGADDR,%ax
318	movw %ax,APMREG_DI(%ebx)
319	movw FLAGS_REGADDR,%ax
320	movw %ax,APMREG_FLAGS(%ebx)
321
322	# finish up, restore registers, and return
323	popfl
324	popl	%gs
325	popl	%fs
326	popl	%es
327	popl	%ds		# see above
328	popl	%ebx
329	popl	%edi
330	popl	%esi
331	leave
332	ret
333
334	.align 4
335IDT_bios:			# BIOS IDT descriptor (real-mode)
336	.word 1023
337	.long 0
338