如何修复“os.asm:113: error: TIMES value -138 is negative"汇编语言 [英] How to fix "os.asm:113: error: TIMES value -138 is negative" in assembly language

查看:15
本文介绍了如何修复“os.asm:113: error: TIMES value -138 is negative"汇编语言的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

我正在用汇编语言开发操作系统.在某个时间,我从 NASM 收到此错误:

<块引用>

os.asm:113: 错误:TIMES 值 -138 为负

我想把这个项目进行到底.只有这样的错误让我绝望!

代码如下:

BITS 16开始:移动斧头,07C0h;在此引导加载程序之后设置 4K 堆栈空间添加斧头,288;(4096 + 512)/每段 16 字节mov ss, 斧头mov sp, 4096移动斧头,07C0h;将数据段设置为我们加载的位置mov ds, 斧头调用 clsMOV 啊, 06h ;向上滚动功能XOR AL, AL ;清除整个屏幕异或 CX, CX ;左上角CH=行,CL=列MOV DX, 184FH ;右下角DH=行,DL=列MOV BH, 1Eh ;黄对蓝INT 10Hmov si, text_string ;将字符串位置放入 SI调用 print_string ;调用我们的字符串打印例程push bx ;推送寄存器推送 cx推dx移动啊,0h整数 16 小时cmp al, '1'je 重启cmp al, '2'je 关机cmp al, '3'我关于cmp al, '4'我的消息cmp al, '5'je 关机cmp al, '6'我学分jmp $;跳到这里 - 无限循环!text_string db '|主菜单||Smile OS V1.4|',13,10,'1) 重启',13,10,'2) 关机',13,10,'3) 关于',13,10,'4) 消息',13,10,'5) 系统暂停',13,10,'6) 积分',0about_string db '|About|',13,10,'Smile OS 是一个基于控制台的汇编语言操作系统.Alex~s Software 完成了 8 小时的紧张工作.很多错误但解决了,非常成功.',13,10,'按任意键返回!',0message_str db '|Message|',10,13,'Hello, World!',13,10,'按任意键返回!',0cr_str db '|Credits|',13,10,'Copyright © 2018 Alex~s Software',13,10,'主程序员:Alex',13,10,'Graphichs:什么图形?',13,10,'想法:没有人 :)',0重启:移动斧头,019 小时关掉:移动斧头,0x1000mov ax, ssmov sp, 0xf000移动斧头,0x5307移动 bx, 0x0001mov cx, 0x0003整数 0x15学分:调用 clsmov si, cr_str ;将字符串位置放入 SI调用 print_string ;调用我们的字符串打印例程push bx ;推送寄存器推送 cx推dx移动啊,0h整数 16 小时我开始信息:调用 clsmov si, message_str ;将字符串位置放入 SI调用 print_string ;调用我们的字符串打印例程push bx ;推送寄存器推送 cx推dx移动啊,0h整数 16 小时我开始分类:普萨移动啊,0x00移动, 0x03 ;文本模式 80x25 16 色整数 0x10波帕退关于:调用 clsmov si, about_string ;将字符串位置放入 SI调用 print_string ;调用我们的字符串打印例程push bx ;推送寄存器推送 cx推dx移动啊,0h整数 16 小时我开始打印字符串:;例程:将 SI 中的字符串输出到屏幕移动啊, 0Eh ;int 10h '打印字符' 函数.重复:lodsb ;从字符串中获取字符cmp al, 0je .done ;如果 char 为零,则字符串结束整数 10 小时;否则打印jmp .repeat.完毕:退时间 512 - ($ - $$) db 0签名 dw 0xaa55

为什么 Times 值为负?为什么其他人没有得到同样的错误?(或类似)

我用这个:

<块引用>

NASM 2.14 版

Oracle VM VirtualBox 版本 6.0.0_RC1

windows 0.5 版的 rawwrite dd.

用于编译:

nasm os.asm -f bin -o os.bindd if=/dev/zero of=os.img bs=1024 count=1440dd if=os.bin of=os.img

解决方案

