MBR with QB?

If you have questions about any aspect of QBasic programming, or would like to help fellow programmers solve their problems, check out this board!

Moderators: Pete, Mods

Post Reply
Patz QuickBASIC Creations
Veteran
Posts: 399
Joined: Wed Mar 02, 2005 9:01 pm
Location: Nashville, Tennessee
Contact:

MBR with QB?

Post by Patz QuickBASIC Creations »

I need to insert a program into my MBR (master boot record) for password protection. It will make a new password everyday (this is not the problem) but I want it to boot before my OS (this is the problem).
Can it..
a. Be done with QBasic?
b. If so, how?
Guest
Veteran
Posts: 128
Joined: Sun Aug 14, 2005 8:33 pm
Location: Forest Lake, MN
Contact:

Post by Guest »

Yes, it could be done with Qbasic, BUT you will have to find the MBR Address.
Patz QuickBASIC Creations
Veteran
Posts: 399
Joined: Wed Mar 02, 2005 9:01 pm
Location: Nashville, Tennessee
Contact:

Post by Patz QuickBASIC Creations »

Well, how exactly would I do it if I found it? (Also, the MBR is on a hard drive, right? I used to think it was MotherBoard Resources)
Guest
Veteran
Posts: 128
Joined: Sun Aug 14, 2005 8:33 pm
Location: Forest Lake, MN
Contact:

Post by Guest »

Yes, the MBR is in the hard drive, first thing there, if I'm not mistaken...
I couldn't really tell you what to do from that point. All I know is modifying the MBR is dangerous. It could stop your computer from booting and functioning...
Patz QuickBASIC Creations
Veteran
Posts: 399
Joined: Wed Mar 02, 2005 9:01 pm
Location: Nashville, Tennessee
Contact:

Post by Patz QuickBASIC Creations »

Well, I can always AutoClave (google it) it if something goes seriously wrong :lol:
Guest
Veteran
Posts: 128
Joined: Sun Aug 14, 2005 8:33 pm
Location: Forest Lake, MN
Contact:

Post by Guest »

It's still a good idea to know what you are doing...
Patz QuickBASIC Creations
Veteran
Posts: 399
Joined: Wed Mar 02, 2005 9:01 pm
Location: Nashville, Tennessee
Contact:

Post by Patz QuickBASIC Creations »

Image

:lol:
Guest
Veteran
Posts: 128
Joined: Sun Aug 14, 2005 8:33 pm
Location: Forest Lake, MN
Contact:

Post by Guest »

Things you can do with a sad mac and paint...
Z!re
Veteran
Posts: 887
Joined: Wed Aug 04, 2004 11:15 am

Post by Z!re »

Tested under QB45:

Code: Select all

' BOOTSEC.BAS   reads the hard drive boot sector into memory.
'
'   Author:     Christy Gemmell
'   Additions:  Martin Overton
'               David Milton (4/7/1995)
'               Andrew Gibson (9/25/1997)
'   Date:       1/9/1998
'
DECLARE FUNCTION FloppyDriveReady% (Drive$, ErrCode%)
DECLARE FUNCTION GetDiskID$ (Drive$)
DECLARE FUNCTION Lo% (IntegerVar%)
DECLARE SUB BootSec (Drive$, ParTable%, Done%)
DECLARE SUB GetDTAAddr ()
DECLARE SUB Help ()

'REGTYPE.BAS - Include file for CALL INTERRUPT & INTERRUPTX
TYPE RegType
  AX    AS INTEGER
  BX    AS INTEGER
  CX    AS INTEGER
  DX    AS INTEGER
  BP    AS INTEGER
  SI    AS INTEGER
  DI    AS INTEGER
  flags AS INTEGER
  DS    AS INTEGER
  ES    AS INTEGER
END TYPE

TYPE ExtendedFCBRecord
	ExtFCB   AS STRING * 1
	Res1     AS STRING * 5
	Attr     AS STRING * 1
	Drive    AS STRING * 1
	Name1    AS STRING * 11
	Unused1  AS STRING * 5
	Name2    AS STRING * 11
	Unused2  AS STRING * 9
END TYPE

