2005-04-16 15:20:36 -07:00
/ *
* setup. S C o p y r i g h t ( C ) 1 9 9 1 , 1 9 9 2 L i n u s T o r v a l d s
*
* setup. s i s r e s p o n s i b l e f o r g e t t i n g t h e s y s t e m d a t a f r o m t h e B I O S ,
* and p u t t i n g t h e m i n t o t h e a p p r o p r i a t e p l a c e s i n s y s t e m m e m o r y .
* both s e t u p . s a n d s y s t e m h a s b e e n l o a d e d b y t h e b o o t b l o c k .
*
* This c o d e a s k s t h e b i o s f o r m e m o r y / d i s k / o t h e r p a r a m e t e r s , a n d
* puts t h e m i n a " s a f e " p l a c e : 0 x90 0 0 0 - 0 x90 1 F F , i e w h e r e t h e
* boot- b l o c k u s e d t o b e . I t i s t h e n u p t o t h e p r o t e c t e d m o d e
* system t o r e a d t h e m f r o m t h e r e b e f o r e t h e a r e a i s o v e r w r i t t e n
* for b u f f e r - b l o c k s .
*
* Move P S / 2 a u x i n i t c o d e t o p s a u x . c
* ( troyer@saifr00.cfsat.Honeywell.COM) 03Oct92
*
* some c h a n g e s a n d a d d i t i o n a l f e a t u r e s b y C h r i s t o p h N i e m a n n ,
* March 1 9 9 3 / J u n e 1 9 9 4 ( C h r i s t o p h . N i e m a n n @linux.org)
*
* add A P M B I O S c h e c k i n g b y S t e p h e n R o t h w e l l , M a y 1 9 9 4
* ( sfr@canb.auug.org.au)
*
* High l o a d s t u f f , i n i t r d s u p p o r t a n d p o s i t i o n i n d e p e n d e n c y
* by H a n s L e r m e n & W e r n e r A l m e s b e r g e r , F e b r u a r y 1 9 9 6
* < lermen@elserv.ffm.fgan.de>, <almesber@lrc.epfl.ch>
*
* Video h a n d l i n g m o v e d t o v i d e o . S b y M a r t i n M a r e s , M a r c h 1 9 9 6
* < mj@k332.feld.cvut.cz>
*
* Extended m e m o r y d e t e c t i o n s c h e m e r e t w i d d l e d b y o r c @pell.chi.il.us (david
* parsons) t o a v o i d l o a d l i n c o n f u s i o n , J u l y 1 9 9 7
*
* Transcribed f r o m I n t e l ( a s86 ) - > A T & T ( g a s ) b y C h r i s N o e , M a y 1 9 9 9 .
* < stiker@northlink.com>
*
2005-06-25 14:58:59 -07:00
* Fix t o w o r k a r o u n d b u g g y B I O S e s w h i c h d o n ' t u s e c a r r y b i t c o r r e c t l y
2005-04-16 15:20:36 -07:00
* and/ o r r e p o r t e x t e n d e d m e m o r y i n C X / D X f o r e 8 0 1 h m e m o r y s i z e d e t e c t i o n
* call. A s a r e s u l t t h e k e r n e l g o t w r o n g f i g u r e s . T h e i n t 1 5 / e 8 0 1 h d o c s
* from R a l f B r o w n i n t e r r u p t l i s t s e e m t o i n d i c a t e A X / B X s h o u l d b e u s e d
* anyway. S o t o a v o i d b r e a k i n g m a n y m a c h i n e s ( p r e s u m a b l y t h e r e w a s a r e a s o n
* to o r g i n a l l y u s e C X / D X i n s t e a d o f A X / B X ) , w e d o a k l u d g e t o s e e
* if C X / D X h a v e b e e n c h a n g e d i n t h e e 8 0 1 c a l l a n d i f s o u s e A X / B X .
* Michael M i l l e r , A p r i l 2 0 0 1 < m i c h a e l m @mjmm.org>
*
* Added l o n g m o d e c h e c k i n g a n d S S E f o r c e . M a r c h 2 0 0 3 , A n d i K l e e n .
* /
# include < a s m / s e g m e n t . h >
2006-07-03 23:30:54 +02:00
# include < l i n u x / u t s r e l e a s e . h >
2005-04-16 15:20:36 -07:00
# include < l i n u x / c o m p i l e . h >
# include < a s m / b o o t . h >
# include < a s m / e 8 2 0 . h >
# include < a s m / p a g e . h >
/* Signature words to ensure LILO loaded us right */
# define S I G 1 0 x A A 5 5
# define S I G 2 0 x5 A 5 A
INITSEG = D E F _ I N I T S E G # 0x9000 , w e m o v e b o o t h e r e , o u t o f t h e w a y
SYSSEG = D E F _ S Y S S E G # 0x1000 , s y s t e m l o a d e d a t 0 x10 0 0 0 ( 6 5 5 3 6 ) .
SETUPSEG = D E F _ S E T U P S E G # 0x9020 , t h i s i s t h e c u r r e n t s e g m e n t
# . . . and t h e f o r m e r c o n t e n t s o f C S
DELTA_ I N I T S E G = S E T U P S E G - I N I T S E G # 0x0020
.code16
.globl begtext, b e g d a t a , b e g b s s , e n d t e x t , e n d d a t a , e n d b s s
.text
begtext :
.data
begdata :
.bss
begbss :
.text
start :
jmp t r a m p o l i n e
# This i s t h e s e t u p h e a d e r , a n d i t m u s t s t a r t a t % c s : 2 ( o l d 0 x90 2 0 : 2 )
.ascii " HdrS" # h e a d e r s i g n a t u r e
2005-09-06 15:17:24 -07:00
.word 0x0204 # header v e r s i o n n u m b e r ( > = 0 x01 0 5 )
2005-04-16 15:20:36 -07:00
# or e l s e o l d l o a d l i n - 1 . 5 w i l l f a i l )
realmode_swtch : .word 0 , 0 # default_ s w i t c h , S E T U P S E G
start_sys_seg : .word S Y S S E G
.word kernel_version # pointing t o k e r n e l v e r s i o n s t r i n g
# above s e c t i o n o f h e a d e r i s c o m p a t i b l e
# with l o a d l i n - 1 . 5 ( h e a d e r v1 . 5 ) . D o n ' t
# change i t .
type_of_loader : .byte 0 # = 0 , old o n e ( L I L O , L o a d l i n ,
# Bootlin, S Y S L X , b o o t s e c t . . . )
# See D o c u m e n t a t i o n / i 3 8 6 / b o o t . t x t f o r
# assigned i d s
# flags, u n u s e d b i t s m u s t b e z e r o ( R F U ) b i t w i t h i n l o a d f l a g s
loadflags :
LOADED_ H I G H = 1 # I f s e t , t h e k e r n e l i s l o a d e d h i g h
CAN_ U S E _ H E A P = 0 x80 # I f s e t , t h e l o a d e r a l s o h a s s e t
# heap_ e n d _ p t r t o t e l l h o w m u c h
# space b e h i n d s e t u p . S c a n b e u s e d f o r
# heap p u r p o s e s .
# Only t h e l o a d e r k n o w s w h a t i s f r e e
# ifndef _ _ B I G _ K E R N E L _ _
.byte 0
# else
.byte LOADED_HIGH
# endif
setup_move_size : .word 0x8000 # size t o m o v e , w h e n s e t u p i s n o t
# loaded a t 0 x90 0 0 0 . W e w i l l m o v e s e t u p
# to 0 x90 0 0 0 t h e n j u s t b e f o r e j u m p i n g
# into t h e k e r n e l . H o w e v e r , o n l y t h e
# loader k n o w s h o w m u c h d a t a b e h i n d
# us a l s o n e e d s t o b e l o a d e d .
code32_start : # here l o a d e r s c a n p u t a d i f f e r e n t
# start a d d r e s s f o r 3 2 - b i t c o d e .
# ifndef _ _ B I G _ K E R N E L _ _
.long 0x1000 # 0 x1 0 0 0 = d e f a u l t f o r z I m a g e
# else
.long 0x100000 # 0 x1 0 0 0 0 0 = d e f a u l t f o r b i g k e r n e l
# endif
ramdisk_image : .long 0 # address o f l o a d e d r a m d i s k i m a g e
# Here t h e l o a d e r p u t s t h e 3 2 - b i t
# address w h e r e i t l o a d e d t h e i m a g e .
# This o n l y w i l l b e r e a d b y t h e k e r n e l .
ramdisk_size : .long 0 # its s i z e i n b y t e s
bootsect_kludge :
.long 0 # obsolete
heap_end_ptr : .word m o d e l i s t + 1024 # ( Header v e r s i o n 0 x02 0 1 o r l a t e r )
# space f r o m h e r e ( e x c l u s i v e ) d o w n t o
# end o f s e t u p c o d e c a n b e u s e d b y s e t u p
# for l o c a l h e a p p u r p o s e s .
pad1 : .word 0
cmd_line_ptr : .long 0 # ( Header v e r s i o n 0 x02 0 2 o r l a t e r )
# If n o n z e r o , a 3 2 - b i t p o i n t e r
# to t h e k e r n e l c o m m a n d l i n e .
# The c o m m a n d l i n e s h o u l d b e
# located b e t w e e n t h e s t a r t o f
# setup a n d t h e e n d o f l o w
# memory ( 0 x a00 0 0 ) , o r i t m a y
# get o v e r w r i t t e n b e f o r e i t
# gets r e a d . I f t h i s f i e l d i s
# used, t h e r e i s n o l o n g e r
# anything m a g i c a l a b o u t t h e
# 0 x9 0 0 0 0 s e g m e n t ; the setup
# can b e l o c a t e d a n y w h e r e i n
# low m e m o r y 0 x10 0 0 0 o r h i g h e r .
ramdisk_max : .long 0xffffffff
trampoline : call s t a r t _ o f _ s e t u p
.align 16
# The o f f s e t a t t h i s p o i n t i s 0 x24 0
2005-05-01 08:58:51 -07:00
.space ( 0 xeff- 0 x24 0 + 1 ) # E 820 & E D D s p a c e ( e n d i n g a t 0 x e f f )
2005-04-16 15:20:36 -07:00
# End o f s e t u p h e a d e r ## # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # # #
start_of_setup :
# Bootlin d e p e n d s o n t h i s b e i n g d o n e e a r l y
movw $ 0 x01 5 0 0 , % a x
movb $ 0 x81 , % d l
int $ 0 x13
# ifdef S A F E _ R E S E T _ D I S K _ C O N T R O L L E R
# Reset t h e d i s k c o n t r o l l e r .
movw $ 0 x00 0 0 , % a x
movb $ 0 x80 , % d l
int $ 0 x13
# endif
# Set % d s = % c s , w e k n o w t h a t S E T U P S E G = % c s a t t h i s p o i n t
movw % c s , % a x # a k a S E T U P S E G
movw % a x , % d s
# Check s i g n a t u r e a t e n d o f s e t u p
cmpw $ S I G 1 , s e t u p _ s i g 1
jne b a d _ s i g
cmpw $ S I G 2 , s e t u p _ s i g 2
jne b a d _ s i g
jmp g o o d _ s i g 1
# Routine t o p r i n t a s c i i z s t r i n g a t d s : s i
prtstr :
lodsb
andb % a l , % a l
jz f i n
call p r t c h r
jmp p r t s t r
fin : ret
# Space p r i n t i n g
prtsp2 : call p r t s p c # P r i n t d o u b l e s p a c e
prtspc : movb $ 0 x20 , % a l # P r i n t s i n g l e s p a c e ( n o t e : f a l l - t h r u )
prtchr :
pushw % a x
pushw % c x
movw $ 0 0 0 7 ,% b x
movw $ 0 x01 , % c x
movb $ 0 x0 e , % a h
int $ 0 x10
popw % c x
popw % a x
ret
beep : movb $ 0 x07 , % a l
jmp p r t c h r
no_sig_mess : .string " No setup signature found ... "
good_sig1 :
jmp g o o d _ s i g
# We n o w h a v e t o f i n d t h e r e s t o f t h e s e t u p c o d e / d a t a
bad_sig :
movw % c s , % a x # S E T U P S E G
subw $ D E L T A _ I N I T S E G , % a x # I N I T S E G
movw % a x , % d s
xorb % b h , % b h
movb ( 4 9 7 ) , % b l # g e t s e t u p s e c t f r o m b o o t s e c t
subw $ 4 , % b x # L I L O l o a d s 4 s e c t o r s o f s e t u p
shlw $ 8 , % b x # c o n v e r t t o w o r d s ( 1 s e c t =2 ^ 8 w o r d s )
movw % b x , % c x
shrw $ 3 , % b x # c o n v e r t t o s e g m e n t
addw $ S Y S S E G , % b x
movw % b x , % c s : s t a r t _ s y s _ s e g
# Move r e s t o f s e t u p c o d e / d a t a t o h e r e
movw $ 2 0 4 8 , % d i # f o u r s e c t o r s l o a d e d b y L I L O
subw % s i , % s i
movw % c s , % a x # a k a S E T U P S E G
movw % a x , % e s
movw $ S Y S S E G , % a x
movw % a x , % d s
rep
movsw
movw % c s , % a x # a k a S E T U P S E G
movw % a x , % d s
cmpw $ S I G 1 , s e t u p _ s i g 1
jne n o _ s i g
cmpw $ S I G 2 , s e t u p _ s i g 2
jne n o _ s i g
jmp g o o d _ s i g
no_sig :
lea n o _ s i g _ m e s s , % s i
call p r t s t r
no_sig_loop :
jmp n o _ s i g _ l o o p
good_sig :
movw % c s , % a x # a k a S E T U P S E G
subw $ D E L T A _ I N I T S E G , % a x # a k a I N I T S E G
movw % a x , % d s
# Check i f a n o l d l o a d e r t r i e s t o l o a d a b i g - k e r n e l
testb $ L O A D E D _ H I G H , % c s : l o a d f l a g s # D o w e h a v e a b i g k e r n e l ?
jz l o a d e r _ o k # N o , n o d a n g e r f o r o l d l o a d e r s .
cmpb $ 0 , % c s : t y p e _ o f _ l o a d e r # D o w e h a v e a l o a d e r t h a t
# can d e a l w i t h u s ?
jnz l o a d e r _ o k # Y e s , c o n t i n u e .
pushw % c s # N o , w e h a v e a n o l d l o a d e r ,
popw % d s # d i e .
lea l o a d e r _ p a n i c _ m e s s , % s i
call p r t s t r
jmp n o _ s i g _ l o o p
loader_panic_mess : .string " Wrong loader, giving up... "
loader_ok :
/* check for long mode. */
/ * we h a v e t o d o t h i s b e f o r e t h e V E S A s e t u p , o t h e r w i s e t h e u s e r
can' t s e e t h e e r r o r m e s s a g e . * /
pushw % d s
movw % c s ,% a x
movw % a x ,% d s
/* minimum CPUID flags for x86-64 */
/* see http://www.x86-64.org/lists/discuss/msg02971.html */
# define S S E _ M A S K ( ( 1 < < 2 5 ) | ( 1 < < 2 6 ) )
# define R E Q U I R E D _ M A S K 1 ( ( 1 < < 0 ) | ( 1 < < 3 ) | ( 1 < < 4 ) | ( 1 < < 5 ) | ( 1 < < 6 ) | ( 1 < < 8 ) | \
( 1 < < 1 3 ) | ( 1 < < 1 5 ) | ( 1 < < 2 4 ) )
# define R E Q U I R E D _ M A S K 2 ( 1 < < 2 9 )
pushfl / * s t a n d a r d w a y t o c h e c k f o r c p u i d * /
popl % e a x
movl % e a x ,% e b x
xorl $ 0 x20 0 0 0 0 ,% e a x
pushl % e a x
popfl
pushfl
popl % e a x
cmpl % e a x ,% e b x
jz n o _ l o n g m o d e / * c p u h a s n o c p u i d * /
movl $ 0 x0 ,% e a x
cpuid
cmpl $ 0 x1 ,% e a x
jb n o _ l o n g m o d e / * n o c p u i d 1 * /
xor % d i ,% d i
cmpl $ 0 x68 7 4 7 5 4 1 ,% e b x / * A u t h e n t i c A M D * /
jnz n o a m d
cmpl $ 0 x69 7 4 6 e 6 5 ,% e d x
jnz n o a m d
cmpl $ 0 x44 4 d41 6 3 ,% e c x
jnz n o a m d
mov $ 1 ,% d i / * c p u i s f r o m A M D * /
noamd :
movl $ 0 x1 ,% e a x
cpuid
andl $ R E Q U I R E D _ M A S K 1 ,% e d x
xorl $ R E Q U I R E D _ M A S K 1 ,% e d x
jnz n o _ l o n g m o d e
movl $ 0 x80 0 0 0 0 0 0 ,% e a x
cpuid
cmpl $ 0 x80 0 0 0 0 0 1 ,% e a x
jb n o _ l o n g m o d e / * n o e x t e n d e d c p u i d * /
movl $ 0 x80 0 0 0 0 0 1 ,% e a x
cpuid
andl $ R E Q U I R E D _ M A S K 2 ,% e d x
xorl $ R E Q U I R E D _ M A S K 2 ,% e d x
jnz n o _ l o n g m o d e
sse_test :
movl $ 1 ,% e a x
cpuid
andl $ S S E _ M A S K ,% e d x
cmpl $ S S E _ M A S K ,% e d x
je s s e _ o k
test % d i ,% d i
jz n o _ l o n g m o d e / * o n l y t r y t o f o r c e S S E o n A M D * /
movl $ 0 x c00 1 0 0 1 5 ,% e c x / * H W C R * /
rdmsr
btr $ 1 5 ,% e a x / * e n a b l e S S E * /
wrmsr
xor % d i ,% d i / * d o n ' t l o o p * /
jmp s s e _ t e s t / * t r y a g a i n * /
no_longmode :
call b e e p
lea l o n g _ m o d e _ p a n i c ,% s i
call p r t s t r
no_longmode_loop :
jmp n o _ l o n g m o d e _ l o o p
long_mode_panic :
.string " Your C P U d o e s n o t s u p p o r t l o n g m o d e . U s e a 3 2 b i t d i s t r i b u t i o n . "
.byte 0
sse_ok :
popw % d s
# tell B I O S w e w a n t t o g o t o l o n g m o d e
movl $ 0 x e c00 ,% e a x # d e c l a r e t a r g e t o p e r a t i n g m o d e
movl $ 2 ,% e b x # l o n g m o d e
int $ 0 x15
# Get m e m o r y s i z e ( e x t e n d e d m e m , k B )
xorl % e a x , % e a x
movl % e a x , ( 0 x1 e 0 )
# ifndef S T A N D A R D _ M E M O R Y _ B I O S _ C A L L
movb % a l , ( E 8 2 0 N R )
# Try t h r e e d i f f e r e n t m e m o r y d e t e c t i o n s c h e m e s . F i r s t , t r y
# e8 2 0 h , w h i c h l e t s u s a s s e m b l e a m e m o r y m a p , t h e n t r y e 8 0 1 h ,
# which r e t u r n s a 3 2 - b i t m e m o r y s i z e , a n d f i n a l l y 8 8 h , w h i c h
# returns 0 - 6 4 m
# method E 8 2 0 H :
# the m e m o r y m a p f r o m h e l l . e 8 2 0 h r e t u r n s m e m o r y c l a s s i f i e d i n t o
# a w h o l e b u n c h o f d i f f e r e n t t y p e s , a n d a l l o w s m e m o r y h o l e s a n d
# everything. W e s c a n t h r o u g h t h i s m e m o r y m a p a n d b u i l d a l i s t
# of t h e f i r s t 3 2 m e m o r y a r e a s , w h i c h w e r e t u r n a t [ E 8 2 0 M A P ] .
2005-06-25 14:58:59 -07:00
# This i s d o c u m e n t e d a t h t t p : / / w w w . a c p i . i n f o / , i n t h e A C P I 2 . 0 s p e c i f i c a t i o n .
2005-04-16 15:20:36 -07:00
# define S M A P 0 x53 4 d41 5 0
meme820 :
xorl % e b x , % e b x # c o n t i n u a t i o n c o u n t e r
movw $ E 8 2 0 M A P , % d i # p o i n t i n t o t h e w h i t e l i s t
# so w e c a n h a v e t h e b i o s
# directly w r i t e i n t o i t .
jmpe820 :
movl $ 0 x00 0 0 e 8 2 0 , % e a x # e 820 , u p p e r w o r d z e r o e d
movl $ S M A P , % e d x # a s c i i ' S M A P '
movl $ 2 0 , % e c x # s i z e o f t h e e 820 r e c
pushw % d s # d a t a r e c o r d .
popw % e s
int $ 0 x15 # m a k e t h e c a l l
jc b a i l 8 2 0 # f a l l t o e 801 i f i t f a i l s
cmpl $ S M A P , % e a x # c h e c k t h e r e t u r n i s ` S M A P '
jne b a i l 8 2 0 # f a l l t o e 801 i f i t f a i l s
# cmpl $ 1 , 1 6 ( % d i ) # i s t h i s u s a b l e m e m o r y ?
# jne a g a i n 8 2 0
# If t h i s i s u s a b l e m e m o r y , w e s a v e i t b y s i m p l y a d v a n c i n g % d i b y
# sizeof( e 8 2 0 r e c ) .
#
good820 :
2005-05-01 08:58:51 -07:00
movb ( E 8 2 0 N R ) , % a l # u p t o 128 e n t r i e s
2005-04-16 15:20:36 -07:00
cmpb $ E 8 2 0 M A X , % a l
2005-05-01 08:58:51 -07:00
jae b a i l 8 2 0
2005-04-16 15:20:36 -07:00
incb ( E 8 2 0 N R )
movw % d i , % a x
addw $ 2 0 , % a x
movw % a x , % d i
again820 :
cmpl $ 0 , % e b x # c h e c k t o s e e i f
jne j m p e 8 2 0 # % e b x i s s e t t o E O F
bail820 :
# method E 8 0 1 H :
# memory s i z e i s i n 1 k c h u n k s i z e s , t o a v o i d c o n f u s i n g l o a d l i n .
# we s t o r e t h e 0 x e 8 0 1 m e m o r y s i z e i n a c o m p l e t e l y d i f f e r e n t p l a c e ,
# because i t w i l l m o s t l i k e l y b e l o n g e r t h a n 1 6 b i t s .
# ( use 1 e 0 b e c a u s e t h a t ' s w h a t L a r r y A u g u s t i n e u s e s i n h i s
# alternative n e w m e m o r y d e t e c t i o n s c h e m e , a n d i t ' s s e n s i b l e
# to w r i t e e v e r y t h i n g i n t o t h e s a m e p l a c e . )
meme801 :
stc # f i x t o w o r k a r o u n d b u g g y
2005-06-25 14:58:59 -07:00
xorw % c x ,% c x # B I O S e s w h i c h d o n ' t c l e a r / s e t
2005-04-16 15:20:36 -07:00
xorw % d x ,% d x # c a r r y o n p a s s / e r r o r o f
# e8 0 1 h m e m o r y s i z e c a l l
# or m e r e l y p a s s c x ,d x t h o u g h
# without c h a n g i n g t h e m .
movw $ 0 x e 8 0 1 , % a x
int $ 0 x15
jc m e m 8 8
cmpw $ 0 x0 , % c x # K l u d g e t o h a n d l e B I O S e s
jne e 8 0 1 u s e c x d x # w h i c h r e p o r t t h e i r e x t e n d e d
cmpw $ 0 x0 , % d x # m e m o r y i n A X / B X r a t h e r t h a n
jne e 8 0 1 u s e c x d x # C X / D X . T h e s p e c I h a v e r e a d
movw % a x , % c x # s e e m s t o i n d i c a t e A X / B X
movw % b x , % d x # a r e m o r e r e a s o n a b l e a n y w a y . . .
e801usecxdx :
andl $ 0 x f f f f , % e d x # c l e a r s i g n e x t e n d
shll $ 6 , % e d x # a n d g o f r o m 64 k t o 1 k c h u n k s
movl % e d x , ( 0 x1 e 0 ) # s t o r e e x t e n d e d m e m o r y s i z e
andl $ 0 x f f f f , % e c x # c l e a r s i g n e x t e n d
addl % e c x , ( 0 x1 e 0 ) # a n d a d d l o w e r m e m o r y i n t o
# total s i z e .
# Ye O l d e T r a d i t i o n a l M e t h o d e . R e t u r n s t h e m e m o r y s i z e ( u p t o 1 6 m b o r
# 6 4 mb, d e p e n d i n g o n t h e b i o s ) i n a x .
mem88 :
# endif
movb $ 0 x88 , % a h
int $ 0 x15
movw % a x , ( 2 )
# Set t h e k e y b o a r d r e p e a t r a t e t o t h e m a x
movw $ 0 x03 0 5 , % a x
xorw % b x , % b x
int $ 0 x16
# Check f o r v i d e o a d a p t e r a n d i t s p a r a m e t e r s a n d a l l o w t h e
# user t o b r o w s e v i d e o m o d e s .
call v i d e o # N O T E : w e n e e d % d s p o i n t i n g
# to b o o t s e c t o r
# Get h d0 d a t a . . .
xorw % a x , % a x
movw % a x , % d s
ldsw ( 4 * 0 x41 ) , % s i
movw % c s , % a x # a k a S E T U P S E G
subw $ D E L T A _ I N I T S E G , % a x # a k a I N I T S E G
pushw % a x
movw % a x , % e s
movw $ 0 x00 8 0 , % d i
movw $ 0 x10 , % c x
pushw % c x
cld
rep
movsb
# Get h d1 d a t a . . .
xorw % a x , % a x
movw % a x , % d s
ldsw ( 4 * 0 x46 ) , % s i
popw % c x
popw % e s
movw $ 0 x00 9 0 , % d i
rep
movsb
# Check t h a t t h e r e I S a h d1 : - )
movw $ 0 x01 5 0 0 , % a x
movb $ 0 x81 , % d l
int $ 0 x13
jc n o _ d i s k 1
cmpb $ 3 , % a h
je i s _ d i s k 1
no_disk1 :
movw % c s , % a x # a k a S E T U P S E G
subw $ D E L T A _ I N I T S E G , % a x # a k a I N I T S E G
movw % a x , % e s
movw $ 0 x00 9 0 , % d i
movw $ 0 x10 , % c x
xorw % a x , % a x
cld
rep
stosb
is_disk1 :
# Check f o r P S / 2 p o i n t i n g d e v i c e
movw % c s , % a x # a k a S E T U P S E G
subw $ D E L T A _ I N I T S E G , % a x # a k a I N I T S E G
movw % a x , % d s
2006-09-26 10:52:30 +02:00
movb $ 0 , ( 0 x1 f f ) # d e f a u l t i s n o p o i n t i n g d e v i c e
2005-04-16 15:20:36 -07:00
int $ 0 x11 # i n t 0x11 : e q u i p m e n t l i s t
testb $ 0 x04 , % a l # c h e c k i f m o u s e i n s t a l l e d
jz n o _ p s m o u s e
2006-09-26 10:52:30 +02:00
movb $ 0 x A A , ( 0 x1 f f ) # d e v i c e p r e s e n t
2005-04-16 15:20:36 -07:00
no_psmouse :
# include " . . / . . / i 3 8 6 / b o o t / e d d . S "
# Now w e w a n t t o m o v e t o p r o t e c t e d m o d e . . .
cmpw $ 0 , % c s : r e a l m o d e _ s w t c h
jz r m o d e s w t c h _ n o r m a l
lcall * % c s : r e a l m o d e _ s w t c h
jmp r m o d e s w t c h _ e n d
rmodeswtch_normal :
pushw % c s
call d e f a u l t _ s w i t c h
rmodeswtch_end :
# we g e t t h e c o d e 3 2 s t a r t a d d r e s s a n d m o d i f y t h e b e l o w ' j m p i '
# ( loader m a y h a v e c h a n g e d i t )
movl % c s : c o d e 3 2 _ s t a r t , % e a x
movl % e a x , % c s : c o d e 3 2
# Now w e m o v e t h e s y s t e m t o i t s r i g h t f u l p l a c e . . . b u t w e c h e c k i f w e h a v e a
# big- k e r n e l . I n t h a t c a s e w e * m u s t * n o t m o v e i t . . .
testb $ L O A D E D _ H I G H , % c s : l o a d f l a g s
jz d o _ m o v e 0 # . . t h e n w e h a v e a n o r m a l l o w
# loaded z I m a g e
# . . or e l s e w e h a v e a h i g h
# loaded b z I m a g e
jmp e n d _ m o v e # . . . a n d w e s k i p m o v i n g
do_move0 :
movw $ 0 x10 0 , % a x # s t a r t o f d e s t i n a t i o n s e g m e n t
movw % c s , % b p # a k a S E T U P S E G
subw $ D E L T A _ I N I T S E G , % b p # a k a I N I T S E G
movw % c s : s t a r t _ s y s _ s e g , % b x # s t a r t o f s o u r c e s e g m e n t
cld
do_move :
movw % a x , % e s # d e s t i n a t i o n s e g m e n t
incb % a h # i n s t e a d o f a d d a x , # 0x100
movw % b x , % d s # s o u r c e s e g m e n t
addw $ 0 x10 0 , % b x
subw % d i , % d i
subw % s i , % s i
movw $ 0 x80 0 , % c x
rep
movsw
cmpw % b p , % b x # a s s u m e s t a r t _ s y s _ s e g > 0x200 ,
# so w e w i l l p e r h a p s r e a d o n e
# page m o r e t h a n n e e d e d , b u t
# never o v e r w r i t e I N I T S E G
# because d e s t i n a t i o n i s a
# minimum o n e p a g e b e l o w s o u r c e
jb d o _ m o v e
end_move :
# then w e l o a d t h e s e g m e n t d e s c r i p t o r s
movw % c s , % a x # a k a S E T U P S E G
movw % a x , % d s
# Check w h e t h e r w e n e e d t o b e d o w n w a r d c o m p a t i b l e w i t h v e r s i o n < =201
cmpl $ 0 , c m d _ l i n e _ p t r
jne e n d _ m o v e _ s e l f # l o a d e r u s e s v e r s i o n > = 202 f e a t u r e s
cmpb $ 0 x20 , t y p e _ o f _ l o a d e r
je e n d _ m o v e _ s e l f # b o o t s e c t l o a d e r , w e k n o w o f i t
# Boot l o a d e r d o e s n t s u p p o r t b o o t p r o t o c o l v e r s i o n 2 . 0 2 .
# If w e h a v e o u r c o d e n o t a t 0 x90 0 0 0 , w e n e e d t o m o v e i t t h e r e n o w .
# We a l s o t h e n n e e d t o m o v e t h e p a r a m s b e h i n d i t ( c o m m a n d l i n e )
# Because w e w o u l d o v e r w r i t e t h e c o d e o n t h e c u r r e n t I P , w e m o v e
# it i n t w o s t e p s , j u m p i n g h i g h a f t e r t h e f i r s t o n e .
movw % c s , % a x
cmpw $ S E T U P S E G , % a x
je e n d _ m o v e _ s e l f
cli # m a k e s u r e w e r e a l l y h a v e
# interrupts d i s a b l e d !
# because a f t e r t h i s t h e s t a c k
# should n o t b e u s e d
subw $ D E L T A _ I N I T S E G , % a x # a k a I N I T S E G
movw % s s , % d x
cmpw % a x , % d x
jb m o v e _ s e l f _ 1
addw $ I N I T S E G , % d x
subw % a x , % d x # t h i s w i l l g o i n t o % s s a f t e r
# the m o v e
move_self_1 :
movw % a x , % d s
movw $ I N I T S E G , % a x # r e a l I N I T S E G
movw % a x , % e s
movw % c s : s e t u p _ m o v e _ s i z e , % c x
std # w e h a v e t o m o v e u p , s o w e u s e
# direction d o w n b e c a u s e t h e
# areas m a y o v e r l a p
movw % c x , % d i
decw % d i
movw % d i , % s i
subw $ m o v e _ s e l f _ h e r e + 0 x20 0 , % c x
rep
movsb
ljmp $ S E T U P S E G , $ m o v e _ s e l f _ h e r e
move_self_here :
movw $ m o v e _ s e l f _ h e r e + 0 x20 0 , % c x
rep
movsb
movw $ S E T U P S E G , % a x
movw % a x , % d s
movw % d x , % s s
end_move_self : # now w e a r e a t t h e r i g h t p l a c e
lidt i d t _ 4 8 # l o a d i d t w i t h 0 ,0
xorl % e a x , % e a x # C o m p u t e g d t _ b a s e
movw % d s , % a x # ( C o n v e r t % d s : g d t t o a l i n e a r p t r )
shll $ 4 , % e a x
addl $ g d t , % e a x
movl % e a x , ( g d t _ 4 8 + 2 )
lgdt g d t _ 4 8 # l o a d g d t w i t h w h a t e v e r i s
# appropriate
# that w a s p a i n l e s s , n o w w e e n a b l e a20
call e m p t y _ 8 0 4 2
movb $ 0 x D 1 , % a l # c o m m a n d w r i t e
outb % a l , $ 0 x64
call e m p t y _ 8 0 4 2
movb $ 0 x D F , % a l # A 20 o n
outb % a l , $ 0 x60
call e m p t y _ 8 0 4 2
#
# You m u s t p r e s e r v e t h e o t h e r b i t s h e r e . O t h e r w i s e e m b a r r a s i n g t h i n g s
# like l a p t o p s p o w e r i n g o f f o n b o o t h a p p e n . C o r r e c t e d v e r s i o n b y K i r a
# Brown f r o m L i n u x 2 . 2
#
inb $ 0 x92 , % a l #
orb $ 0 2 , % a l # " fast A20 " v e r s i o n
outb % a l , $ 0 x92 # s o m e c h i p s h a v e o n l y t h i s
# wait u n t i l a20 r e a l l y * i s * e n a b l e d ; it can take a fair amount of
# time o n c e r t a i n s y s t e m s ; Toshiba Tecras are known to have this
# problem. T h e m e m o r y l o c a t i o n u s e d h e r e ( 0 x20 0 ) i s t h e i n t 0 x80
# vector, w h i c h s h o u l d b e s a f e t o u s e .
xorw % a x , % a x # s e g m e n t 0x0000
movw % a x , % f s
decw % a x # s e g m e n t 0xffff ( H M A )
movw % a x , % g s
a20_wait :
incw % a x # u n u s e d m e m o r y l o c a t i o n < 0xfff0
movw % a x , % f s : ( 0 x20 0 ) # w e u s e t h e " int 0x80 " v e c t o r
cmpw % g s : ( 0 x21 0 ) , % a x # a n d i t s c o r r e s p o n d i n g H M A a d d r
je a20 _ w a i t # l o o p u n t i l n o l o n g e r a l i a s e d
# make s u r e a n y p o s s i b l e c o p r o c e s s o r i s p r o p e r l y r e s e t . .
xorw % a x , % a x
outb % a l , $ 0 x f0
call d e l a y
outb % a l , $ 0 x f1
call d e l a y
# well, t h a t w e n t o k , I h o p e . N o w w e m a s k a l l i n t e r r u p t s - t h e r e s t
# is d o n e i n i n i t _ I R Q ( ) .
movb $ 0 x F F , % a l # m a s k a l l i n t e r r u p t s f o r n o w
outb % a l , $ 0 x A 1
call d e l a y
movb $ 0 x F B , % a l # m a s k a l l i r q ' s b u t i r q 2 w h i c h
outb % a l , $ 0 x21 # i s c a s c a d e d
# Well, t h a t c e r t a i n l y w a s n ' t f u n : - ( . H o p e f u l l y i t w o r k s , a n d w e d o n ' t
# need n o s t e e n k i n g B I O S a n y w a y ( e x c e p t f o r t h e i n i t i a l l o a d i n g : - ) .
# The B I O S - r o u t i n e w a n t s l o t s o f u n n e c e s s a r y d a t a , a n d i t ' s l e s s
# " interesting" a n y w a y . T h i s i s h o w R E A L p r o g r a m m e r s d o i t .
#
# Well, n o w ' s t h e t i m e t o a c t u a l l y m o v e i n t o p r o t e c t e d m o d e . T o m a k e
# things a s s i m p l e a s p o s s i b l e , w e d o n o r e g i s t e r s e t - u p o r a n y t h i n g ,
# we l e t t h e g n u - c o m p i l e d 3 2 - b i t p r o g r a m s d o t h a t . W e j u s t j u m p t o
# absolute a d d r e s s 0 x10 0 0 ( o r t h e l o a d e r s u p p l i e d o n e ) ,
# in 3 2 - b i t p r o t e c t e d m o d e .
#
# Note t h a t t h e s h o r t j u m p i s n ' t s t r i c t l y n e e d e d , a l t h o u g h t h e r e a r e
# reasons w h y i t m i g h t b e a g o o d i d e a . I t w o n ' t h u r t i n a n y c a s e .
movw $ 1 , % a x # p r o t e c t e d m o d e ( P E ) b i t
lmsw % a x # T h i s i s i t !
jmp f l u s h _ i n s t r
flush_instr :
xorw % b x , % b x # F l a g t o i n d i c a t e a b o o t
xorl % e s i , % e s i # P o i n t e r t o r e a l - m o d e c o d e
movw % c s , % s i
subw $ D E L T A _ I N I T S E G , % s i
shll $ 4 , % e s i # C o n v e r t t o 32 - b i t p o i n t e r
# NOTE : For h i g h l o a d e d b i g k e r n e l s w e n e e d a
# jmpi 0 x10 0 0 0 0 ,_ _ K E R N E L _ C S
#
# but w e y e t h a v e n ' t r e l o a d e d t h e C S r e g i s t e r , s o t h e d e f a u l t s i z e
# of t h e t a r g e t o f f s e t s t i l l i s 1 6 b i t .
2005-06-25 14:58:59 -07:00
# However, u s i n g a n o p e r a n d p r e f i x ( 0 x66 ) , t h e C P U w i l l p r o p e r l y
2005-04-16 15:20:36 -07:00
# take o u r 4 8 b i t f a r p o i n t e r . ( I N T e L 8 0 3 8 6 P r o g r a m m e r ' s R e f e r e n c e
# Manual, M i x i n g 1 6 - b i t a n d 3 2 - b i t c o d e , p a g e 1 6 - 6 )
.byte 0 x6 6 , 0 x e a # p r e f i x + j m p i - o p c o d e
code32 : .long 0x1000 # will b e s e t t o 0 x10 0 0 0 0
# for b i g k e r n e l s
.word __KERNEL_CS
# Here' s a b u n c h o f i n f o r m a t i o n a b o u t y o u r c u r r e n t k e r n e l . .
kernel_version : .ascii U T S _ R E L E A S E
.ascii " ( "
.ascii LINUX_COMPILE_BY
.ascii " @"
.ascii LINUX_COMPILE_HOST
.ascii " ) "
.ascii UTS_VERSION
.byte 0
# This i s t h e d e f a u l t r e a l m o d e s w i t c h r o u t i n e .
# to b e c a l l e d j u s t b e f o r e p r o t e c t e d m o d e t r a n s i t i o n
default_switch :
cli # n o i n t e r r u p t s a l l o w e d !
movb $ 0 x80 , % a l # d i s a b l e N M I f o r b o o t u p
# sequence
outb % a l , $ 0 x70
lret
# This r o u t i n e c h e c k s t h a t t h e k e y b o a r d c o m m a n d q u e u e i s e m p t y
# ( after e m p t y i n g t h e o u t p u t b u f f e r s )
#
# Some m a c h i n e s h a v e d e l u s i o n s t h a t t h e k e y b o a r d b u f f e r i s a l w a y s f u l l
# with n o k e y b o a r d a t t a c h e d . . .
#
# If t h e r e i s n o k e y b o a r d c o n t r o l l e r , w e w i l l u s u a l l y g e t 0 x f f
# to a l l t h e r e a d s . W i t h e a c h I O t a k i n g a m i c r o s e c o n d a n d
# a t i m e o u t o f 1 0 0 ,0 0 0 i t e r a t i o n s , t h i s c a n t a k e a b o u t h a l f a
# second ( " d e l a y " = = o u t b t o p o r t 0 x80 ) . T h a t s h o u l d b e o k ,
# and s h o u l d a l s o b e p l e n t y o f t i m e f o r a r e a l k e y b o a r d c o n t r o l l e r
# to e m p t y .
#
empty_8042 :
pushl % e c x
movl $ 1 0 0 0 0 0 , % e c x
empty_8042_loop :
decl % e c x
jz e m p t y _ 8 0 4 2 _ e n d _ l o o p
call d e l a y
inb $ 0 x64 , % a l # 8042 s t a t u s p o r t
testb $ 1 , % a l # o u t p u t b u f f e r ?
jz n o _ o u t p u t
call d e l a y
inb $ 0 x60 , % a l # r e a d i t
jmp e m p t y _ 8 0 4 2 _ l o o p
no_output :
testb $ 2 , % a l # i s i n p u t b u f f e r f u l l ?
jnz e m p t y _ 8 0 4 2 _ l o o p # y e s - l o o p
empty_8042_end_loop :
popl % e c x
ret
# Read t h e c m o s c l o c k . R e t u r n t h e s e c o n d s i n a l
gettime :
pushw % c x
movb $ 0 x02 , % a h
int $ 0 x1 a
movb % d h , % a l # % d h c o n t a i n s t h e s e c o n d s
andb $ 0 x0 f , % a l
movb % d h , % a h
movb $ 0 x04 , % c l
shrb % c l , % a h
aad
popw % c x
ret
# Delay i s n e e d e d a f t e r d o i n g I / O
delay :
outb % a l ,$ 0 x80
ret
# Descriptor t a b l e s
gdt :
.word 0 , 0 , 0 , 0 # dummy
.word 0 , 0 , 0 , 0 # unused
.word 0xFFFF # 4 Gb - ( 0 x10 0 0 0 0 * 0 x10 0 0 = 4 G b )
.word 0 # base a d d r e s s = 0
.word 0x9A00 # code r e a d / e x e c
.word 0x00CF # granularity = 4 0 9 6 , 3 8 6
# ( + 5 th n i b b l e o f l i m i t )
.word 0xFFFF # 4 Gb - ( 0 x10 0 0 0 0 * 0 x10 0 0 = 4 G b )
.word 0 # base a d d r e s s = 0
.word 0x9200 # data r e a d / w r i t e
.word 0x00CF # granularity = 4 0 9 6 , 3 8 6
# ( + 5 th n i b b l e o f l i m i t )
idt_48 :
.word 0 # idt l i m i t = 0
.word 0 , 0 # idt b a s e = 0 L
gdt_48 :
.word 0x8000 # gdt l i m i t =2048 ,
# 2 5 6 GDT e n t r i e s
.word 0 , 0 # gdt b a s e ( f i l l e d i n l a t e r )
# Include v i d e o s e t u p & d e t e c t i o n c o d e
# include " v i d e o . S "
# Setup s i g n a t u r e - - m u s t b e l a s t
setup_sig1 : .word S I G 1
setup_sig2 : .word S I G 2
# After t h i s p o i n t , t h e r e i s s o m e f r e e s p a c e w h i c h i s u s e d b y t h e v i d e o m o d e
# handling c o d e t o s t o r e t h e t e m p o r a r y m o d e t a b l e ( n o t u s e d b y t h e k e r n e l ) .
modelist :
.text
endtext :
.data
enddata :
.bss
endbss :