Read the operating system boot program roughly

Keywords: Linux Linker Assembly Language less

[1] linux 0.11 bootsect.s

  • Copy the contents of the memory segment [0x07c00, 0x07e00) to the memory segment [0x90000, 0x90200],
    Then jump to 0x9000 segment to execute the program that is not executed after bootdetect. S.
  • The subsequent program of bootsec. S will start the setup.s program in the disk (floppy disk) into the [0x90200, 0x90a00] memory segment.
  • Then read the operating system program in the boot disk into the [0x10000, 0x40000) memory segment.
  • Check and set the root file system device number for subsequent operating system programs based on the check results
    (the default root file device number 0x306 is set at the bootsec. S 508 offset.).
  • Finally, jump to the setup.s program.
!
! SYS_SIZE is the number of clicks (16 bytes) to be loaded.
! 0x3000 is 0x30000 bytes = 196kB, more than enough for current
! versions of linux
! 
! SYSSIZE To load from the boot disk linux 0.11 Size of operating system program, !
! Operating system program refers to head.s And after C Program. !
! The value is x86 Segments in real mode(Omit the lowest 4 bits of 0)As a unit, !
! Namely SYSSIZE The actual value is 0 x30000, That is 192 Kb(0x30000 >> 10 ), !
! about linux 0.11 Speaking, 192Kb Larger than the actual size of its operating system program.!
SYSSIZE = 0x3000
!
!	bootsect.s		(C) 1991 Linus Torvalds
!
! bootsect.s is loaded at 0x7c00 by the bios-startup routines, and moves
! iself out of the way to address 0x90000, and jumps there.
!
! It then loads 'setup' directly after itself (0x90200), and the system
! at 0x10000, using BIOS interrupts. 
!
! NOTE! currently system is at most 8*65536 bytes long. This should be no
! problem, even in the future. I want to keep it simple. This 512 kB
! kernel size should be enough, especially as this doesn't contain the
! buffer cache as in minix
!
! The loader has been made as simple as possible, and continuos
! read errors will result in a unbreakable loop. Reboot by hand. It
! loads pretty fast by getting whole sectors at a time whenever possible.
!
! Be located BIOS Boot disk(It was a floppy disk)Boot area bootsect.s 512 bytes in total.!
! Power on the computer BIOS After initialization execution, !
! BIOS It will automatically read 512 bytes of boot area to !
! [0x07c00, 0x07e00)In the memory segment corresponding to the memory address segment, !
! 0 is now being checked x07dfe And 0 x07dff Two bytes are 0 xAA55 Time !
! Jump to 0 x07c00 Instructions in memory are executed bootsect.s Program.!
! 
! along with bootsect.s Being executed,
! He will first[0x07c00, 0x07e00)The contents of the memory segment are copied to[0x90000, 0x90200)Memory segment, !
! Then jump to 0 x9000 Execution in paragraph bootsect.s stay[0x07c00, 0x07e00)Subsequent code not executed in.!
! 
! At 0 x9000 Execution in paragraph bootsect.s Mainly completed !
! [1] Will start the setup.s Program read to[0x90200, 0x90a00)Memory segment; !
! [2] Copy the operating system program on the boot disk to the[0x10000, 0x40000)In memory segment.!
!
! Though for linux 0.11 Speaking,
! bootsect.s Read 0 at most from the startup disk x30000(192Kb)Operating system program into memory,
! But the author has reserved 8*65536=2^19 Byte 512 Kb Memory space, To be expanded in the future.!
!
! bootsect.s Want to read operating system programs into memory as easily as possible from the startup disk, !
! Error in reading, that bootsect.s Will enter a reread or a pure dead cycle, !
! So we have to restart the computer to solve this embarrassing situation.!


! .globl by(as86 Of)Assembly pseudo instruction: statement begtext Etc. are global labels.
! .text .data .bss Respectively(as86)A pseudoinstruction in an assembler that identifies a code segment data addition segment.
! They told(as86/ld86)Assembly compiler and linker,
! begtext and endtext The labels are the beginning and the end of the code segment(address), 
! begdata and enddata The label is the start and end address of the data segment, 
! begbss and endbss The label is the start and end address of the data additional segment.
! When these labels are referenced in the program, The linker will convert them to the appropriate address value.
! 
! although bootsect.s Program instructions and program data are mixed together, 
! No other program refers to the label defined by these pseudo instructions, But they can still be understood in this way.
.globl begtext, begdata, begbss, endtext, enddata, endbss
.text
begtext:
.data
begdata:
.bss
begbss:
.text