CONST FALSE = 0, TRUE = NOT FALSE
DIM SHARED REGISTERS AS RegType, Segment, Offset
DIM SHARED Sector AS STRING * 512
DIM SHARED Part AS STRING * 512

	CLS : Drive$ = "D"


	IF Drive$ = "" OR Drive$ = "/?" OR Drive$ = "?" OR Drive$ = "HELP" THEN Help: END
	IF Drive$ = "A" OR Drive$ = "B" OR Drive$ = "A:" OR Drive$ = "B:" THEN
	DT = FloppyDriveReady%(Drive$, ErrCode%)
	IF ErrCode% <> TRUE AND DT <> TRUE THEN
	   PRINT "Error occured with Floppy Disk Drive "; CHR$(34); Drive$; CHR$(34); ", ";
	   SELECT CASE ErrCode%
	     CASE &H1
	      PRINT "Bad command."
	     CASE &H2
	      PRINT "Address mark not found."
	     CASE &H3
	      PRINT "Diskette write protected."
	     CASE &H4
	      PRINT "Sector not found."
	     CASE &H6
	      PRINT "Diskette removed."
	     CASE &H8
	      PRINT "DMA Overrun."
	     CASE &H9
	      PRINT "DMA across 64k boundary."
	     CASE &H10
	      PRINT "Bad CRC or ECC."
	     CASE &H20
	      PRINT "CONTROLLER FAILED !!!!"
	     CASE &H40
	      PRINT "Seek Failed."
	     CASE &H80
	      PRINT "Drive timeout."
	     CASE ELSE
	      PRINT "Disk Status Code is "; HEX$(ErrCode%); "h."
	   END SELECT
	   END
	END IF
	END IF

	BootSec Drive$, ParTable%, Done%    ' Read boot sector
	IF Done% THEN                       ' If successful...
	   PRINT "Boot Sector for Drive "; Drive$
	   PRINT "========================"
	   PRINT "Media descriptor         = "; HEX$(ASC(MID$(Sector, 22, 8)))
	   PRINT "OEM Identifier           = "; MID$(Sector, 4, 8)
	   PRINT "Boot Sector Volume Label = "; MID$(Sector, 44, 11)
	   PRINT "Directory Volume Label   = "; GetDiskID$(Drive$)
	   PRINT "Serial number            = ";
	   FOR i% = 43 TO 40 STEP -1
			   PRINT RIGHT$("0" + HEX$(ASC(MID$(Sector, i%, 1))), 2);
			   IF i% = 42 THEN PRINT "-";
	   NEXT i%
	   PRINT : PRINT "File system              = "; MID$(Sector, 55, 8)
	   PRINT
	   IF ParTable% THEN
			  PRINT "Partition Table for Drive "; Drive$
			  PRINT "============================"
			  i% = 447: P% = 1
			  DO
					 PRINT "Partition"; P%;
					 IF ASC(MID$(Part, i%, 1)) = 128 THEN
							PRINT TAB(21); "ACTIVE PARTITION";
					 END IF
					 OS% = ASC(MID$(Part, i% + 4, 1))
					 PRINT TAB(41);
					 SELECT CASE OS%
							 CASE 0
									  PRINT "Empty"
							 CASE 1
									  PRINT "DOS 12-bit FAT"
							 CASE 4
									  PRINT "DOS 16-bit FAT (up to 32MB)"
							 CASE 5
									  PRINT "Extended partition"
							 CASE 6
									  PRINT "16-bit FAT (over 32MB)"
							 CASE 7
									  PRINT "OS/2 HPFS or Windows NTFS"
							 CASE ELSE
									  PRINT "Operating System Unknown."; OS%
					 END SELECT
					 i% = i% + 16: P% = P% + 1
			  LOOP UNTIL P% > 4
			  PRINT
			  Sig& = ASC(MID$(Part, i%, 1)) + (256& * ASC(MID$(Part, i% + 1, 1)))
			  IF Sig& = 43605 THEN
			       COLOR 15: PRINT "Valid boot block.": COLOR 7
			  ELSE
			       COLOR 28: PRINT "WARNING: INVALID BOOT BLOCK !!!!!!": COLOR 7
			  END IF
	   END IF
	   PRINT "-----------------------------------------------------------"
	ELSE
	PRINT "Boot Sector Interpreter Version 1.51.01": PRINT
	PRINT "You must use a valid drive letter on the command line."
	PRINT CHR$(34); Drive$; CHR$(34); " does not work or is non-existant."
	END IF
