Linux内核完全注释(基于Linux0.11)_笔记_/linux/boot/

news/2024/7/3 0:23:27

文章目录

  • 说明
    • 前言
    • 作用
      • bootsect.s程序
      • setup.s程序
      • head.s程序
  • 执行流程
  • 代码解析
    • linux/boot/bootsect.s
    • linux/boot/setup.s
    • linux/boot/head.s

说明

前言

本章主要描述boot目录中的三个汇编文件,这三个虽都是汇编文件,但却用到了两种语法格式
bootsect.s和setup.s是实模式下运行的16位代码程序,采用近似于Intel的汇编语言语法,这也是为何Makefile中使用Intel 8086汇编器和链接器来处理这两个汇编文件
head.s使用的是GNU的汇编程序格式(AT&T),并且运行在保护模式下,需要用GNU的汇编器进行处理
使用两种编译器的主要原因是对于Intel x86处理器系列来讲,Linus那时的GNU编译器仅仅支持i386以及后续的CPU代码指令,若不采用特殊方法就不能生成运行在实模式下的16位代码程序
详情参见GNU汇编器手册《Using as - The GNU Assembler》

作用

bootsect.s程序

bootsect.s代码是磁盘引导块程序,位于磁盘的第0个柱面第0个磁头第1个扇区中(扇区从1开始计数)
在PC加电自检(执行一段32位保护模式下的环境检查代码)后,会将磁盘的第1个扇区加载到内存的0x7c00处,然后跳转到bootsect.s的入口开始执行
bootsect.s执行期间,会将自身移动到内存绝对地址0x90000开始处并跳转到相应位置继续执行,然后将位于磁盘的第2~4扇区的setup模块加载到内存中的0x90200(紧贴着bootsect.s),然后将system模块加载到内存0x10000处,随后确定根文件系统的设备号,若没有指定,则根据引导盘的每磁道扇区数识别盘的类型和种类并保存其设备号于root_dev,然后跳转至setup入口执行

setup.s程序

setup.s是一个操作系统加载程序,一开始它使用ROM BIOS中断读取机器系统数据,并将这些数据保存到0x90000处(覆盖bootsect.s),这些数据将被内核中相关程序使用,如字符设备驱动程序
然后setup.s将system模块从0x10000处移动到0x0000处,接下来做一些进入32位保护模式的准备工作(加载全局描述符寄存器GDTR和中断描述符寄存器IDTR,开启A20地址线,重新设置中断控制芯片8259A),然后设置控制寄存器CR0进入32位保护模式并跳转至system模块中的head.s程序中执行

head.s程序

head.s在被编译为目标文件后会和其他内核程序一起被链接为system模块,位于system模块的开始位置
从这里开始,程序就是在保护模式下运行了,此后的汇编语言使用的也都是AT&T的汇编语言格式
head.s首先加载各种段寄存器、重新设置中断描述符表和重新设置全局段描述符表,然后检查A20是否开启成功以及数学协处理器芯片的存在性,最后设置内存管理的分页处理机制并跳转至/init/main.c的入口地址执行

执行流程

代码解析

linux/boot/bootsect.s

# 定义system模块的大小
SYSSIZE = 0x3000

# 定义了段的全局符号(代码段、数据段、bss段),该程序实际上并未分段
.globl begtext, begdata, begbss, endtext, enddata, endbss
.text
begtext:
.data
begdata:
.bss
begbss:
.text

# 定义了setup模块在磁盘中所占用的扇区数量
SETUPLEN = 4

# 本程序的起始段地址
BOOTSEG  = 0x07c0

# 本程序将要移动的目标段地址
INITSEG  = 0x9000

# setup模块的加载段地址
SETUPSEG = 0x9020

# system模块的加载开始段地址
SYSSEG   = 0x1000

# system模块的加载结束段地址
ENDSEG   = SYSSEG + SYSSIZE

# 设备号0x306指定的是根文件系统设备的第2个硬盘的第1个分区
ROOT_DEV = 0x306

# 指定程序的入口地址为_start
entry _start
_start:
	# 将自身从0x7c00移动到0x90000,共512字节
	mov	ax,#BOOTSEG
	mov	ds,ax
	mov	ax,#INITSEG
	mov	es,ax
	mov	cx,#256
	sub	si,si
	sub	di,di
	rep
	movw

	# 跳转至0x90000+go处执行
	jmpi	go,INITSEG

	# 根据cs重新设置寄存器ds,es,此时cs为0x9000