TL;DR : 您的代码和数据太大,与文件最后 2 个字节的引导签名发生冲突.下面的代码是一个软盘引导加载程序,它读取第二阶段(您的内核)并将控制权转移给它.提供的 BPB 适用于 1.44MiB 软盘.与引导加载程序不同,stage2 将被加载到物理地址 0x07e00(紧跟在内存中的引导加载程序之后).这允许您的代码大小高达 32.5KiB.如果需要,您的第二阶段可以读取更多扇区.这段代码的设计目的是让其他人可以将其用作读取第二阶段并将控制权转移给它的模板.

<小时>

这个问题实际上已经在您之前的

信用屏幕显示为:

<小时>

注意事项:

1您使用这些包含错误的命令:

nasm os.asm -f bin -o os.bindd if=/dev/zero of=os.img bs=1024 count=1440dd if=os.bin of=os.img

最后一行应该是 dd if=os.bin of=os.img conv=notrunc 以便在 os.bin 文件写入其中.如果您查看磁盘映像的大小,您可能会发现不是预期的 1474560.

<小时>

2另一种 stage2info.inc 文件使用 0x07e0:0x0000 而不是 0x0000:0x7e00 将控制转移到 stage2:

STAGE2_ABS_ADDR equ 0x07e00 ;stage2的物理地址;用于将 (FAR JMP) 控制转移到 Stage2 的 Segment 和 Offset;段:偏移= 0x07e0:0x0000STAGE2_RUN_SEG 等于 STAGE2_ABS_ADDR>>4STAGE2_RUN_OFS 等于 0x0000

I'm developing an operating system in assembly language. At a certain time i get this error from NASM:

os.asm:113: error: TIMES value -138 is negative

I want to take this project to the end. Only the errors like that despair me!

Here is the code:

BITS 16

start:
    mov ax, 07C0h       ; Set up 4K stack space after this bootloader
    add ax, 288     ; (4096 + 512) / 16 bytes per paragraph
    mov ss, ax
    mov sp, 4096
    mov ax, 07C0h       ; Set data segment to where we're loaded
    mov ds, ax
    call cls
    MOV AH, 06h    ; Scroll up function
    XOR AL, AL     ; Clear entire screen
    XOR CX, CX     ; Upper left corner CH=row, CL=column
    MOV DX, 184FH  ; lower right corner DH=row, DL=column 
    MOV BH, 1Eh    ; YellowOnBlue
    INT 10H
    mov si, text_string ; Put string position into SI
    call print_string   ; Call our string-printing routine
push bx ;push registers
push cx
push dx
mov ah,0h
int 16h
       cmp al, '1'
       je reboot
       cmp al, '2'
       je shutdown
       cmp al, '3'
       je about
       cmp al, '4'
       je message
       cmp al, '5'
       je shutdown
       cmp al, '6'
       je credits

       jmp $            ; Jump here - infinite loop!


    text_string db '|Main Menu| |Smile OS V1.4|',13,10,'1) Reboot',13,10,'2) Shutdown',13,10,'3) About',13,10,'4) Message',13,10,'5) System Halt',13,10,'6) Credits',0
    about_string db '|About|',13,10,'Smile OS is a console based operating system in assembly language. 8 hours of intense work done by Alex~s Software. Many errors but solved and very successful.',13,10,'Press any key to go back!',0
    message_str db '|Message|',10,13,'Hello, World!',13,10,'Press any key to go back!',0
    cr_str db '|Credits|',13,10,'Copyright © 2018 Alex~s Software',13,10,'Main Programer: Alex',13,10,'Graphichs: What graphics?',13,10,'Idea:  nobody :)',0

reboot:
mov ax, 0
int 19h

shutdown:
mov ax, 0x1000
mov ax, ss
mov sp, 0xf000
mov ax, 0x5307
mov bx, 0x0001
mov cx, 0x0003
int 0x15

credits:
call cls
mov si, cr_str  ; Put string position into SI
call print_string   ; Call our string-printing routine
push bx ;push registers
push cx
push dx
mov ah,0h
int 16h
je start

message:
call cls
mov si, message_str ; Put string position into SI
call print_string   ; Call our string-printing routine
push bx ;push registers
push cx
push dx
mov ah,0h
int 16h
je start

cls:
  pusha
  mov ah, 0x00
  mov al, 0x03  ; text mode 80x25 16 colours
  int 0x10
  popa
  ret