END

'   Read the boot sector and partition table of a specified drive.
'
SUB BootSec (Drive$, ParTable%, Done%)
	LSET Sector = STRING$(512, 0)       ' Fill sector buffer with zeroes
	Disk% = ASC(UCASE$(Drive$)) - 65    ' Get drive number
	Head% = 0                           ' Floppies use head zero
	IF Disk% > 1 THEN                   ' Adjust
	   Disk% = (Disk% + 128) - 2        '   for hard
	   Head% = 1                        '     disk
	END IF                              '       drives
	REGISTERS.CX = &H1                       ' Get sector 1 of track zero
	REGISTERS.DX = (Head% * 256) + Disk%     '   of selected drive
	REGISTERS.AX = &H201                     ' Read one full sector
	REGISTERS.BX = VARPTR(Sector)            ' Offset of read buffer
	REGISTERS.ES = VARSEG(Sector)            ' Segment of read buffer
	CALL INTERRUPTX(&H13, REGISTERS, REGISTERS)       ' Read sector into memory
	IF REGISTERS.flags AND 1 THEN            ' Test carry flag for error
	   Done% = FALSE                    ' If set report an error
	ELSE                                ' Otherwise
	   IF Disk% > 1 THEN                ' Hard drive
			  LSET Part = STRING$(512, 0)   ' Fill partition buffer with zeroes
			  Head% = 0                     ' Partition table is under head zero
			  REGISTERS.CX = &H1                 ' Get sector 1 of track zero
			  REGISTERS.DX = (Head% * 256) + Disk% ' of selected drive
			  REGISTERS.AX = &H201               ' Read one full sector
			  REGISTERS.BX = VARPTR(Part)        ' Offset of read buffer
			  REGISTERS.ES = VARSEG(Part)        ' Segment of read buffer
			  CALL INTERRUPTX(&H13, REGISTERS, REGISTERS)    ' Read sector into memory
			  IF REGISTERS.flags AND 1 THEN      ' Test carry flag for error
				 ParTable% = FALSE          ' If set report failure
			  ELSE                          ' Otherwise
				 ParTable% = TRUE           ' Report success
			  END IF
	   END IF
	   Done% = TRUE                     ' report success
	END IF
END SUB

FUNCTION FloppyDriveReady% (Drive$, ErrCode%)
'returns True (-1) if the floppy drive specified in Drive$
'has a disk in it. If the function returns False (0), ErrCode%
'contains the DOS error code.
'by Douglas H. Lusher, April, 1993

Drive% = ASC(UCASE$(Drive$)) - 65

'reset floppy drive
REGISTERS.AX = 0
REGISTERS.DX = Drive%
CALL INTERRUPTX(&H13, REGISTERS, REGISTERS)

REGISTERS.AX = &H401
REGISTERS.CX = &H101
REGISTERS.DX = Drive%
CALL INTERRUPTX(&H13, REGISTERS, REGISTERS)

'call the interrupt twice since if a disk has just been inserted,
'the first time gives a wrong answer
REGISTERS.AX = &H401
REGISTERS.CX = &H101
REGISTERS.DX = Drive%
CALL INTERRUPTX(&H13, REGISTERS, REGISTERS)
FloppyDriveReady% = ((REGISTERS.flags AND 1) = 0)
ErrCode% = ((REGISTERS.AX AND &HFF00) \ &H100) AND &HFF
END FUNCTION

FUNCTION GetDiskID$ (Drive$)
DIM EFCB AS ExtendedFCBRecord
'  Get Address of Data Transfer Area (DTA)
GetDTAAddr
'  Call the Find First FCB function
'  using the Volume attribute
EFCB.ExtFCB = CHR$(&HFF)   'Set EFCB flag
EFCB.Attr = CHR$(&H8)      'Vol label attribute
EFCB.Drive = CHR$(ASC(Drive$) - 64)
EFCB.Name1 = "*.*        "
REGISTERS.AX = &H1100        'Call find first FCB
REGISTERS.DS = VARSEG(EFCB)  'Load DS:DX with
REGISTERS.DX = VARPTR(EFCB)  'address of EFCB
CALL INTERRUPTX(&H21, REGISTERS, REGISTERS)
GetDiskID$ = "NO LABEL EXISTS" ' if it doesn't exist
IF Lo(REGISTERS.AX) = 0 THEN  'Successful
	VOL$ = ""
	DEF SEG = Segment       'Set Segment to DTA
	FOR i = Offset + 8 TO Offset + 18
		VOL$ = VOL$ + CHR$(PEEK(i))
	NEXT i
	DEF SEG
	GetDiskID$ = VOL$