! setup.s The number of sectors in the boot disk.
SETUPLEN = 4				! nr of setup-sectors
!
! Paragraph base address, Omit the 0 of the lower 4 bits.
BOOTSEG  = 0x07c0			! original address of boot-sector
INITSEG  = 0x9000			! we move boot here - out of the way
SETUPSEG = 0x9020			! setup starts here
SYSSEG   = 0x1000			! system loaded at 0x10000 (65536).
ENDSEG   = SYSSEG + SYSSIZE		! where to stop loading

! ROOT_DEV:	0x000 - same type of floppy as boot.
!		0x301 - first partition on first drive etc
! Set default root file system device(partition), It is stored in bootsect.s 508 offset of.
! linux 0.11 Mapping external devices and zones with logical numbers, 0x306 Corresponds to the first partition of the second hard disk.
! Understand device drivers such as kernel/blk_drv/hd.c(sys_setup)Then go back and understand the procedure.
ROOT_DEV = 0x306

! Pseudo instruction entry, 
! Tell assembly linker start by bootsect.s Command entry to the program.
entry start
!
! take[0x07c00, 0x07e00)Segment contents copied to[0x90000, 0x90200)In memory segment.
! (cld) rep movw(Should be rep movsw?) Statement is equivalent to 
! while (cx--) 
!    movw es:di, ds:si
!    si += 2
!    di += 2
start:
	mov	ax,#BOOTSEG
	mov	ds,ax
	mov	ax,#INITSEG
	mov	es,ax
	mov	cx,#256
	sub	si,si
	sub	di,di
	rep
	movw