about:
call cls
mov si, about_string    ; Put string position into SI
call print_string   ; Call our string-printing routine
push bx ;push registers
push cx
push dx
mov ah,0h
int 16h 
je start

print_string:           ; Routine: output string in SI to screen
    mov ah, 0Eh     ; int 10h 'print char' function

.repeat:
    lodsb           ; Get character from string
    cmp al, 0
    je .done        ; If char is zero, end of string
    int 10h         ; Otherwise, print it
    jmp .repeat

.done:
    ret     

times   512 - ($ - $$)    db  0
signature       dw      0xaa55

Why Times value is negative? Hhy others do not get the same error? (Or like that)

I use this :

NASM version 2.14

Oracle VM VirtualBox version 6.0.0_RC1

rawwrite dd for windows version 0.5.

For compile:

nasm os.asm -f bin -o os.bin  
dd if=/dev/zero of=os.img bs=1024 count=1440   
dd if=os.bin of=os.img

解决方案

TL;DR : Your code and data is too big and collided with the boot signature in the last 2 bytes of the file. The code below is a floppy disk bootloader that reads a second stage (your kernel) and transfers control to it. The provided BPB is for a 1.44MiB floppy. Unlike a bootloader, stage2 will be loaded to physical address 0x07e00 (right after the bootloader in memory). This allows your code to be up to 32.5KiB in size. Your second stage can read more sectors if needed. This code has been designed so others can use this as a template for reading a second stage and transferring control to it.


This question has actually been already answered under your previous Stackoverflow Question. There is a warning about the padding using times 512 - ($ - $$) db 0x00 needing to be 510 and not 512. The answer warns of too much code and data (exceeding 512 bytes), and a way to get better error/warnings from NASM about the size. The note in my other answer summarizes the size issue as:

If the file os.bin is more than 512 bytes then you will need to use the BIOS to read more disk sectors into memory manually. The disk reads from a floppy can be done with INT 13h/AH=2h.

What wasn't provided was a mechanism (example) that uses NASM and INT 13h/AH=2h to read more disk sectors (aka stage2) into memory right after the bootloader at physical address 0x07E00. The code is commented, but it effectively does:

  • The start up code properly sets up segment registers and uses the boot drive passed by the BIOS in the DL register. This is discussed in my Stackoverflow General Bootloader Tips
  • The stack is placed below the bootloader at 0x0000:0x7c00. Setting your own stack is important when reading data into memory outside 0x7c00 to 0x7dff since you don't know where the BIOS set the default stack (SS:SP).
  • Presents itself as a 1.44MB floppy with a BIOS Parameter Block to make it compatible with USB Floppy Drive Emulation booting on real hardware.
  • Stage2 is read a sector at a time using INT 13h/AH=2h starting at 0x07e00. It supports retry on errors.
  • Once Stage2 is finished loading the kernel, the bootloader transfers control to the stage2 code at 0x0000:0x7E00 (stage2_start)
  • Stage2 can contain the code you wish to run. You will have 32.5KiB of space to test your code rather than the limitations of a single boot sector (512 bytes).
  • Stage2's disk sectors immediately follow the boot sector in the disk image.
  • Your Stage2 (kernel) code goes into stage2.asm. stage2.asm gets assembled into stage2.bin and os.asm includes the binary file stage2.bin so that the size of stage2 can be determined for purposes of loading it into memory by the bootloader.
  • stage2.asm must use ORG 0x7e00 since the process above will be loading this code to 0x7e00, so the ORG (origin point) must be set to match.
  • This bootloader will pass the original boot drive number (passed by the BIOS) in register DL to the code running in stage2.
  • The file stage2info.inc defines constants to determine what the origin point of stage2 is, and what segment and offset should be used for the FAR JMP when transferring control to it. The default version of this file assumes stage2 is accessed via 0x0000:0x7e00. An alternative version2 of the file can be used to make that 0x07e0:0x0000. The latter version allows your code to take up a full 64kb segment.

The Code:

bpb.inc:

    jmp boot_start
    TIMES 3-($-$$) DB 0x90   ; Support 2 or 3 byte encoded JMPs before BPB.