go:	mov	ax,cs
	mov	ds,ax
	mov	es,ax

	# 设置堆栈ss:sp为0x9000:0xff00
	mov	ss,ax
	mov	sp,#0xFF00		! arbitrary value >>512

# setup模块读取
load_setup:

	# 磁头号(dh),驱动器号(dl)
	mov	dx,#0x0000		! drive 0, head 0

	# 磁道号(cl高两位:ch),扇区号(cl低六位)
	mov	cx,#0x0002		! sector 2, track 0

	# 设置bx,使得es:bx指向setup加载位置
	mov	bx,#0x0200		! address = 512, in INITSEG

	# 开始读取的扇区号(ah),设置扇区读取数量(al)
	mov	ax,#0x0200+SETUPLEN	! service 2, nr of sectors

	# 使用以上参数读取setup模块
	int	0x13			! read it

	# 加载成功,跳转至ok_load_setup
	jnc	ok_load_setup		! ok - continue
	mov	dx,#0x0000
	mov	ax,#0x0000		! reset the diskette
	int	0x13
	j	load_setup

# 磁盘驱动器参数读取,下面是返回值
# ah=0,al=0,bl=驱动器类型
# cx(15~6)=最大磁道号,cx(5~0)=每磁道最大扇区数
# dh=最大磁头数,dl=驱动器数量
# es:di指向软驱磁盘参数表
ok_load_setup:

	# 指定驱动器号
	mov	dl,#0x00

	# 设置ah,确定调用哪一号中断
	mov	ax,#0x0800		! AH=8 is get drive parameters

	# 中断调用
	int	0x13
	mov	ch,#0x00

	# 这一条语句表明下一条指令的操作数位于cs段
	seg cs

	# 保存每条磁道的扇区数
	mov	sectors,cx

	# int13使用了es,此处重新指定es
	mov	ax,#INITSEG
	mov	es,ax

# 读取光标信息,以显示"Loading system"
# 返回信息:
# ch=扫描开始线,cl=扫描结束线,dh=行号,dl=列号
	# 中断号
	mov	ah,#0x03		! read cursor pos

	# 指定页号
	xor	bh,bh

	# 中断调用
	int	0x10

# 字符显示
	# 字符数量设置
	mov	cx,#24

	# bh设置页面号,bl设置字符属性
	mov	bx,#0x0007		! page 0, attribute 7 (normal)

	# 压入字符串起始地址
	mov	bp,#msg1

	# 指定中断号
	mov	ax,#0x1301		! write string, move cursor

	# 中断调用
	int	0x10

# 接下来加载system模块
	# 设置加载的内存地址
	mov	ax,#SYSSEG
	mov	es,ax		! segment of 0x010000

	# 调用加载函数
	call	read_it

	# 关闭驱动器马达
	call	kill_motor

# 接下来检查可用的根文件系统设备,若已经指定设备就直接使用
# 否则需要根据之前获取的驱动器信息来决定使用哪一个根文件设备
	# 指定下一条指令的操作数位于cs段
	seg cs

	# 读取根文件系统设备号
	mov	ax,root_dev

	# 检查是否设置了根文件系统设备号,若未设置则需程序自动选择
	cmp	ax,#0

	# 若不为零,表明已设置,直接跳过自动选择的步骤
	jne	root_defined

	# 为零,需程序自动选择
	# 指定下一条指令的操作数位于cs段
	seg cs

	# 取每磁道扇区数量
	mov	bx,sectors

	# 设置1.2MB驱动器对应的设备号
	mov	ax,#0x0208		! /dev/ps0 - 1.2Mb

	# 扇区数量=15,则就是设备号就是0x0208
	cmp	bx,#15
	je	root_defined

	# 设置1.44MB驱动器对应的设备号
	mov	ax,#0x021c		! /dev/PS0 - 1.44Mb

	# 扇区数量=18,则就是设备号就是0x021c
	cmp	bx,#18
	je	root_defined

# 若未识别到合法的驱动器则会在此进行无限循环
undef_root:
	jmp undef_root

# 设备识别成功后,跳转至此处
root_defined:
	# 指定下一条指令的操作数位于cs段
	seg cs

	# 保存根设备号
	mov	root_dev,ax

# 跳转至setup模块的入口地址执行
# SETUPSEG为段地址,0为偏移
	jmpi	0,SETUPSEG

