This is a continuation of the other answer as the post limit was exceeded.
Example Demonstrating #GP and #UD generated in v8086 mode
The following code is not meant as a primer on entering v8086 mode or writing a proper v8086 monitor (#GP handler). Information on entering v8086 mode can be found in another of my Stackoverflow answers. That answer discusses the mechanisms of getting into v8086 mode. The following code is based on that answer, but includes a TSS, and an Interrupt descriptor table that only handles #UD (exception 6) and #GP (exception 13). I chose #UD because it is an exception without an error code, and I chose #GP because it is an exception with an error code.
Most of the code is support code to print to the display in real and protected mode. The idea behind this example is simply to execute the instruction UD2 in v8086 mode and issue a privileged HLT instruction. I am entering v8086 mode with an IOPL of 0 so HLT causes a #GP exception that is handled by a protected mode GPF handler. #GP has an error code, and #UD does not. To find out if an error code is pushed an exception handler only need to subtract the current ESP from the address of the bottom of the stack. I use a 32-bit gate so with an error code the exception stack frame should be 40 bytes (0x28), and without it should be 36 (0x24).
- With an error code GS, FS, DS, ES, USER_SS, USER_ESP, EFLAGS, CS, EIP, Error code are pushed. Each is 32-bits wide (4 bytes). 10*4=40.
- Without an error code GS, FS, DS, ES, USER_SS, USER_ESP, EFLAGS, CS, EIP are pushed. Each is 32-bits wide (4 bytes). 9*4=36.
The code in v8086 mode does this for the test:
; v8086 code entry point
v86_mode_entry:
    ud2                         ; Cause a #UD exception (no error code pushed)
    mov dword [vidmem_ptr], 0xb8000+80*2
                                ; Advance current video ptr to second line
    hlt                         ; Cause a #GP exception (error code pushed)
    ; End of the test - enter infinite loop sice we didn't provide a way for
    ; the v8086 process to be terminated. We can't do a HLT at ring 3.
.endloop:
    jmp $
There are two protected mode exception handlers reached through a 32-bit interrupt gate. Although long they ultimately do one thing - print out (in hex) the size of the exception stack frame as it appeared right after control reached the exception handler. Because the exception handler uses pusha to save all the general purpose registers, 32 bytes (8*4) is subtracted from the total amount.
; #UD Invalid Opcode v8086 exception handler
exc_invopcode:
    pusha                       ; Save all general purpose registers
    mov eax, DATA32_SEL         ; Setup the segment registers with kernel data selector
    mov ds, eax
    mov es, eax
    cld                         ; DF=0 forward string movement
    test dword [esp+efrm_noerr.user_flags], 1<<EFLAGS_VM_BIT
                                ; Is the VM (v8086) set in the EFLAGS of the code
                                ;     that was interrupted?
    jnz .isvm                   ; If set then proceed with processing the exception
    mov esi, exc_not_vm         ; Otherwise print msg we weren't interrupting v8086 code
    mov ah, ATTR_BWHITE_ON_RED
    call print_string_pm        ; Print message to console
.endloop:
    hlt
    jmp .endloop                ; Infinite HLT loop
.isvm:
    mov esi, exc_msg_ud
    mov ah, ATTR_BWHITE_ON_MAGENTA
    call print_string_pm        ; Print that we are a #UD exception
    ; The difference between the bottom of the kernel stack and the ESP
    ; value (accounting for the extra 8 pushes by PUSHA) is the original
    ; exception stack frame size. Without an error code this should print 0x24.
    mov eax, EXC_STACK-8*4
    sub eax, esp                ; EAX = size of exception stack frame without
                                ;       registers pushed by PUSHA
    mov edi, tmp_hex_str        ; EDI = address of buffer to store converted integer
    mov esi, edi                ; ESI = copy of address for call to print_string_pm
    call dword_to_hex_pm        ; Convert EAX to HEX string
    mov ah, ATTR_BWHITE_ON_MAGENTA
    call print_string_pm        ; Print size of frame in HEX
    add word [esp+efrm_noerr.user_eip], 2
                                ; A UD2 instruction is encoded as 2 bytes so update
                                ;     the real mode instruction pointer to point to
                                ;     next instruction so that the test can continue
                                ;     rather than repeatedly throwing #UD exceptions
    popa                        ; Restore all general purpose registers
    iret
; #GP v8086 General Protection Fault handler
exc_gpf:
    pusha                       ; Save all general purpose registers
    mov eax, DATA32_SEL         ; Setup the segment registers with kernel data selector
    mov ds, eax
    mov es, eax
    cld                         ; DF=0 forward string movement
    test dword [esp+efrm_err.user_flags], 1<<EFLAGS_VM_BIT
                                ; Is the VM (v8086) set in the EFLAGS of the code
                                ;     that was interrupted?
    jnz .isvm                   ; If set then proceed with processing the exception
    mov esi, exc_not_vm         ; Otherwise print msg we weren't interrupting v8086 code
    mov ah, ATTR_BWHITE_ON_RED
    call print_string_pm        ; Print message to console
.endloop:
    hlt
    jmp .endloop                ; Infinite HLT loop
.isvm:
    mov esi, exc_msg_gp
    mov ah, ATTR_BWHITE_ON_MAGENTA
    call print_string_pm        ; Print that we are a #UD exception
    ; The difference between the bottom of the kernel stack and the ESP
    ; value (accounting for the extra 8 pushes by PUSHA) is the original
    ; exception stack frame size. With an error code this should print 0x28.
    mov eax, EXC_STACK-8*4
    sub eax, esp                ; EAX = size of exception stack frame without
                                ;       registers pushed by PUSHA
    mov edi, tmp_hex_str        ; EDI = address of buffer to store converted integer
    mov esi, edi                ; ESI = copy of address for call to print_string_pm
    call dword_to_hex_pm        ; Convert EAX to HEX string
    mov ah, ATTR_BWHITE_ON_MAGENTA
    call print_string_pm        ; Print size of frame in HEX
    inc word [esp+efrm_err.user_eip]
                                ; A HLT instruction is encoded as 1 bytes so update
                                ;     the real mode instruction pointer to point to
                                ;     next instruction so that the test can continue
                                ;     rather than repeatedly throwing #GP exceptions
    popa                        ; Restore all general purpose registers
    add esp, 4                  ; Remove the error code
    iret
There is some hard coded trickery to adjust the CS:IP when returning back to v8086 mode so that we don't get in an infinite loop faulting on the same exception repeatedly. A UD2 instruction is 2 bytes so we add 2 bytes. In the case of HLT we add 1 to v8086 CS:IP before returning. These exception handlers only do something useful if coming from v8086 mode, otherwise they print an error if the exception occurred from somewhere other than v8086 mode. Do not consider this code a way to create your own exception and interrupt handlers, they have been coded specifically for this test and aren't generic.
The following code can be run in an emulator or booted on real hardware using the bootloader test harness in this Stackoverflow answer:
stage2.asm:
VIDEO_TEXT_ADDR        EQU 0xb8000 ; Hard code beginning of text video memory
ATTR_BWHITE_ON_MAGENTA EQU 0x5f    ; Bright White on magenta attribute
ATTR_BWHITE_ON_RED     EQU 0x4f    ; Bright White on red attribute
PM_MODE_STACK          EQU 0x80000 ; Protected mode stack below EBDA
EXC_STACK              EQU 0x70000 ; Kernel Stack for interrupt/exception handling
V86_STACK_SEG          EQU 0x0000  ; v8086 stack SS
V86_STACK_OFS          EQU 0x7c00  ; v8086 stack SP
V86_CS_SEG             EQU 0x0000  ; v8086 code segment CS
EFLAGS_VM_BIT          EQU 17      ; EFLAGS VM bit
EFLAGS_BIT1            EQU 1       ; EFLAGS bit 1 (reserved, always 1)
EFLAGS_IF_BIT          EQU 9       ; EFLAGS IF bit
TSS_IO_BITMAP_SIZE     EQU 0x400/8 ; IO Bitmap for 0x400 IO ports
                                   ; Size 0 disables IO port bitmap (no permission)
ORG_ADDR               EQU 0x7e00  ; Origin point of stage2 (test code)
; Macro to build a GDT descriptor entry
%define MAKE_GDT_DESC(base, limit, access, flags) \
    (((base & 0x00FFFFFF) << 16) | \
    ((base & 0xFF000000) << 32) | \
    (limit & 0x0000FFFF) | \
    ((limit & 0x000F0000) << 32) | \
    ((access & 0xFF) << 40) | \
    ((flags & 0x0F) << 52))
; Macro to build a IDT descriptor entry
%define MAKE_IDT_DESC(offset, selector, access) \
    ((offset & 0x0000FFFF) | \
    ((offset & 0xFFFF0000) << 32) | \
    ((selector & 0x0000FFFF) << 16) | \
    ((access & 0xFF) << 40))
; Macro to convert an address to an absolute offset
%define ABS_ADDR(label) \
    (ORG_ADDR + (label - $$))
; Structure representing exception frame WITH an error code
; including registers pushed by a PUSHA
struc efrm_err
; General purpose registers pushed by PUSHA
.edi:        resd 1
.esi:        resd 1
.ebp:        resd 1
.esp:        resd 1
.ebx:        resd 1
.edx:        resd 1
.ecx:        resd 1
.eax:        resd 1
; Items pushed by the CPU when an exception occurred
.errno:      resd 1
.user_eip:   resd 1
.user_cs:    resd 1
.user_flags: resd 1
.user_esp:   resd 1
.user_ss:    resd 1
.vm_es:      resd 1
.vm_ds:      resd 1
.vm_fs:      resd 1
.vm_gs:      resd 1
EFRAME_ERROR_SIZE equ $-$$
endstruc
; Structure representing exception frame WITHOUT an error code
; including registers pushed by a PUSHA
struc efrm_noerr
; General purpose registers pushed by PUSHA
.edi:        resd 1
.esi:        resd 1
.ebp:        resd 1
.esp:        resd 1
.ebx:        resd 1
.edx:        resd 1
.ecx:        resd 1
.eax:        resd 1
; Items pushed by the CPU when an exception occurred
.user_eip:   resd 1
.user_cs:    resd 1
.user_flags: resd 1
.user_esp:   resd 1
.user_ss:    resd 1
.vm_es:      resd 1
.vm_ds:      resd 1
.vm_fs:      resd 1
.vm_gs:      resd 1
EFRAME_NOERROR_SIZE equ $-$$
endstruc
bits 16
ORG ORG_ADDR
start:
    xor ax, ax                  ; DS=SS=ES=0
    mov ds, ax
    mov ss, ax                  ; Stack at 0x0000:0x7c00
    mov sp, 0x7c00
    cld                         ; Set string instructions to use forward movement
    ; No enabling A20 as we don't require it
    lgdt [gdtr]                 ; Load our GDT
    lidt [idtr]                 ; Install interrupt table
    mov eax, cr0
    or eax, 1
    mov cr0, eax                ; Set protected mode flag
    jmp CODE32_SEL:start32      ; FAR JMP to set CS
; v8086 code entry point
v86_mode_entry:
    ud2                         ; Cause a #UD exception (no error code pushed)
    mov dword [vidmem_ptr], 0xb8000+80*2
                                ; Advance current video ptr to second line
    hlt                         ; Cause a #GP exception (error code pushed)
    ; End of the test - enter infinite loop sice we didn't provide a way for
    ; the v8086 process to be terminated. We can't do a HLT at ring 3.
.endloop:
    jmp $
; 32-bit protected mode entry point
bits 32
start32:
    mov ax, DATA32_SEL          ; Setup the segment registers with data selector
    mov ds, ax
    mov es, ax
    mov ss, ax
    mov esp, PM_MODE_STACK      ; Set protected mode stack pointer
    mov fs, ax                  ; Not currently using FS and GS
    mov gs, ax
    mov ecx, BSS_SIZE_D         ; Zero out BSS section a DWORD at a time
    mov edi, bss_start
    xor eax, eax
    rep stosd
    ; Set iomap_base in tss with the offset of the iomap relative to beginning of the tss
    mov word [tss_entry.iomap_base], tss_entry.iomap-tss_entry
    mov dword [tss_entry.esp0], EXC_STACK
    mov dword [tss_entry.ss0], DATA32_SEL
    mov eax, TSS32_SEL
    ltr ax                      ; Load default TSS (used for exceptions, interrupts, etc)
    xor ebx, ebx                ; EBX=0
    push ebx                    ; Real mode GS=0
    push ebx                    ; Real mode FS=0
    push ebx                    ; Real mode DS=0
    push ebx                    ; Real mode ES=0
    push V86_STACK_SEG
    push V86_STACK_OFS          ; v8086 stack SS:SP (grows down from SS:SP)
    push dword 1<<EFLAGS_VM_BIT | 1<<EFLAGS_BIT1
                                ; Set VM Bit, IF bit is off, DF=0(forward direction),
                                ; IOPL=0, Reserved bit (bit 1) always 1. Everything
                                ; else 0. These flags will be loaded in the v8086 mode
                                ; during the IRET. We don't want interrupts enabled
                                ; because we don't have a proper v86 monitor
                                ; GPF handler to process them.
    push V86_CS_SEG             ; Real Mode CS (segment)
    push v86_mode_entry         ; Entry point (offset)
    iret                        ; Transfer control to v8086 mode and our real mode code
; Function: print_string_pm
;           Display a string to the console on display page 0 in protected mode.
;           Very basic. Doesn't update hardware cursor, doesn't handle scrolling,
;           LF, CR, TAB.
;
; Inputs:   ESI = Offset of address to print
;           AH  = Attribute of string to print
; Clobbers: None
; Returns:  None
print_string_pm:
    push edi
    push esi
    push eax
    mov edi, [vidmem_ptr]       ; Start from video address stored at vidmem_ptr
    jmp .getchar
.outchar:
    stosw                       ; Output character to video display
.getchar:
    lodsb                       ; Load next character from string
    test al, al                 ; Is character NUL?
    jne .outchar                ;     If not, go back and output character
    mov [vidmem_ptr], edi       ; Update global video pointer
    pop eax
    pop esi
    pop edi
    ret
; Function: dword_to_hex_pm
;           Convert a 32-bit value to its equivalent HEXadecimal string
;
; Inputs:   EDI = Offset of buffer for converted string (at least 8 bytes)
;           EAX = 32-bit value to convert to HEX
; Clobbers: None
; Returns:  None
dword_to_hex_pm:
    push edx                    ; Save all registers we use
    push ecx
    push edi
    mov ecx, 8                  ; Process 8 nibbles (4 bits each)
.nibble_loop:
    rol eax, 4                  ; Rotate the high nibble to the low nibble of EAX
    mov edx, eax                ; Save copy of rotated value to continue conversion
    and edx, 0x0f               ; Mask off eveything but the lower nibble
    movzx edx, byte [.hex_lookup_tbl+edx]
    mov [edi], dl               ; Convert nibble to HEX character using lookup table
    inc edi                     ; Continue with the next nibble
    dec ecx
    jnz .nibble_loop            ; Continue with next nibble if we haven't processed all
    pop edi                     ; Retsore all the registers we clobbered
    pop ecx
    pop edx
    ret
.hex_lookup_tbl:  db  "0123456789abcdef"
; #UD Invalid Opcode v8086 exception handler
exc_invopcode:
    pusha                       ; Save all general purpose registers
    mov eax, DATA32_SEL         ; Setup the segment registers with kernel data selector
    mov ds, eax
    mov es, eax
    cld                         ; DF=0 forward string movement
    test dword [esp+efrm_noerr.user_flags], 1<<EFLAGS_VM_BIT
                                ; Is the VM (v8086) set in the EFLAGS of the code
                                ;     that was interrupted?
    jnz .isvm                   ; If set then proceed with processing the exception
    mov esi, exc_not_vm         ; Otherwise print msg we weren't interrupting v8086 code
    mov ah, ATTR_BWHITE_ON_RED
    call print_string_pm        ; Print message to console
.endloop:
    hlt
    jmp .endloop                ; Infinite HLT loop
.isvm:
    mov esi, exc_msg_ud
    mov ah, ATTR_BWHITE_ON_MAGENTA
    call print_string_pm        ; Print that we are a #UD exception
    ; The difference between the bottom of the kernel stack and the ESP
    ; value (accounting for the extra 8 pushes by PUSHA) is the original
    ; exception stack frame size. Without an error code this should print 0x24.
    mov eax, EXC_STACK-8*4
    sub eax, esp                ; EAX = size of exception stack frame without
                                ;       registers pushed by PUSHA
    mov edi, tmp_hex_str        ; EDI = address of buffer to store converted integer
    mov esi, edi                ; ESI = copy of address for call to print_string_pm
    call dword_to_hex_pm        ; Convert EAX to HEX string
    mov ah, ATTR_BWHITE_ON_MAGENTA
    call print_string_pm        ; Print size of frame in HEX
    add word [esp+efrm_noerr.user_eip], 2
                                ; A UD2 instruction is encoded as 2 bytes so update
                                ;     the real mode instruction pointer to point to
                                ;     next instruction so that the test can continue
                                ;     rather than repeatedly throwing #UD exceptions
    popa                        ; Restore all general purpose registers
    iret
; #GP v8086 General Protection Fault handler
exc_gpf:
    pusha                       ; Save all general purpose registers
    mov eax, DATA32_SEL         ; Setup the segment registers with kernel data selector
    mov ds, eax
    mov es, eax
    cld                         ; DF=0 forward string movement
    test dword [esp+efrm_err.user_flags], 1<<EFLAGS_VM_BIT
                                ; Is the VM (v8086) set in the EFLAGS of the code
                                ;     that was interrupted?
    jnz .isvm                   ; If set then proceed with processing the exception
    mov esi, exc_not_vm         ; Otherwise print msg we weren't interrupting v8086 code
    mov ah, ATTR_BWHITE_ON_RED
    call print_string_pm        ; Print message to console
.endloop:
    hlt
    jmp .endloop                ; Infinite HLT loop
.isvm:
    mov esi, exc_msg_gp
    mov ah, ATTR_BWHITE_ON_MAGENTA
    call print_string_pm        ; Print that we are a #UD exception
    ; The difference between the bottom of the kernel stack and the ESP
    ; value (accounting for the extra 8 pushes by PUSHA) is the original
    ; exception stack frame size. With an error code this should print 0x28.
    mov eax, EXC_STACK-8*4
    sub eax, esp                ; EAX = size of exception stack frame without
                                ;       registers pushed by PUSHA
    mov edi, tmp_hex_str        ; EDI = address of buffer to store converted integer
    mov esi, edi                ; ESI = copy of address for call to print_string_pm
    call dword_to_hex_pm        ; Convert EAX to HEX string
    mov ah, ATTR_BWHITE_ON_MAGENTA
    call print_string_pm        ; Print size of frame in HEX
    inc word [esp+efrm_err.user_eip]
                                ; A HLT instruction is encoded as 1 bytes so update
                                ;     the real mode instruction pointer to point to
                                ;     next instruction so that the test can continue
                                ;     rather than repeatedly throwing #GP exceptions
    popa                        ; Restore all general purpose registers
    add esp, 4                  ; Remove the error code
    iret
; Data section
align 4
vidmem_ptr: dd VIDEO_TEXT_ADDR  ; Start console output in upper left of display
tmp_hex_str: TIMES 9 db 0       ; String to store 32-bit value converted HEX + NUL byte
exc_msg_ud:
    db "#UD frame size: 0x", 0
exc_msg_gp:
    db "#GP frame size: 0x", 0
exc_not_vm:
    db "Not a v8086 exception", 0
align 4
gdt_start:
    dq MAKE_GDT_DESC(0, 0, 0, 0)   ; null descriptor
gdt32_code:
    dq MAKE_GDT_DESC(0, 0x000fffff, 10011010b, 1100b)
                                ; 32-bit code, 4kb gran, limit 0xffffffff bytes, base=0
gdt32_data:
    dq MAKE_GDT_DESC(0, 0x000fffff, 10010010b, 1100b)
                                ; 32-bit data, 4kb gran, limit 0xffffffff bytes, base=0
gdt32_tss:
    dq MAKE_GDT_DESC(tss_entry, TSS_SIZE-1, 10001001b, 0000b)
                                ; 32-bit TSS, 1b gran, available, IOPL=0
end_of_gdt:
CODE32_SEL equ gdt32_code - gdt_start
DATA32_SEL equ gdt32_data - gdt_start
TSS32_SEL  equ gdt32_tss  - gdt_start
gdtr:
    dw end_of_gdt - gdt_start - 1
                                ; limit (Size of GDT - 1)
    dd gdt_start                ; base of GDT
align 4
; Create an IDT which handles #UD and #GPF. All other exceptions set to 0
; so that they triple fault. No external interrupts supported.
idt_start:
    TIMES 6 dq 0
    dq MAKE_IDT_DESC(ABS_ADDR(exc_invopcode), CODE32_SEL, 10001110b) ; 6
    TIMES 6 dq 0
    dq MAKE_IDT_DESC(ABS_ADDR(exc_gpf), CODE32_SEL, 10001110b) ; D
    TIMES 18 dq 0
end_of_idt:
align 4
idtr:
    dw end_of_idt - idt_start - 1
                                ; limit (Size of IDT - 1)
    dd idt_start                ; base of IDT
; Data section above bootloader acts like a BSS section
align 4
ABSOLUTE ABS_ADDR($)            ; Convert location counter to absolute address
bss_start:
; Task State Structure (TSS)
tss_entry:
.back_link: resd 1
.esp0:      resd 1              ; Kernel stack pointer used on ring transitions
.ss0:       resd 1              ; Kernel stack segment used on ring transitions
.esp1:      resd 1
.ss1:       resd 1
.esp2:      resd 1
.ss2:       resd 1
.cr3:       resd 1
.eip:       resd 1
.eflags:    resd 1
.eax:       resd 1
.ecx:       resd 1
.edx:       resd 1
.ebx:       resd 1
.esp:       resd 1
.ebp:       resd 1
.esi:       resd 1
.edi:       resd 1
.es:        resd 1
.cs:        resd 1
.ss:        resd 1
.ds:        resd 1
.fs:        resd 1
.gs:        resd 1
.ldt:       resd 1
.trap:      resw 1
.iomap_base:resw 1              ; IOPB offset
.iomap: resb TSS_IO_BITMAP_SIZE ; IO bitmap (IOPB) size 8192 (8*8192=65536) representing
                                ; all ports. An IO bitmap size of 0 would fault all IO
                                ; port access if IOPL < CPL (CPL=3 with v8086)
%if TSS_IO_BITMAP_SIZE > 0
.iomap_pad: resb 1              ; Padding byte that has to be filled with 0xff
                                ; To deal with issues on some CPUs when using an IOPB
%endif
TSS_SIZE EQU $-tss_entry
bss_end:
BSS_SIZE_B EQU bss_end-bss_start; BSS size in bytes
BSS_SIZE_D EQU (BSS_SIZE_B+3)/4 ; BSS size in dwords
Acquire the bpb.inc file and boot.asm from the test harness. Assemble to a disk image with:
nasm -f bin stage2.asm -o stage2.bin
nasm -f bin boot.asm -o disk.img
stage2.bin has to be assembled first as it is embedded as binary by boot.asm. The result should be a 1.44MiB floppy disk image called disk.img. If run in QEMU with:
qemu-system-i386 -fda disk.img
The result should be similar to:

- UD frame size should be 0x00000024 (36 = size of exception frame without error code)
- GP frame size should be 0x00000028 (40 = size of exception frame with error code)