bpb_disk_info:
    ; Dos 4.0 EBPB 1.44MB floppy
    OEMname:           db    "mkfs.fat"  ; mkfs.fat is what OEMname mkdosfs uses
    bytesPerSector:    dw    512
    sectPerCluster:    db    1
    reservedSectors:   dw    1
    numFAT:            db    2
    numRootDirEntries: dw    224
    numSectors:        dw    2880
    mediaType:         db    0xf0
    numFATsectors:     dw    9
    sectorsPerTrack:   dw    18
    numHeads:          dw    2
    numHiddenSectors:  dd    0
    numSectorsHuge:    dd    0
    driveNum:          db    0
    reserved:          db    0
    signature:         db    0x29
    volumeID:          dd    0x2d7e5a1a
    volumeLabel:       db    "NO NAME    "
    fileSysType:       db    "FAT12   "

stage2info.inc:

STAGE2_ABS_ADDR   equ 0x07e00    ; Physical address of stage2

; Segment and Offset to use to transfer (FAR JMP) control to Stage2
;     Segment:Offset = 0x0000:0x7e00
STAGE2_RUN_SEG   equ 0x0000
STAGE2_RUN_OFS   equ STAGE2_ABS_ADDR

os.asm:

%include "stage2info.inc"

STAGE2_LOAD_SEG  equ STAGE2_ABS_ADDR>>4
                                ; Segment to start reading Stage2 into
                                ;     right after bootloader

STAGE2_LBA_START equ 1          ; Logical Block Address(LBA) Stage2 starts on
                                ;     LBA 1 = sector after boot sector
STAGE2_LBA_END   equ STAGE2_LBA_START + NUM_STAGE2_SECTORS
                                ; Logical Block Address(LBA) Stage2 ends at
DISK_RETRIES     equ 3          ; Number of times to retry on disk error

bits 16
ORG 0x7c00

; Include a BPB (1.44MB floppy with FAT12) to be more comaptible with USB floppy media
%include "bpb.inc"

boot_start:
    xor ax, ax                  ; DS=SS=ES=0 for stage2 loading
    mov ds, ax
    mov ss, ax                  ; Stack at 0x0000:0x7c00
    mov sp, 0x7c00
    cld                         ; Set string instructions to use forward movement

    ; Read Stage2 1 sector at a time until stage2 is completely loaded
load_stage2:
    mov [bootDevice], dl        ; Save boot drive
    mov di, STAGE2_LOAD_SEG     ; DI = Current segment to read into
    mov si, STAGE2_LBA_START    ; SI = LBA that stage2 starts at
    jmp .chk_for_last_lba       ; Check to see if we are last sector in stage2

.read_sector_loop:
    mov bp, DISK_RETRIES        ; Set disk retry count

    call lba_to_chs             ; Convert current LBA to CHS
    mov es, di                  ; Set ES to current segment number to read into
    xor bx, bx                  ; Offset zero in segment

.retry:
    mov ax, 0x0201              ; Call function 0x02 of int 13h (read sectors)
                                ;     AL = 1 = Sectors to read
    int 0x13                    ; BIOS Disk interrupt call
    jc .disk_error              ; If CF set then disk error

.success:
    add di, 512>>4              ; Advance to next 512 byte segment (0x20*16=512)
    inc si                      ; Next LBA

.chk_for_last_lba:
    cmp si, STAGE2_LBA_END      ; Have we reached the last stage2 sector?
    jl .read_sector_loop        ;     If we haven't then read next sector

.stage2_loaded:
    mov ax, STAGE2_RUN_SEG      ; Set up the segments appropriate for Stage2 to run
    mov ds, ax
    mov es, ax

    ; FAR JMP to the Stage2 entry point at physical address 0x07e00
    jmp STAGE2_RUN_SEG:STAGE2_RUN_OFS

.disk_error:
    xor ah, ah                  ; Int13h/AH=0 is drive reset
    int 0x13
    dec bp                      ; Decrease retry count
    jge .retry                  ; If retry count not exceeded then try again

error_end:
    ; Unrecoverable error; print drive error; enter infinite loop
    mov si, diskErrorMsg        ; Display disk error message
    call print_string
    cli
.error_loop:
    hlt
    jmp .error_loop