# 下面是两个子程序
# read_it用于读取磁盘,输入:es=开始内存地址段值
# kill_motor用于关闭驱动马达,使得内核可以读取驱动器状态

# 驱动器当前状态
sread:	.word 1+SETUPLEN	! sectors read of current track
head:	.word 0			! current head
track:	.word 0			! current track

# 磁盘读取函数
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
rp_read:
	mov ax,es
	cmp ax,#ENDSEG		! have we loaded all yet?
	jb ok1_read
	ret
ok1_read:
	seg cs
	mov ax,sectors
	sub ax,sread
	mov cx,ax
	shl cx,#9
	add cx,bx
	jnc ok2_read
	je ok2_read
	xor ax,ax
	sub ax,bx
	shr ax,#9
ok2_read:
	call read_track
	mov cx,ax
	add ax,sread
	seg cs
	cmp ax,sectors
	jne ok3_read
	mov ax,#1
	sub ax,head
	jne ok4_read
	inc track
ok4_read:
	mov head,ax
	xor ax,ax
ok3_read:
	mov sread,ax
	shl cx,#9
	add bx,cx
	jnc rp_read
	mov ax,es
	add ax,#0x1000
	mov es,ax
	xor bx,bx
	jmp rp_read

read_track:
	push ax
	push bx
	push cx
	push dx
	mov dx,track
	mov cx,sread
	inc cx
	mov ch,dl
	mov dx,head
	mov dh,dl
	mov dl,#0
	and dx,#0x0100
	mov ah,#2
	int 0x13
	jc bad_rt
	pop dx
	pop cx
	pop bx
	pop ax
	ret
bad_rt:	mov ax,#0
	mov dx,#0
	int 0x13
	pop dx
	pop cx
	pop bx
	pop ax
	jmp read_track

# 驱动关闭函数
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 508
root_dev:
	.word ROOT_DEV
boot_flag:
	.word 0xAA55

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

linux/boot/setup.s

# 系统参数存放位置
INITSEG  = 0x9000	! we move boot here - out of the way

# system模块存放位置
SYSSEG   = 0x1000	! system loaded at 0x10000 (65536).

# 本程序存放位置
SETUPSEG = 0x9020	! this is the current segment

# 代码段、数据段和bss定义,但并未用到
.globl begtext, begdata, begbss, endtext, enddata, endbss
.text
begtext:
.data
begdata:
.bss
begbss:
.text

# 定义程序入口
entry start
start:

	# 光标位置获取
	mov	ax,#INITSEG	! this is done in bootsect already, but...
	mov	ds,ax
	mov	ah,#0x03	! read cursor pos
	xor	bh,bh
	int	0x10		! save it in known place, con_init fetches
	mov	[0],dx		! it from 0x90000.

	# 扩展内存大小获取
	mov	ah,#0x88
	int	0x15
	mov	[2],ax

	# 显卡当前显示模式获取
	mov	ah,#0x0f
	int	0x10
	mov	[4],bx		! bh = display page
	mov	[6],ax		! al = video mode, ah = window width

	# 显示相关参数获取
	mov	ah,#0x12
	mov	bl,#0x10
	int	0x10
	mov	[8],ax
	mov	[10],bx
	mov	[12],cx

	# 获取第1个硬盘的参数表
	mov	ax,#0x0000
	mov	ds,ax
	lds	si,[4*0x41]
	mov	ax,#INITSEG
	mov	es,ax
	mov	di,#0x0080
	mov	cx,#0x10
	rep
	movsb

	# 检查是否还有其他硬盘若有则继续上面的步骤
	mov	ax,#0x0000
	mov	ds,ax
	lds	si,[4*0x46]
	mov	ax,#INITSEG
	mov	es,ax
	mov	di,#0x0090
	mov	cx,#0x10
	rep
	movsb

! Check that there IS a hd1 :-)

	mov	ax,#0x01500
	mov	dl,#0x81
	int	0x13
	jc	no_disk1
	cmp	ah,#3
	je	is_disk1
no_disk1:
	mov	ax,#INITSEG
	mov	es,ax
	mov	di,#0x0090
	mov	cx,#0x10
	mov	ax,#0x00
	rep
	stosb
is_disk1:

	# 将system模块从0x10000移至0x00000
	cli			! no interrupts allowed !
	mov	ax,#0x0000
	cld			! 'direction'=0, movs moves forward