END IF
END FUNCTION

SUB GetDTAAddr
REGISTERS.AX = &H2F00
CALL INTERRUPTX(&H21, REGISTERS, REGISTERS)
Segment = REGISTERS.ES   'Return address of DTA
Offset = REGISTERS.BX    'Segment:Offset format
END SUB

SUB Help
PRINT "Boot Sector Interpreter Version 1.51.01": PRINT
PRINT "The program interprets the contents of Floppy diskette and Hard drive boot"
PRINT "sectors (and active partitions on Hard Disk Drives) and displays the translated"
PRINT "contents. (Does not alter boot sector in ANY WAY !)": PRINT
PRINT SPC(3); "Usage:  BOOTSEC driveletter": PRINT
PRINT "Replace 'driveletter' with the identifier of a known working drive."
PRINT "( I.E. BOOTSEC A: )"
PRINT : PRINT "Original Author: Christy Gemmell"
PRINT "Additions:  Martin Overton, David Milton (4/7/1995), Andrew Gibson (9/25/1997)"
END SUB

FUNCTION Lo% (IntegerVar%)
Lo% = IntegerVar% MOD 256
END FUNCTION
I have left this dump.
Brandon Cornell

MBR is ion the HDD

Post by Brandon Cornell »

I know for sure the MBR is on the HDD because I have had a few Computers get hit with the Stoned.Empire.Monkey Virus It wipe out the MBR Sectors on your Harddrive so you have to repartition the drive.
User avatar
{Nathan}
Veteran
Posts: 1169
Joined: Thu Aug 19, 2004 6:08 pm
Location: The wetlands of central Ohio, USA
Contact:

Post by {Nathan} »

OK, my guess is that since the MBR is so small, it doesn't have an operating system on it, so in order to make a password protection program in QB you would have to add DOS commands to your MBR... kinda confusing...

Anyway, but most BIOs have an option for password, why not use that? But anyway, I do NOT think it is possible to do this in QB anyway...
Image
Z!re
Veteran
Posts: 887
Joined: Wed Aug 04, 2004 11:15 am

Post by Z!re »

MBR is the first part of the HD or partition..

IIRC it's a few hundred bytes in size..

What you can do is have it call another program.. which can be any size..

so in order to make a password protection program in QB you would have to add DOS commands to your MBR... kinda confusing...
Applesausace poop! I figured I'd be random too.. :D
I have left this dump.
User avatar
{Nathan}
Veteran
Posts: 1169
Joined: Thu Aug 19, 2004 6:08 pm
Location: The wetlands of central Ohio, USA
Contact:

Post by {Nathan} »

Applesauce poop? Well yeah, I thought about that some more and I realized you would just have to send the bit code of the .exe to the processor or sometin like that... my brain hurts.
Image
DrV
Veteran
Posts: 63
Joined: Thu Jun 02, 2005 9:44 pm

Post by DrV »

The MBR is 512 bytes: http://en.wikipedia.org/wiki/MBR

You can't really write a boot sector in QB, because the code it emits requires the QB runtime to function. You won't be able to fit it into 512 bytes. Every boot sector I've seen has been written in assembly language. You can find a minimal working boot sector in the Linux source code at arch/i386/boot/bootsect.S: http://lxr.linux.no/source/arch/i386/boot/bootsect.S
PQBC at school

Post by PQBC at school »

Anyway nate, here's some psuedocode for you.

Code: Select all

LET SEED = VAL(LEFT$(DATE$,2))+VAL(MID$(DATE$,4,2))+VAL(RIGHT$(DATE$,2))
RANDOMIZE SEED
While LEN(PASS$) <> 8
LET RED = INT(RND * 36)+55   ' (or whatever 0's ASCII value is)
LET PASS$ = PASS$ + CHR$(RED)
WEND
WRONG:
INPUT "Daily password"; confirm$
IF CONFIRM$ <> PASS$ THEN GOTO WRONG
I want to load that into my MBR so I need a password that changes everyday. (long story)
Post Reply