; Function: print_string
;           Display a string to the console on display page 0
;
; Inputs:   SI = Offset of address to print
; Clobbers: AX, BX, SI

print_string:
    mov ah, 0x0e                ; BIOS tty Print
    xor bx, bx                  ; Set display page to 0 (BL)
    jmp .getch
.repeat:
    int 0x10                    ; print character
.getch:
    lodsb                       ; Get character from string
    test al,al                  ; Have we reached end of string?
    jnz .repeat                 ;     if not process next character
.end:
    ret

;    Function: lba_to_chs
; Description: Translate Logical block address to CHS (Cylinder, Head, Sector).
;              Works for all valid FAT12 compatible disk geometries.
;
;   Resources: http://www.ctyme.com/intr/rb-0607.htm
;              https://en.wikipedia.org/wiki/Logical_block_addressing#CHS_conversion
;              https://stackoverflow.com/q/45434899/3857942
;              Sector    = (LBA mod SPT) + 1
;              Head      = (LBA / SPT) mod HEADS
;              Cylinder  = (LBA / SPT) / HEADS
;
;      Inputs: SI = LBA
;     Outputs: DL = Boot Drive Number
;              DH = Head
;              CH = Cylinder (lower 8 bits of 10-bit cylinder)
;              CL = Sector/Cylinder
;                   Upper 2 bits of 10-bit Cylinders in upper 2 bits of CL
;                   Sector in lower 6 bits of CL
;
;       Notes: Output registers match expectation of Int 13h/AH=2 inputs
;
lba_to_chs:
    push ax                     ; Preserve AX
    mov ax, si                  ; Copy LBA to AX
    xor dx, dx                  ; Upper 16-bit of 32-bit value set to 0 for DIV
    div word [sectorsPerTrack]  ; 32-bit by 16-bit DIV : LBA / SPT
    mov cl, dl                  ; CL = S = LBA mod SPT
    inc cl                      ; CL = S = (LBA mod SPT) + 1
    xor dx, dx                  ; Upper 16-bit of 32-bit value set to 0 for DIV
    div word [numHeads]         ; 32-bit by 16-bit DIV : (LBA / SPT) / HEADS
    mov dh, dl                  ; DH = H = (LBA / SPT) mod HEADS
    mov dl, [bootDevice]        ; boot device, not necessary to set but convenient
    mov ch, al                  ; CH = C(lower 8 bits) = (LBA / SPT) / HEADS
    shl ah, 6                   ; Store upper 2 bits of 10-bit Cylinder into
    or  cl, ah                  ;     upper 2 bits of Sector (CL)
    pop ax                      ; Restore scratch registers
    ret

; Uncomment these lines if not using a BPB (via bpb.inc)
; numHeads:        dw 2         ; 1.44MB Floppy has 2 heads & 18 sector per track
; sectorsPerTrack: dw 18

bootDevice:      db 0x00
diskErrorMsg:    db "Unrecoverable disk error!", 0

; Pad boot sector to 510 bytes and add 2 byte boot signature for 512 total bytes
TIMES 510-($-$$) db  0
dw 0xaa55

; Beginning of stage2. This is at 0x7E00 and will allow your stage2 to be 32.5KiB
; before running into problems. DL will be set to the drive number originally
; passed to us by the BIOS.

NUM_STAGE2_SECTORS equ (stage2_end-stage2_start+511) / 512
                                ; Number of 512 byte sectors stage2 uses.

stage2_start:
    ; Insert stage2 binary here. It is done this way since we
    ; can determine the size(and number of sectors) to load since
    ;     Size = stage2_end-stage2_start
    incbin "stage2.bin"

; End of stage2. Make sure this label is LAST in this file!
stage2_end:

You place all the code you want to test in the file stage2.asm which will be included by my version of os.asm. A version of your code with the unnecessary parts at the beginning and end removed is:

stage2.asm

%include "stage2info.inc"
ORG STAGE2_RUN_OFS

BITS 16