do_move:
	mov	es,ax		! destination segment
	add	ax,#0x1000
	cmp	ax,#0x9000
	jz	end_move
	mov	ds,ax		! source segment
	sub	di,di
	sub	si,si
	mov 	cx,#0x8000
	rep
	movsw
	jmp	do_move

# 下面开始处理段描述符(进入32位保护的必要条件)

end_move:

	# 设置数据段寄存器ds
	mov	ax,#SETUPSEG
	mov	ds,ax

	# 设置中断描述符表寄存器与全局描述符表寄存器
	lidt	idt_48
	lgdt	gdt_48

# 下面开启A20地址线
	# 检测8042状态寄存器,等待输入缓冲可用
	# 0xD1表示写数据到8042的P2端口
	call	empty_8042
	mov	al,#0xD1		! command write
	out	#0x64,al

	# 检测8042状态寄存器,等待输入缓冲可用
	# 将数据0xDF写到0x60口
	call	empty_8042
	mov	al,#0xDF		! A20 on
	out	#0x60,al

	# 若此时输入缓冲为空则表示A20开启成功
	call	empty_8042

# 下面是对8259A芯片进行编程
# 因为0~31号中断为Intel保留的硬件中断
# 所以要将PC机的BIOS中断放在31号中断之后
	# 初始化工作
	mov	al,#0x11		! initialization sequence

	#发送至主芯片
	# 这里定义的两个十六进制数实际上是机器语言(这就是手撕机器语言吗!)
	# 无实际意义,仅仅是让cpu跳过这两条指令自身
	out	#0x20,al		! send it to 8259A-1
	.word	0x00eb,0x00eb

	# 发送至从芯片
	# 这里定义的两个十六进制数实际上是机器语言
	# 无实际意义,仅仅是让cpu跳过这两条指令自身
	out	#0xA0,al		! and to 8259A-2
	.word	0x00eb,0x00eb

	# 设置主芯片中断号以0x20开始
	mov	al,#0x20		! start of hardware int's (0x20)
	out	#0x21,al
	.word	0x00eb,0x00eb

	# 设置主芯片中断号以0x28开始
	mov	al,#0x28		! start of hardware int's 2 (0x28)
	out	#0xA1,al
	.word	0x00eb,0x00eb

	# 设置主从芯片ICW2、ICW3命令字
	mov	al,#0x04		! 8259-1 is master
	out	#0x21,al
	.word	0x00eb,0x00eb
	mov	al,#0x02		! 8259-2 is slave
	out	#0xA1,al
	.word	0x00eb,0x00eb

	# 设置主从芯片工作模式(ICW4命令字)
	mov	al,#0x01
	out	#0x21,al
	.word	0x00eb,0x00eb
	out	#0xA1,al
	.word	0x00eb,0x00eb

	# 屏蔽主从芯片的中断请求
	mov	al,#0xFF		! mask off all interrupts for now
	out	#0x21,al
	.word	0x00eb,0x00eb
	out	#0xA1,al

# 下面对CR0机器状态字寄存器进行修改,进入32位保护模式
	mov	ax,#0x0001	! protected mode (PE) bit
	lmsw	ax		! This is it!

	# 跳转至段选择子=8,段偏移=0处执行
	# 实际上8=0000 0000 0000 1000其中前13位指定段选择子为2
	# 也就是选中gdt表中第2项,其指向的就是system模块
	jmpi	0,8		! jmp offset 0 of segment 8 (cs)

# 下面是3个函数
# 第1个函数用于检查8042输入缓冲是否为空
# 第2个函数用于设置gdt表
# 第3个函数用于设置idt表
#后面两个函数的作用是为进入32位保护模式做准备
empty_8042:
	.word	0x00eb,0x00eb
	in	al,#0x64	! 8042 status port
	test	al,#2		! is input buffer full?
	jnz	empty_8042	! yes - loop
	ret

gdt:
	.word	0,0,0,0		! dummy

	.word	0x07FF		! 8Mb - limit=2047 (2048*4096=8Mb)
	.word	0x0000		! base address=0
	.word	0x9A00		! code read/exec
	.word	0x00C0		! granularity=4096, 386

	.word	0x07FF		! 8Mb - limit=2047 (2048*4096=8Mb)
	.word	0x0000		! base address=0
	.word	0x9200		! data read/write
	.word	0x00C0		! granularity=4096, 386

idt_48:
	.word	0			! idt limit=0
	.word	0,0			! idt base=0L