! 
! After copying the bootstrap, Jump to the new memory segment to execute the subsequent program.
! jmpi offset, seg Jump between segments cs = seg, ip = offset. 
! seg Segment base address, offset Based on seg Offset of the segment.
!
! jmpi go, INITSEG Jump to execute 0 x9000:go Instructions.
! here, go At 0 x7c00 Duan and 0 x9000 Same offset in segment(That's why we can jump right). 
	jmpi	go,INITSEG
!
! take ds and es Data segment register assignment segment base address 0 x9000, In order to access 0 correctly x9000 Data in the segment.
go:	mov	ax,cs
	mov	ds,ax
	mov	es,ax
! The ss:sp Register set to 0 x9000:0x9ff0, 
! sp=0x9ff0 It will reserve enough memory for the program code, !
! Reasonable stack operation will not cover the program code in memory.
! bootsect.s and setup.s stay[0x90000, 0x90a00)Memory segment, 
! Subsequently read operating system code will be temporarily stored in[0x10000, 0x40000)In memory segment.
! put stack at 0x9ff00.
	mov	ss,ax
	mov	sp,#0xFF00		! arbitrary value >>512

! load the setup-sectors directly after the bootblock.
! Note that 'es' is already set up.
! After setting data and stack register, 
! The next read is on the boot disk(floppy disk)in[1..5]Sector setup.s Program to[0x90200, 0x90a00)Memory segment,
! If the read fails, reset the floppy disk to read again, Until the read is successful.
load_setup:
	mov	dx,#0x0000		! drive 0, head 0
	mov	cx,#0x0002		! sector 2, track 0
	mov	bx,#0x0200		! address = 512, in INITSEG
	mov	ax,#0x0200+SETUPLEN	! service 2, nr of sectors
	int	0x13			! read it
	jnc	ok_load_setup		! ok - continue
	mov	dx,#0x0000
	mov	ax,#0x0000		! reset the diskette
	int	0x13
	j	load_setup
! Trial inspection BIOS 13h Interrupt call manual.
! Participation.
! ah = 02h, call BIOS 13h in(Subprocess No. 02 h)Read disk subprogram of;
! al = Number of sectors to read, SETUPLEN=4;
! es:bx = Memory first address to store the read content, 0x9000:200;
! dh = head number, 0x00; dl = Drive number, 0x00 Drive for diskette;
! cx = 0x0002, Read from sector 2 of cylinder 0.
! |F|E|D|C|B|A|9|8|7|6|5-0|
! | | | | | | | | | |   `----- To read the starting sector
! | | | | | | | | `---------   The height of the initial cylinder to be read is 2
! `------------------------    8 lower positions of the starting cylinder to be read
!
! Sets the parameter flag register.
! ah = Status number(00h-No mistake..., );
! al = Number of sectors read successfully;
! Flag register CF=0, Read successful; CF=1, Read failed.

! read setup.s After success, adopt BIOS 13h Get floppy parameters,
! Track the track(cylinder)Number of sectors stored in cs(0x9000):sectors place,
! Supply bootsect.s Read operating system program use.
ok_load_setup:
! Get disk drive parameters, specifically nr of sectors/track
	mov	dl,#0x00
	mov	ax,#0x0800		! AH=8 is get drive parameters
	int	0x13
	mov	ch,#0x00
	seg cs
	mov	sectors,cx
	mov	ax,#INITSEG
	mov	es,ax

! Print some inane message
! adopt BIOS 10h Interrupt call displays a prompt to read the operating system program to memory.
	mov	ah,#0x03		! read cursor pos
	xor	bh,bh
	int	0x10
	mov	cx,#24
	mov	bx,#0x0007		! page 0, attribute 7 (normal)
	mov	bp,#msg1
	mov	ax,#0x1301		! write string, move cursor
	int	0x10

! ok, we've written the message, now
! we want to load the system (at 0x10000)
! Everything is all set., 
! adopt BIOS 13h Read operating system program to start at 0 x10000 In the memory segment of, Common reading 0 x30000 Byte.
! After reading successfully, Turn off the diskette motor.
! about read_it - You can skip the logical details of reading operating system programs from floppy disks.
	mov	ax,#SYSSEG
	mov	es,ax		! segment of 0x010000
	call	read_it
	call	kill_motor

! After that we check which root-device to use. If the device is
! defined (!= 0), nothing is done and the given device is used.
! Otherwise, either /dev/PS0 (2,28) or /dev/at0 (2,8), depending
! on the number of sectors that the BIOS reports currently.
! After successfully reading the operating system to memory, Next, check which device is the root file system.!
! if root_dev Store value is not 0, !
! Then use the default storage device number here(ROOT_DEV=0x306)The corresponding device is the root file system device.!
! if root_dev Store value is 0, !
! It is determined by the total number of sectors on the floppy track of the boot disk
! /dev/PS0(2, 28)still/dev/at0 (2, 8)The corresponding device is the root file system device.!
! (We need to understand the device driver and file system before we understand the/dev/PS0(2, 28)And so on.)
	seg cs
	mov	ax,root_dev
	cmp	ax,#0
	jne	root_defined
	seg cs
	mov	bx,sectors
	mov	ax,#0x0208		! /dev/ps0 - 1.2Mb
	cmp	bx,#15
	je	root_defined
	mov	ax,#0x021c		! /dev/PS0 - 1.44Mb
	cmp	bx,#18
	je	root_defined
undef_root:
	jmp undef_root
root_defined:
	seg cs
	mov	root_dev,ax

! after that (everyting loaded), we jump to
! the setup-routine loaded directly after
! the bootblock:
! All programs have been read into the specified memory segment, 
! Default devices are also set for the root file system(Number), 
! Now jump jump execute cs:ip=0x9020:0 Jump to execute setup.s Order at the entrance.
	jmpi	0,SETUPSEG


! (1) bootsect.s End of this run, Summarize its main functions.
! -------------------------------------------
! [1] Memory segment[0x07c00, 0x07e00)Copy content to[0x90000, 0x90200)Memory segment,
! Then jump to 0 x9000 Execution in paragraph bootsect.s Subsequent procedures not executed.
! [2] bootsect.s Subsequent programs will start disk(floppy disk)Medium setup.s Program to[0x90200, 0x90a00)In memory segment.
! [3] Then read the operating system program in the boot disk to[0x10000, 0x40000)In memory segment.
! [4] Check and set the root file system device number for subsequent operating system programs based on the check results
! (bootsect.s 508 Root file device number 0 is set by default at offset x306). 
! [5] Last jump execution setup.s Program.
!
! (2) Rough understanding 80 x86 Computer power up to bootsect.s(Bootloader)Be carried out.
! 80x86 After the computer hardware is powered on, CPU Run in real mode by default, BIOS yes CPU The first program to execute.
!
! Simplify understanding BIOS: complete I/O Initialization of hardware and software information.
!
! BIOS I/O Hardware initialization.
! BIOS complete I/O After hardware initialization, I/O Hardware goes into started state, 
! I.e. access energy and CPU Status of communication, Follow-up CPU For each I/O Is based on this state.
! 
! BIOS Software information initialization.
! In memory[0x0, 0x00400)Set up BIOS Interrupt vector table to provide BIOS interrupt call, 
! At the same time, some I/O Device parameter information to memory.
! subsequently BIOS Call it 19 h Interrupt program No. 1 reads the contents of the boot area of the boot disk to[0x07c00, 0x07e00)Memory segment, 
! If the last two bytes of the boot area are 0 xAA55 Jump to 0 x7c00:0 Instructions.
! 
! bootsect.s It is written to the boot area of the boot disk after being converted to machine code, This acts as the boot code.
! stay BIOS Interface, You can set the boot disk or floppy disk, hard disk, etc.
! 
! (3) Rough understanding bootsect.s Memory address space distribution before and after execution.
! BIOS After initialization, The memory address space before the boot code is loaded is roughly distributed.
! 0x00000|----------------------------------|
!        |            1KB RAM               |
!        | BIOS Interrupt vector table etc. |
! 0x003FF|==================================|----
!        |                                  |  ↑
!        |                                  |  |
!        |             639KB                | available
!        |         RAM addr space           |  |
!        |                                  |  |
!        |                                  |  ↓
! 0x9FFFF|==================================|----
!        |                                  |
!        |              128K                |
!        |    video card ram addr space     |
! 0xBFFFF|==================================|
!        |                                  |
!        |             256KB                |
!        |      BIOS ROM addr space         |
!        |                                  |
!        |                                  |
! 0xFFFFF|==================================|
! bootsect.s When accessing memory or reading the startup disk program into memory,
! There is a reference to the memory address space distribution.
! as
! Because it will be used later BIOS Interrupt caller, So memory address space
! [0x0, 0x400)Not used as code or data storage temporarily;
! as
! [0xC0000, 0x100000)For each card ROM Address space of memory module,
! Write operation is not supported in this memory address space;
! as
! [0x400, 0xa0000)by(various)RAM Address space of memory module,
! The free part can be used to store program code or data.
!
! bootsect.s After execution, the memory distribution is roughly as follows.
! 0x00000|----------------------------------|
!        |           1KB RAM                |
!        | BIOS Interrupt vector table etc. |
! 0x003FF|==================================|
!        |             ...                  |
! 0x10000|----------------------------------|
!        |          OS routines             |
! 0x40000|==================================|
!        |             ...                  |
! 0x90000|----------------------------------|← ss(0x9000)
!        |           bootsect.s             |
! 0x90200|==================================|← cs:ip(0x9020:0)
!        |             setup.s              |
! 0x90A00|==================================|
!        |               ...                |← sp(0xff00)
! 0x9FFFF|==================================|
!        |                                  |
!        |              128K                |
!        |    video card ram addr space     |
! 0xBFFFF|==================================|
!        |                                  |
!        |              256KB               |
!        |      BIOS ROM addr space         |
!        |                                  |
!        |                                  |
! 0xFFFFF|==================================|
!
! (4) Rough understanding 80 x86 The real mode operation mechanism synthesizes the memory address.
! At 80 x86 Real mode, Only the first 20 memory address lines are available,
! That is, the memory address space range is[0x0, 0x100000). 
! CPU The register for programming is only 16 bits,
! CPU Use"Paragraph base address << 4 + Offset address"To synthesize a 20 bit memory address
! It is then transferred to the memory address line to address the physical memory unit.
! 
! as
! use ds Storage base address 0 x07c0, use si Save offset address 3,
! be CPU use"Paragraph base address << 4 + Offset address"mode
! take ds:si=0x07c0:3 Synthesized memory address is 0 x07c0 << 4 + 3 = 0x07c03. 
! Namely ds:si Final address to 0 x07c03 The memory address of.
!
! 64 from segment base Kb(16 Bit register maximum offset 64 Kb)Memory is called a segment.
!
! (5) Roughly understand some instructions in 80 x86 Behavior in real mode.
! [1] In segment jump command.
! Unconditional or conditional jump instruction, as jmp/j/je/jnc label
! function: Jump execution label Instructions.
! Jump mode: ip += label reach ip value(After taking the current command)Offset.
!
! call sub_fun
! function: Jump execution sub_fun Instructions.
! Jump mode: push ip, ip += sub_fun reach ip value(After taking the current command)Offset.
!
! ret - Jump to execute the command at the top of the stack, Chang He call Continuous use.
! Jump mode: pop ip. 
!
! Intra segment jump is independent of segment base address and offset start value,
! Segment jump
//The program can run normally anywhere in memory.
! 
! [2] Jump command between segments.
! jmpi offset, seg
! function: Jump execution seg:offset Instructions.
! Jump mode: cs=seg, ip=offset. 
! 
! Jump between segments is independent of segment base address, But the correct offset address needs to be calculated in order to jump correctly.
! As in this procedure jmpi go, #INITSEG instruction, 
! if go The offset value in the current program is start_offset,
! When the current program is loaded into memory, 
! Jump to accounting go Time base address, bring go The offset based on the base address of this section is also start_offset.
! 
! The assembly linker will convert the target operands of each assembly instruction to corresponding values according to the meaning of each instruction.
! As the assembly linker will j label Medium label Convert to label And current ip(After taking the current command)The offset value of.
!
! [3] Explicit stack operation instructions.
! push ax
! function: take ax Press into the top of the stack.
! Stack process: sp -= 2, (sp) = ax;
!
! pop ax
! function: Assign top of stack content to ax. 
! Stack process: ax = (sp), sp += 2. 
!
! Here(sp),
! (sp)Represented by left value sp The memory address pointed to accepts the assignment;(sp)As right value sp Points to content in memory.
! 
! (6) Complement related understanding.
! about k Binary system n digit, Two positive integers that can just overflow by adding are complement numbers to each other.
! For example, three digits in decimal system, And the two numbers of 10000 complement each other, Such as 7000 and 3000, 9999 And 1.
! about k Binary system n digit m, Its complement is equal to(k^n - m). 
!
! Compiler uses complement principle and binary n The greater half of the digits represents a negative number.
! When the compiler encounters a negative number in the program, 
! The complement of the absolute value of the negative number is used to replace the negative number in memory or register.
! It is more convenient to find the complement of a binary number than that of other base numbers, 
! Take the number and add 1 to get, 
! For registers, Negation and addition are basic operations.
! 
! Example with 16 bit binary number, Match the list.
! | 0  ... 32767 | -32768 ...  -1   | Signed Decimal 
! |--------------|-------------------
! | 0  ... 32767 | 32768  ... 65535 | Unsigned decimal number
! |--------------|-------------------
! |0x0 ... 0x7fff| 0x8000 ... 0xffff| Binary number
! |--------------|-------------------
! 
! (7) Follow bootsect.s Some references related to the content.
! [1] 80x86 Enlightenment reference book on the meaning of assembly instructions
! <Assembly language- Wang Shuang.
! 
! [2] BIOS Interrupt call reference manual.
! Find 1453406200@qq.com Email one copy;
! Or download a copy from(Upload this article, But this platform needs 5 points by default when downloading)
! https://download.csdn.net/download/misskissc/10997523
!
! [3] Diskette introduction reference.
! If you want to read carefully
! Read operating system code to[0x10000, 0x40000)The code of memory is read_it, 
! except BIOS Out of reference manual for interrupt call, You may also need to understand the format of floppy disk organization data,
! Refer to 30 day self-made operating system- The third day of Sichuan hexiushi P47_49. 
!
! If you need to understand the principle of floppy disk, such as the information storage layer, you can refer to books such as the principle of computer composition.
!
! (8) Have a rough understanding of the process of making the operating system program on the startup disk.
!       Compiler+Linker      Tools for removing compile link information and organizing it on the startup disk
!             ↓                           ↓
! Source program file ---> Compile link information+Machine instructions+data--->Machine instructions+Data to boot disk.
!
! (9) bootsect.s and setup.s Use as86 Assembly compiler and ld86 The main reason for linkers may be
! At that time, it was more convenient to compile 16 bit executable programs with them.
!
! (10) about AT&T and Intel Assembly format.
! bootsect.s and setup.s Similar Intel Assembler, The assembly involved in the operating system program is AT&T Formatted.
! Intel In assembly instruction, The source operand is on the right, Destination operand is on the left; 
! and AT&T The destination operand of is on the right, The source operand is on the left.
! For reading assembly source, This is the main difference between the two.
! as sub ax, bx
! ax = ax - bx ! intel assembly
! bx = bx - ax ! AT&T assembly
!
! 2019.05.25
! ------------------------


! This routine loads the system at address 0x10000, making sure
! no 64kB boundaries are crossed. We try to load it as fast as
! possible, loading whole tracks whenever we can.
!
! in:	es - starting address segment (normally 0x1000)
!
sread:	.word 1+SETUPLEN	! sectors read of current track
head:	.word 0			! current head
track:	.word 0			! current track

! reat_it And subsequent subroutines pass BIOS 13h Read the operating system program on the boot disk to the !
! [0x10000, 0x40000)In memory segment.!
! Reading read_it Before relevant subprogram, First in BIOS A rough understanding of the lower startup disk-Floppy disk related parameters.
! With 1.4Mb Floppy disk as an example, It has two faces, BIOS 13h Use a magnetic head number(0 start)Corresponding to a face,
! 80 tracks on each side/cylinder, BIOS 13h Use a track number(0 start)Corresponding to one track/cylinder,
! 18 sectors per track, 1 512 bytes in sectors, 
! BIOS 13h Use a sector code(1 start)Corresponding to a sector.
! Namely 2 * 80 * 18 * 512 = 1.4Mb. 
! 
! By continuously organizing the parameters of head, track, sector, etc. in these subprograms
! to BIOS 13h To read operating system programs into memory.
! The general logic of reading the operating system from the boot disk is: 
! for (track = 0; track < 80; ++track) 
!    for (head = 0; head < 2; ++head) 
!       while (Not finished reading current track and head Sector below)
!           if ((Unread sector bytes + Number of bytes read in the current memory segment) < Total bytes size of memory segment)
!               Read the contents of the current unread sector to the current memory segment
!           else 
!               Read part or all of the unread sector contents to the current memory segment to make the current memory segment read full
!               if (Read 0 x30000 byte)
!                   End of reading
!               else 
!                   Continue reading next memory segment
! Push back., When the operating system program was written to the boot disk, it was also written according to this logic.
! 
! sread, head and track Is the initial parameter to read the operating system program, They mean
! Current track read sectors(bootsect.s 1 sector and setup.s 4 sectors of), Head number and track number.
! 
!
! reat_it, 
! Read startup disk-0 on diskette x30000 Byte operating system program to[0x10000, 0x40000)In memory segment.
! BIOS Interrupt call to read disk(int 13h)Will save the read to es:bx In the memory pointed to.
! es With 64 Kb Boundary alignment(es << 4 The last 16 bits are 0), If the initial value does not meet this condition, it enters the dead cycle.
! bx Is the in segment offset address, The initial value is 0.
read_it:
	mov ax,es
	test ax,#0x0fff
die:	jne die			! es must be at 64kB boundary
	xor bx,bx		! bx is starting address within segment

! When es The value is less than 0. x4000 I.e. not read full 0 x30000 Jump on byte ok1_read Continue reading at,
! Otherwise return-Read operating system program complete.
rp_read:
	mov ax,es
	cmp ax,#ENDSEG		! have we loaded all yet?
	jb ok1_read
	ret

ok1_read:
! Calculates the number of sectors that should also be read.
! al = Number of unread sectors = (Number of cylinder sectors - Number of sectors read)
    seg cs
    mov ax,sectors
    sub ax,sread
! Calculate the number of unread sectors corresponding to the number of bytes(Move 9 bits to the left to multiply 512)Whether the sum of bytes of read sectors exceeds 64 Kb
! (16 Carry in bit register means more than 0 xffff, If it just exceeds 0 xffff When 16 bit register value is 0),
! Jump if not ok2_read Read at, If more than 64 Kb Number of sectors required.
    mov cx,ax
    shl cx,#9
    add cx,bx
    jnc ok2_read
    je ok2_read
! In this paper, we use the principle that the compiler uses complement to represent number,
! 16 Negative digit(-bx)The complement of is 0 x10000(64Kb) - bx, That is to say, calculate how many bytes are less than 64 Kb, 
! Convert and store results in sectors to al Register.
    xor ax,ax
    sub ax,bx
    shr ax,#9
    
! call read_track After reading the specified number of sectors from the current location of the boot disk,
! Check that all sectors of the current track have been read, 
! Skip if you have not read all sectors of the current track ok3_read Continue reading sector contents to next memory segment at,
! If it has been read, check whether the current head number is 1, Jump if not 1 ok4_read Reading head No. is on side 1
! All sectors on the current track, If the head number is already 1, the increase track number has read the sector on the next track.
ok2_read:
	call read_track
	mov cx,ax      ! cx=Just now read_track Number of sectors read in
	add ax,sread   ! ax += sread, Current track and number of read sectors under head
	seg cs
	cmp ax,sectors
	jne ok3_read   ! Compare the current total number of read sectors with the total number of track sectors, Unequal(Insufficient)Then jump. ok3_read
	mov ax,#1
	sub ax,head    ! If the current head number is not 1, Jump to execution ok4_head Read the side with head No. 1 of the startup disk at
	jne ok4_read
	inc track      ! If the front and back of the current track(head head=0/1)All have been read, Read next track

! Reset head number,
! if head The original value is 0, be ax stay ok2_read The value retained in is 1,
! if head The original value is 1, be ax stay ok2_read The value in is already 0.
ok4_read:
	mov head,ax
	xor ax,ax

! After updating the parameters related to reading the startup disk and memory segment,
! Jump rp_read Continue reading the boot disk.
ok3_read:
	mov sread,ax  ! Reset the number of read sectors under the current track and head(0 Or total number of read sectors)
	shl cx,#9
	add bx,cx     ! Update offset in current memory segment
	jnc rp_read   ! If carry does not occur in 16 bit register, The current segment is not read full, Then jump. rp_read Continue reading
	mov ax,es
	add ax,#0x1000
	mov es,ax     ! If the current memory segment is full es Point to next memory segment
	xor bx,bx     ! In segment offset reset to 0
	jmp rp_read   ! Jump rp_read Read the contents of the startup disk to the current internal segment

! Read the specified number of sectors from the current location of the boot disk(from ok1_read Calculate and store in al in)
read_track:
	push ax
	push bx
	push cx
	push dx
	mov dx,track
	mov cx,sread
	inc cx         ! from cl[5..0]Sector number corresponding to sector start reading
	mov ch,dl      ! cl[7..6] ch=Track number
	mov dx,head
	mov dh,dl      ! Assign the head number to dh
	mov dl,#0! DL = drive number, 0 is floppy drive number
	and dx,#0x0100! Floppy disk only has two head numbers of 0 / 1, make sure the maximum value of dh is 1
	mov ah,#2! Ah = BIOS 13h function number, 2h means read operation
	int 0x13
	jc bad_rt
	pop dx
	pop cx
	pop bx
	pop ax
	ret
! If the read fails, reset the floppy disk and jump to read_track Continue reading at
bad_rt:	mov ax,#0
	mov dx,#0
	int 0x13
	pop dx
	pop cx
	pop bx
	pop ax
	jmp read_track

/*
 * This procedure turns off the floppy drive motor, so
 * that we enter the kernel in a known state, and
 * don't have to worry about it later.
 */
kill_motor:
	push dx
	mov dx,#0x3f2
	mov al,#0
	outb
	pop dx
	ret

sectors:
	.word 0

msg1:
	.byte 13,10
	.ascii "Loading system ..."
	.byte 13,10,13,10

! org Tell the assembler bootsect.s 2 bytes at offset 508
! Storage root file device root_dev, To leave the last two bytes of the boot disk.
.org 508
root_dev:
	.word ROOT_DEV

! When the last two bytes of the boot disk are 0 xaa55 Indicates that the contents of the boot disk are valid,
! BIOS Read bootloader to[0x7c00, 0x7e00)After memory segment, Jump to 0 when the boot disk is valid x7c00. 
boot_flag:
	.word 0xAA55

.text
endtext:
.data
enddata:
.bss
endbss:

The relevant contents of the reference materials are as follows.

(7) some references related to the content of bootect. S.
[1] enlightenment reference book on the meaning of 80x86 assembly instruction
Assembly language - Wang Shuang.

[2] BIOS interrupt call reference manual.
Send a copy to 1453406200@qq.com;
Or download a copy from the following address (this article is uploaded, but the platform needs 5 points for downloading by default)
https://download.csdn.net/download/misskissc/10997523

[3] floppy disk introduction reference.
If you want to read carefully
Read it is the code that reads the operating system code to [0x10000, 0x40000) memory,
In addition to the BIOS interrupt call reference manual, you may also need to understand the format of floppy disk organization data,
Please refer to 30 day self-made operating system - the third day of Chuanhe Xiushi p47_.
If you need to understand the principle of floppy disk, such as the information storage layer, you can refer to books such as the principle of computer composition.

Posted by phpbrat on Sun, 03 Nov 2019 13:58:32 -0800