start:
    ; Removed the segment and stack code
    call cls
    MOV AH, 06h    ; Scroll up function
    XOR AL, AL     ; Clear entire screen
    XOR CX, CX     ; Upper left corner CH=row, CL=column
    MOV DX, 184FH  ; lower right corner DH=row, DL=column
    MOV BH, 1Eh    ; YellowOnBlue
    INT 10H
    mov si, text_string ; Put string position into SI
    call print_string   ; Call our string-printing routine
push bx ;push registers
push cx
push dx
mov ah,0h
int 16h
       cmp al, '1'
       je reboot
       cmp al, '2'
       je shutdown
       cmp al, '3'
       je about
       cmp al, '4'
       je message
       cmp al, '5'
       je shutdown
       cmp al, '6'
       je credits

       jmp $            ; Jump here - infinite loop!


    text_string db '|Main Menu| |Smile OS V1.4|',13,10,'1) Reboot',13,10,'2) Shutdown',13,10,'3) About',13,10,'4) Message',13,10,'5) System Halt',13,10,'6) Credits',0
    about_string db '|About|',13,10,'Smile OS is a console based operating system in assembly language. 8 hours of intense work done by Alex~s Software. Many errors but solved and very successful.',13,10,'Press any key to go back!',0
    message_str db '|Message|',10,13,'Hello, World!',13,10,'Press any key to go back!',0
    cr_str db '|Credits|',13,10,'Copyright © 2018 Alex~s Software',13,10,'Main Programer: Alex',13,10,'Graphichs: What graphics?',13,10,'Idea:  nobody :)',0

reboot:
mov ax, 0
int 19h

shutdown:
mov ax, 0x1000
mov ax, ss
mov sp, 0xf000
mov ax, 0x5307
mov bx, 0x0001
mov cx, 0x0003
int 0x15

credits:
call cls
mov si, cr_str  ; Put string position into SI
call print_string   ; Call our string-printing routine
push bx ;push registers
push cx
push dx
mov ah,0h
int 16h
je start

message:
call cls
mov si, message_str ; Put string position into SI
call print_string   ; Call our string-printing routine
push bx ;push registers
push cx
push dx
mov ah,0h
int 16h
je start

cls:
  pusha
  mov ah, 0x00
  mov al, 0x03  ; text mode 80x25 16 colours
  int 0x10
  popa
  ret

about:
call cls
mov si, about_string    ; Put string position into SI
call print_string   ; Call our string-printing routine
push bx ;push registers
push cx
push dx
mov ah,0h
int 16h
je start

print_string:           ; Routine: output string in SI to screen
    mov ah, 0Eh     ; int 10h 'print char' function

.repeat:
    lodsb           ; Get character from string
    cmp al, 0
    je .done        ; If char is zero, end of string
    int 10h         ; Otherwise, print it
    jmp .repeat

.done:
    ret

You then assemble and build the disk image with these commands1:

# Build stage2 (kernel) FIRST as os.asm will include stage2.bin
nasm -f bin stage2.asm -o stage2.bin
# Build and combine stage1 (boot sector) and stage2 (kernel)
nasm -f bin os.asm -o os.bin

# Build 1.44MB disk image
dd if=/dev/zero of=disk.img bs=1024 count=1440
dd if=os.bin of=disk.img conv=notrunc

Lines starting with # are just comments and are not commands.


Screenshots

The main menu appears as:

The credit screen appears as:


Notes:

1You use these commands which contains an error:

nasm os.asm -f bin -o os.bin  
dd if=/dev/zero of=os.img bs=1024 count=1440   
dd if=os.bin of=os.img

The last line should be dd if=os.bin of=os.img conv=notrunc so that the 1.44MB disk image doesn't get truncated when the os.bin file is written to it. If you look at the size of your disk image you will probably see that is not the expected 1474560.


2An alternative stage2info.inc file to use 0x07e0:0x0000 instead of 0x0000:0x7e00 to transfer control to stage2:

STAGE2_ABS_ADDR   equ 0x07e00    ; Physical address of stage2

; Segment and Offset to use to transfer (FAR JMP) control to Stage2
;     Segment:Offset = 0x07e0:0x0000
STAGE2_RUN_SEG   equ STAGE2_ABS_ADDR>>4
STAGE2_RUN_OFS   equ 0x0000

这篇关于如何修复“os.asm:113: error: TIMES value -138 is negative"汇编语言的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