gdt_48:
	.word	0x800		! gdt limit=2048, 256 GDT entries
	.word	512+gdt,0x9	! gdt base = 0X9xxxx
	
.text
endtext:
.data
enddata:
.bss
endbss:

linux/boot/head.s

.text
# 全局符号定义
.globl idt,gdt,pg_dir,tmp_floppy_area

# 用于存放页目录
pg_dir:

# 入口定义
.globl startup_32
startup_32:

	# 段选择子设置
	movl $0x10,%eax
	mov %ax,%ds
	mov %ax,%es
	mov %ax,%fs
	mov %ax,%gs

	# 设置系统堆栈
	lss stack_start,%esp

	# 设置中断描述符表
	call setup_idt

	# 设置全局描述符表
	call setup_gdt

	# 恢复段选择子以及系统堆栈(在上面的函数调用中被改动)
	movl $0x10,%eax		# reload all the segment registers
	mov %ax,%ds		# after changing gdt. CS was already
	mov %ax,%es		# reloaded in 'setup_gdt'
	mov %ax,%fs
	mov %ax,%gs
	lss stack_start,%esp

	# 测试A20地址线是否已开启
	xorl %eax,%eax
1:	incl %eax		# check that A20 really IS enabled
	movl %eax,0x000000	# loop forever if it isn't
	cmpl %eax,0x100000
	je 1b

# 检查数学协处理器是否存在
	movl %cr0,%eax		# check math chip
	andl $0x80000011,%eax	# Save PG,PE,ET
/* "orl $0x10020,%eax" here for 486 might be good */
	orl $2,%eax		# set MP
	movl %eax,%cr0
	call check_x87
	jmp after_page_tables

# 辅助例程,供系统调用
check_x87:
	fninit
	fstsw %ax
	cmpb $0,%al
	je 1f			/* no coprocessor: have to set bits */
	movl %cr0,%eax
	xorl $6,%eax		/* reset MP, set EM */
	movl %eax,%cr0
	ret
.align 2
1:	.byte 0xDB,0xE4		/* fsetpm for 287, ignored by 387 */
	ret

setup_idt:
	lea ignore_int,%edx
	movl $0x00080000,%eax
	movw %dx,%ax		/* selector = 0x0008 = cs */
	movw $0x8E00,%dx	/* interrupt gate - dpl=0, present */

	lea idt,%edi
	mov $256,%ecx
rp_sidt:
	movl %eax,(%edi)
	movl %edx,4(%edi)
	addl $8,%edi
	dec %ecx
	jne rp_sidt
	lidt idt_descr
	ret

setup_gdt:
	lgdt gdt_descr
	ret

.org 0x1000
pg0:

.org 0x2000
pg1:

.org 0x3000
pg2:

.org 0x4000
pg3:

.org 0x5000

tmp_floppy_area:
	.fill 1024,1,0

# 下面的入栈操作用于为跳转到init/main.c中的main函数做准备工作
# 在最后压入了main的代码入口地址
# 调用 setup_paging启动对内存的分页处理功能,进行地址映射,最后直接通过ret跳转到/init/main.c处执行
after_page_tables:
	pushl $0		# These are the parameters to main :-)
	pushl $0
	pushl $0
	pushl $L6		# return address for main, if it decides to.
	pushl $main
	jmp setup_paging
L6:
	jmp L6			# main should never return here, but
				# just in case, we know what happens.

int_msg:
	.asciz "Unknown interrupt\n\r"
.align 2
ignore_int:
	pushl %eax
	pushl %ecx
	pushl %edx
	push %ds
	push %es
	push %fs
	movl $0x10,%eax
	mov %ax,%ds
	mov %ax,%es
	mov %ax,%fs
	pushl $int_msg
	call printk
	popl %eax
	pop %fs
	pop %es
	pop %ds
	popl %edx
	popl %ecx
	popl %eax
	iret

.align 2
setup_paging:
	movl $1024*5,%ecx		/* 5 pages - pg_dir+4 page tables */
	xorl %eax,%eax
	xorl %edi,%edi			/* pg_dir is at 0x000 */
	cld;rep;stosl
	movl $pg0+7,pg_dir		/* set present bit/user r/w */
	movl $pg1+7,pg_dir+4		/*  --------- " " --------- */
	movl $pg2+7,pg_dir+8		/*  --------- " " --------- */
	movl $pg3+7,pg_dir+12		/*  --------- " " --------- */
	movl $pg3+4092,%edi
	movl $0xfff007,%eax		/*  16Mb - 4096 + 7 (r/w user,p) */
	std
1:	stosl			/* fill pages backwards - more efficient :-) */
	subl $0x1000,%eax
	jge 1b
	xorl %eax,%eax		/* pg_dir is at 0x0000 */
	movl %eax,%cr3		/* cr3 - page directory start */
	movl %cr0,%eax
	orl $0x80000000,%eax
	movl %eax,%cr0		/* set paging (PG) bit */
	ret			/* this also flushes prefetch-queue */

.align 2
.word 0
idt_descr:
	.word 256*8-1		# idt contains 256 entries
	.long idt
.align 2
.word 0
gdt_descr:
	.word 256*8-1		# so does gdt (not that that's any
	.long gdt		# magic number, but it works for me :^)

	.align 8
idt:	.fill 256,8,0		# idt is uninitialized

gdt:	.quad 0x0000000000000000	/* NULL descriptor */
	.quad 0x00c09a0000000fff	/* 16Mb */
	.quad 0x00c0920000000fff	/* 16Mb */
	.quad 0x0000000000000000	/* TEMPORARY - don't use */
	.fill 252,8,0			/* space for LDT's and TSS's etc */


http://lihuaxi.xjx100.cn/news/51980.html

相关文章

JAVA计算机毕业设计毕业生派遣系统Mybatis+系统+数据库+调试部署

JAVA计算机毕业设计毕业生派遣系统Mybatis系统数据库调试部署 JAVA计算机毕业设计毕业生派遣系统Mybatis系统数据库调试部署本源码技术栈: 项目架构:B/S架构 开发语言:Java语言 开发软件:idea eclipse 前端技术:La…

优化APK体积

该篇文章主要来介绍如何减少APK体积,以帮助用户更快地下载App,并加速安装/更新过程。 APK内容结构一瞥 要查看APK文件中都包含哪些内容,有两种方式。第一种通过Android Studio的Analyze APK功能查看,该工具不仅可以还原XML类型代…

基于springboot的智能医化企业设备与档案管理系统

基于springboot技术,数据层为MyBatis,mysql数据库,页面采用html,具有完整的业务逻辑,适合选题:医化企业、设备、档案、医疗录取等前端:bootstrap、layui、js、css等 开发工具:idea 数据库&#…

基于JAVA家教到家平台计算机毕业设计源码+数据库+lw文档+系统+部署

基于JAVA家教到家平台计算机毕业设计源码数据库lw文档系统部署 基于JAVA家教到家平台计算机毕业设计源码数据库lw文档系统部署本源码技术栈: 项目架构:B/S架构 开发语言:Java语言 开发软件:idea eclipse 前端技术:…

基于JAVA计算机组成原理教学网站计算机毕业设计源码+数据库+lw文档+系统+部署

基于JAVA计算机组成原理教学网站计算机毕业设计源码数据库lw文档系统部署 基于JAVA计算机组成原理教学网站计算机毕业设计源码数据库lw文档系统部署本源码技术栈: 项目架构:B/S架构 开发语言:Java语言 开发软件:idea eclipse …

C#的Dictionary类使用说明

C#的Dictionary类使用说明一&#xff1a;Dictionary类简单说明二&#xff1a;Dictionary类的构造函数三&#xff1a;Dictionary类的属性四&#xff1a;Dictionary 类的常用方法1&#xff1a; Dictionary<TKey,TValue>.Add(TKey, TValue)的方法介绍2&#xff1a; Dictiona…

自定义HorizontalScrollView嵌套HorizontalListView实现手势监听、按钮监听横向滚动功能

今日空闲花了点时间对以前自主实现的项目功能进行改进和优化&#xff0c; 其实一些界面的小功能有时候没实现过&#xff0c;也没经验类似项目功能经验&#xff0c;反而耗费的时间会更多。下面我所描述的界面功能就是我在对用RecyclerView控件不熟悉的情况下使用了HorizontalScr…

A_A03_005 STM32程序DAPLINK下载

目录 一、资料下载 二、相关链接 三、交流学习 四、常用单片机系统板 五、DAPLINK下载器 六、STM32程序DAPLINK下载 流程 七、注意事项 一、资料下载 网盘链接 戳它跳转 提取码&#xff1a;oqnj 二、相关链接 DAPLINK驱动安装 WIN10系统驱动免安装 MDK5下载与安装…