;PS3JB - PS3 Jailbreaker ; (C) 2010 by Brandon Wilson. All rights reserved. ;Portions in util.asm, equates.inc (C) Dan Englender. ;I apologize in advance for the true awfulness that is this code file. include "settings.inc" ;Specific settings for this application NOLIST include "ti83plus.inc" LIST include "equates.inc" ;Equates and macros to be used include "header.asm" GLOBALS ON SEGMENT MAIN EXTERN DispHexA,IGetKey,IPutS,IPutC,DispHexHL,DialogBox,DriverInit,VPutSAppCenter,StopLog,WaitTimerBms,ifastcopy,INewLine EXTERN USBactivityHook,sendReadResponse,SendData,MassStorageInit,VPutSApp,MassStorageHandle,CalculatorInit,LCDdelay EXTERN KeyboardInit,DriverKill,SendInterruptData,PutSApp,SendKeypress,fastCopy,SetupLog,DispLog,InitializePeriphUSB EXTERN BCALL_replacement,BCALL_replacementStart,BCALL_replacementEnd,silentLinkHook,receiveAndWriteUSBData_fromInt EXTERN initUSBStuff,initCrystalTimer,MouseInit,GamepadInit,RecycleUSB,getNext,WaitTimer20ms,WaitTimer40ms,WaitTimer100ms EXTERN InitJailbreakMemory,SwitchPort,SetMaxPacketSize,HandleJailbreakStateChanges,SoftKey,myLoadCIndPaged,BHL_plus_DE EXTERN myLoadDEIndPaged EXTERN Device4DeviceDescriptor,Device4ConfigDescriptor1,Device5DeviceDescriptor,Device5ConfigDescriptor EXTERN Device1DeviceDescriptor,Device1ShortConfigDescriptor,Device1ConfigDescriptor,Device2DeviceDescriptor EXTERN HubDeviceDescriptor,HubConfigDescriptor,Device3DeviceDescriptor,Device3ConfigDescriptor,Device2ConfigDescriptor EXTERN Device6DeviceDescriptor,Device6ConfigDescriptor EXTERN jailbreakState,hubIntResponse,lastPortResetClear,jigBytesReceived,lastPortConnClear,lastPortStatus EXTERN deviceBitmap,deviceChangedBitmap,maxPacketSize,portCur,deviceAddressMap EXTERN SHA1Init,SHA1AddByte,SHA1Final,sha1_hash EXTERN GetHexA_StartKeyCodeA,GetHexA ;UI-specific equates Var lwrCaseFlag,1 Var menuAddr,2 Var numChoices,1 Var prevJailbreakState,1 Var prevHookBlock,5 Var curChoice,1 Var topChoice,1 AboutScreen: ;Display the About screen ld a,(iy+plotFlags) push af set plotLoc,(iy+plotFlags) res bufferOnly,(iy+plotFlags) B_CALL ForceFullScreen B_CALL ClrLCDFull ld hl,1 ld (curRow),hl ld hl,sAboutText call PutSApp ld hl,SplashImage ld de,appBackUpScreen ld bc,SplashImageEnd-SplashImage ldir ld hl,appBackUpScreen ld de,42*256+33 B_CALL DisplayImage ld a,57 ld (penRow),a ld hl,Intro_Web call VPutSAppCenter ld a,25 ld (penRow),a ld hl,Intro_Version call VPutSAppCenter ld a,32 ld (penRow),a ld hl,Intro_Build call VPutSAppCenter pop af ld (iy+plotFlags),a xor a ld (kbdKey),a ld (kbdScanCode),a B_CALL GetKey Init: call LoadPS3JBSettings B_CALL CanAlphIns ld (iy+PS3JBFlags),0 ld hl,mainMenu ld (menuAddr),hl DrawMenu: res onInterrupt,(iy+onFlags) B_CALL ClrLCDFull B_CALL HomeUp ld hl,(menuAddr) call PutSApp ld de,0001h ld b,(hl) ld a,b ld (numChoices),a inc hl $$: push bc ld (curRow),de push de call PutSApp pop de inc e inc hl inc hl pop bc djnz $B ld hl,7 ld (curRow),hl ld hl,sInstalledStatus call IPutS ld hl,sStatusNotInstalled bit 0,(iy+3Ah) jr z,$F ld a,(9BD4h+2) ld b,a in a,(6) cp b jr nz,$F ld hl,sStatusInstalled $$: call IPutS keyLoop: B_CALL GetKey cp kQuit jr z,exitApp cp kClear jr z,exitApp cp k1 jr c,keyLoop sub k1 ld b,a ld a,(numChoices) dec a cp b jp m,keyLoop inc b push bc ld hl,(menuAddr) xor a ld bc,24 cpir inc hl pop de dec hl dec hl $$: inc hl inc hl xor a ld bc,24 cpir dec d jr nz,$B ld e,(hl) inc hl ld d,(hl) ex de,hl jp (hl) InstallHook: B_CALL ClrLCDFull B_CALL HomeUp call InstallJailbreakHook ld hl,sInstalled call IPutS call IGetKey jr Init UninstallHook: B_CALL ClrLCDFull B_CALL HomeUp B_CALL DisableUSBActivityHook ld hl,sUninstalled call IPutS call IGetKey jr Init InstallJailbreakHook: ld a,02h out (54h),a ld hl,USBactivityHook in a,(6) B_CALL EnableUSBActivityHook ret DoOptions: NUM_CHOICES EQU 7 ld a,(iy+plotFlags) ld (plotFlagsBackup),a set plotLoc,(iy+plotFlags) res bufferOnly,(iy+plotFlags) res appAutoScroll,(iy+appFlags) call LoadPS3JBSettings ;Get apdTimerValue to something sane ld a,(apdTimerValue) ld c,a srl c ld h,0 ld l,a add hl,hl ld b,0 add hl,bc ld (uiApdTimerValue),hl ;Make sure we're loading sane AppVar names ld a,(Stage1VarName) or a jr nz,$F ld a,AppVarObj ld (Stage1VarName),a $$: ld a,(Stage2VarName) or a jr nz,$F ld a,AppVarObj ld (Stage2VarName),a $$: ld a,(FWCompatVarName) or a jr nz,$F ld a,AppVarObj ld (FWCompatVarName),a $$: xor a ld (curChoice),a ld (topChoice),a B_CALL ClrLCDFull B_CALL HomeUp ld hl,sOptions call IPutS ld bc,55 ld de,95*256+55 ld h,1 B_CALL ILine ld hl,sOptionKeys call SoftKey DrawOptions: ;Is our top choice the first one? ld hl,0F00h ld (curRow),hl ld a,(topChoice) or a ld a,' ' jr z,$F ld a,1Eh $$: call IPutC ld hl,0F06h ld (curRow),hl ld a,(topChoice) inc a inc a ld b,NUM_CHOICES-1 cp b ld a,1Fh jr c,$F jr z,$F ld a,' ' $$: call IPutC ld a,3 ld (curRow),a ld a,(topChoice) call DisplayOptionItem ld a,5 ld (curRow),a ld a,(topChoice) inc a call DisplayOptionItem optionsKeyLoop: call IGetKey cp kClear jr z,ExitOptionsR cp kGraph jr z,ExitOptionsR cp kQuit jr z,ExitOptions cp kYequ jr z,SaveOptions cp kUp jr z,optionsGoUp cp kDown jr z,optionsGoDown cp kLeft jr z,optionsGoLeft cp kRight jr z,optionsGoRight ld b,a ld a,(curChoice) cp 6 ld a,b jr nz,optionsKeyLoop cp kEE jr z,optionsKeyLoop cp kSpace jr z,optionsKeyLoop cp k0 jp m,optionsKeyLoop cp kCapF+1 jp p,optionsKeyLoop ;Okay, so we've pressed a valid key ;Start word input with this character push af ld a,3 ld (curCol),a pop af call GetHexA_StartKeyCodeA ld h,a push hl call GetHexA pop hl ld l,a ld (jigID),hl jr DrawOptions ExitOptionsR: ld a,(plotFlagsBackup) ld (iy+plotFlags),a jr Init ExitOptions: ld a,(plotFlagsBackup) ld (iy+plotFlags),a jr exitApp DisplayOptionItem: ;Get pointer to option item's data ld (tempPage),a add a,a add a,a ld d,0 ld e,a ld ix,OptionDisplayTable add ix,de push ix xor a ld (curCol),a ld a,' ' B_CALL PutMap ld a,15 ld (curCol),a ld a,' ' B_CALL PutMap ld a,(curChoice) ld b,a ld a,(tempPage) cp b jr nz,$F xor a ld (curCol),a ld a,Lleft B_CALL PutMap ld a,15 ld (curCol),a ld a,Lconvert B_CALL PutMap set textInverse,(iy+textFlags) $$: ld hl,curRow dec (hl) xor a ld (curCol),a ;Display string here pop ix push ix ld l,(ix+0) ld h,(ix+1) call IPutS res textInverse,(iy+textFlags) ;Display item-specific data here pop ix ld l,(ix+2) ld h,(ix+3) jp (hl) DisplayFWCompatibilityOptions: ld hl,FWCompatVarName ld de,sNone jr DisplayAppVarName DisplayTurnOffAfter: ld a,1 ld (curCol),a ld hl,(uiApdTimerValue) B_CALL disphl ld hl,sSeconds call IPutS jr ShortEraseEOL DisplayEmulateJig: ld a,3 ld (curCol),a bit 1,(iy+asm_Flag2) ld hl,sNo jr z,$F ld hl,sYes $$: call IPutS jr ShortEraseEOL DisplayJigID: ld a,3 ld (curCol),a ld hl,(jigID) ld a,h or l jr nz,$F ld hl,sRandom call IPutS jr ShortEraseEOL $$: call DispHexHL jr ShortEraseEOL DisplayUseDevice6: ld a,3 ld (curCol),a bit 0,(iy+asm_Flag2) ld hl,sYes jr z,$F ld hl,sNo $$: call IPutS jr ShortEraseEOL DisplayStage1Payload: ld hl,Stage1VarName ld de,sNone ;sDefault jr DisplayAppVarName DisplayStage2Payload: ld hl,Stage2VarName ld de,sNone DisplayAppVarName: ld a,1 ld (curCol),a push de rst 20h B_CALL ChkFindSym ld a,' ' jr c,$F ld a,b or a ld a,' ' jr z,$F ld a,'*' $$: call IPutC pop de ld a,(OP1+1) or a jr z,$F ld hl,OP1+1 xor a ld (OP1+9),a jr dispAVName $$: ex de,hl dispAVName: call IPutS jr ShortEraseEOL OptionDisplayTable: DW sStage1Payload DW DisplayStage1Payload DW sStage2Payload DW DisplayStage2Payload DW sFWCompatibilityOptions DW DisplayFWCompatibilityOptions DW sTurnOffAfter DW DisplayTurnOffAfter DW sUseDevice6 DW DisplayUseDevice6 DW sEmulateJig DW DisplayEmulateJig DW sJigID DW DisplayJigID SaveOptions: ld hl,(uiApdTimerValue) add hl,hl ld c,0 ld de,5 $$: inc c or a sbc hl,de jr c,$F jr z,$F jr $B $$: ld a,c ld (apdTimerValue),a call SavePS3JBSettings jr ExitOptionsR optionsGoUp: ld a,(curChoice) or a jr z,optionsKeyLoop dec a ld (curChoice),a ld b,a ld a,(topChoice) dec a cp b jr nz,DrawOptions ld (topChoice),a jr DrawOptions optionsGoDown: ld a,(curChoice) cp NUM_CHOICES-1 jr z,optionsKeyLoop inc a ld (curChoice),a ld b,a ld a,(topChoice) inc a inc a cp b jr nz,DrawOptions dec a ld (topChoice),a jr DrawOptions optionsGoLeft: ld a,(curChoice) or a ld hl,Stage1VarName jr z,$F cp 1 ld hl,Stage2VarName jr z,$F cp 2 ld hl,FWCompatVarName jr z,$F cp 4 jr z,oglrFlip cp 5 jr z,oglrFlip2 cp 6 jr z,oglPreviousID ld hl,(uiApdTimerValue) ld de,5 or a sbc hl,de jr z,DrawOptions jr c,DrawOptions ld (uiApdTimerValue),hl jr DrawOptions $$: call GetPreviousVariable jr DrawOptions oglPreviousID: ld hl,(jigID) ld a,h or l jr z,DrawOptions dec hl ld (jigID),hl jr DrawOptions oglrFlip: ld a,(iy+asm_Flag2) xor 1 ld (iy+asm_Flag2),a jr DrawOptions oglrFlip2: ld a,(iy+asm_Flag2) xor 2 ld (iy+asm_Flag2),a jr DrawOptions optionsGoRight: ld a,(curChoice) or a ld hl,Stage1VarName jr z,$F cp 1 ld hl,Stage2VarName jr z,$F cp 2 ld hl,FWCompatVarName jr z,$F cp 4 jr z,oglrFlip cp 5 jr z,oglrFlip2 cp 6 jr z,ogrNextID ld hl,(uiApdTimerValue) ld de,5 add hl,de ld de,305 B_CALL cphlde jr nc,DrawOptions ld (uiApdTimerValue),hl jr DrawOptions $$: call GetNextVariable jr DrawOptions ogrNextID: ld hl,(jigID) inc hl ld a,h or l jr z,$F ld (jigID),hl $$: jr DrawOptions GetPreviousVariable: push hl rst 20h B_CALL FindAlphaDn pop de jr nc,$F ;Not found, so return the "Default"/"None" variable ld a,(OP1) push af B_CALL ZeroOP1 pop af ld (OP1),a $$: ld hl,OP1 ld bc,9 ldir ret GetNextVariable: push hl rst 20h B_CALL FindAlphaUp pop de ret c ld hl,OP1 ld bc,9 ldir ret ShortEraseEOL: ld hl,(curRow) push hl $$: ld a,' ' call IPutC ld a,(curCol) cp 15 jr nz,$B pop hl ld (curRow),hl ret sOptionKeys: DB "Save",0 DB 0 DB 0 DB 0 DB "Back",0 GetCompatibilityData: ld (tempPage),a ld hl,FWCompatVarName rst 20h B_CALL ChkFindSym ret c ex de,hl ld a,b or a jr z,$F ld de,9 call BHL_plus_DE call myLoadCIndPaged ld d,0 ld e,c call BHL_plus_DE $$: ;BHL points to the AppVar's size bytes call myLoadDEIndPaged ld a,(tempPage) or a jr z,gcdFound gcdLoop: push af call myLoadDEIndPaged call BHL_plus_DE pop af dec a jr nz,gcdLoop gcdFound: call myLoadDEIndPaged ld a,b push de pop bc ld de,externalDataBuffer B_CALL FlashToRam xor a ret LoadPS3JBSettings: ;Loads stage1 and stage2 names into memory from AppVar ;Does NOT create the AppVar if it can't be found ld hl,Stage1VarName ld bc,30 B_CALL MemClear ld a,DEFAULT_APD_VALUE ld (apdTimerValue),a xor a ld (iy+asm_Flag2),a ld hl,0AAAAh ld (jigID),hl ld hl,sSettingsAppVar rst 20h B_CALL ChkFindSym ret c ex de,hl ld a,b or a jr z,$F ld de,9 call BHL_plus_DE call myLoadCIndPaged ld d,0 ld e,c call BHL_plus_DE $$: ;BHL points to the AppVar's size bytes call myLoadDEIndPaged ld (tempAddress),de ;BHL points to the two AppVar ID bytes call AVLoadDEIndPaged ;BHL points to the version byte call AVLoadCIndPaged ;Now BHL points to stage1 name ld ix,Stage1VarName call GetVarName ld ix,Stage2VarName call GetVarName call IsAtEndOfAppVar ret z ld ix,FWCompatVarName call GetVarName call AVLoadCIndPaged ld a,c ld (apdTimerValue),a call AVLoadCIndPaged ld (iy+asm_Flag2),c call IsAtEndOfAppVar ret z call AVLoadDEIndPaged ld (jigID),de ret GetVarName: ld e,9 $$: push ix push de call AVLoadCIndPaged pop de pop ix ld (ix+0),c inc ix dec e jr nz,$B ret AVLoadDEIndPaged: ld de,(tempAddress) dec de dec de ld (tempAddress),de jr myLoadDEIndPaged AVLoadCIndPaged: ld de,(tempAddress) dec de ld (tempAddress),de jr myLoadCIndPaged IsAtEndOfAppVar: ld de,(tempAddress) ld a,d or e ret SavePS3JBSettings: ;Write stage1 and stage2 names from memory to AppVar res archiveSettingsVar,(iy+PS3JBFlags) ld hl,sSettingsAppVar rst 20h B_CALL ChkFindSym jr c,saveSettings ld a,b or a jr z,$F set archiveSettingsVar,(iy+PS3JBFlags) $$: B_CALL DelVarArc ld hl,sSettingsAppVar rst 20h B_CALL ChkFindSym saveSettings: ld hl,9+9+9+2+1+1+1+2 B_CALL CreateAppVar inc de inc de ex de,hl ld (hl),26h inc hl ld (hl),79h inc hl ld (hl),0 inc hl ex de,hl ld hl,Stage1VarName ld bc,9 ldir ld hl,Stage2VarName ld bc,9 ldir ld hl,FWCompatVarName ld bc,9 ldir ld a,(apdTimerValue) ld (de),a inc de ld a,(iy+asm_Flag2) ld (de),a inc de ld a,(jigID) ld (de),a inc de ld a,(jigID+1) ld (de),a bit archiveSettingsVar,(iy+PS3JBFlags) ret z ld hl,sSettingsAppVar rst 20h B_CALL ChkFindSym B_CALL Arc_Unarc ret PS3Jailbreak: ;Back up previous hook, if any ld hl,9BD4h ld de,prevHookBlock ld bc,4 ldir ld hl,flags+3Ah ldi ld hl,jbMonitorVectors B_CALL AppInit res appAutoScroll,(iy+appFlags) call InstallJailbreakHook call InitJailbreakMemory ld a,(jailbreakState) ld (prevJailbreakState),a B_CALL ClrLCDFull B_CALL HomeUp ld hl,sInstructions call PutSApp mainKeyLoop: di ld a,(jailbreakState) cp HUB_READY jr nz,$F B_CALL ClrLCDFull B_CALL HomeUp ld hl,sWorking call IPutS jr startKeyLoop $$: ld a,(jailbreakState) cp DONE jr nz,$F B_CALL DispDone call IGetKey jr PS3JailbreakDone $$: ld a,(prevJailbreakState) ld b,a ld a,(jailbreakState) cp b jr z,$F ld (prevJailbreakState),a dec a ld h,0 ld l,a add hl,hl ld de,StateStringTable add hl,de ld e,(hl) inc hl ld d,(hl) ex de,hl ld de,7 ld (curRow),de call IPutS B_CALL EraseEOL jr startKeyLoop $$: ;Add any other state change checks here startKeyLoop: ei halt in a,(4) bit 3,a jr nz,mainKeyLoop PS3JailbreakDone: call CleanupJailbreak jr Init jbMonitorVectors: DW DummyRet DW DummyRet DW jbPutAway DW DummyRet DW DummyRet DW DummyRet DB appTextSaveF DummyRet: ret jbPutAway: call CleanupJailbreak bit monAbandon,(iy+monFlags) jr nz,$F ld a,iAll out (intrptEnPort),a B_CALL LCD_DRIVERON set onRunning,(iy+onFlags) ei jr exitApp $$: B_JUMP PutAway CleanupJailbreak: B_CALL ReloadAppEntryVecs call StopLog ;Restore previous hook, if any ld hl,prevHookBlock ld de,9BD4h ld bc,4 ldir ld de,flags+3Ah ldi ret exitApp: ld a,(lwrCaseFlag) ld (iy+appLwrCaseFlag),a B_CALL ClrLCDFull res indicOnly,(iy+indicFlags) B_JUMP JForceCmdNoChar mainMenu: DB "PS3JB ",VER_STRING,0 DB 6 DB "1) PS3 Jailbreak",0 DW PS3Jailbreak DB "2) Install",0 DW InstallHook DB "3) Uninstall",0 DW UninstallHook DB "4) View Log",0 DW DispLog DB "5) Options",0 DW DoOptions DB "6) About",0 DW AboutScreen ; DB "6) Quit",0 ; DW exitApp sAboutText: DB " PS3Jailbreak " DB " Brandon Wilson ",0 SplashImage: DB 13, 30 DB 00000000b,00000000b,01100000b,00000000b DB 00000000b,00000111b,11110000b,00000000b DB 00000000b,00001111b,11110000b,00000000b DB 00000000b,00011100b,01100000b,00000000b DB 00011000b,00111000b,00000000b,00000000b DB 00111100b,01110000b,00000000b,01100000b DB 01111111b,11111111b,11111111b,11110000b DB 01111111b,11111111b,11111111b,11110000b DB 00111100b,00000111b,00000000b,01100000b DB 00011000b,00000011b,10001110b,00000000b DB 00000000b,00000001b,11111111b,00000000b DB 00000000b,00000000b,11111111b,00000000b DB 00000000b,00000000b,00001110b,00000000b SplashImageEnd: Intro_Web: DB "brandonw.net/ps3jb",0 Intro_Version: DB "Version ",VER_STRING,0 Intro_Build: DB "Build ",BUILD_STRING,0 sInstalled: DB "Hook installed. " DB "Simply connect " DB "cable at any " DB "point and turn " DB "on PS3 as " DB "normal. " DB " " DB "Press any key",0CEh,0 sUninstalled: DB "Hook has been " DB "uninstalled. " DB "You can install " DB "again or select " DB "PS3 Jailbreak " DB "from menu to use" DB "jailbreak. " DB "Press any key",0CEh,0 sInstructions: DB "Connect your PS3" DB "to your " DB "calculator using" DB "a USB cable now." DB "Press ",LlBrack,"ON] at " DB "any time to " DB "quit.",0 sWorking: DB "Working",0CEh,0 sInstalledStatus: DB "Installed? ",0 sStatusInstalled: DB "Yes",0 sStatusNotInstalled: DB "No",0 sOptions: DB "PS3JB Options",0 sStage1Payload: DB "Stage 1 Payload:",0 sStage2Payload: DB "Stage 2 Payload:",0 sFWCompatibilityOptions: DB "FW Compat. Opts:",0 sTurnOffAfter: DB "Turn off after: ",0 sUseDevice6: DB "Use Device 6? ",0 sEmulateJig: DB "Emulate jig? ",0 sJigID:DB "Dongle ID: ",0 sSeconds: DB " secs",0 sAppVarType: DB "AVAR",0 sDefault: DB "Default",0 sNone: DB "None",0 sSave: DB "Save",0 sYes: DB "Yes",0 sNo: DB "No",0 sRandom: DB "Random",0 sSettingsAppVar: DB AppVarObj,"PS3JBOPT",0 ;Possible states StateStringTable: JB_INIT EQU 1 DW JBInit WAIT_HUB_READY EQU 2 DW WaitHubReady HUB_READY EQU 3 DW HubReady P1_WAIT_RESET EQU 4 DW P1WaitReset P1_WAIT_ENUMERATE EQU 5 DW P1WaitEnumerate P1_READY EQU 6 DW P1Ready P2_WAIT_RESET EQU 7 DW P2WaitReset P2_WAIT_ENUMERATE EQU 8 DW P2WaitEnumerate P2_READY EQU 9 DW P2Ready P3_WAIT_RESET EQU 10 DW P3WaitReset P3_WAIT_ENUMERATE EQU 11 DW P3WaitEnumerate P3_READY EQU 12 DW P3Ready P2_WAIT_DISCONNECT EQU 13 DW P2WaitDisconnect P4_WAIT_CONNECT EQU 14 DW P4WaitConnect P4_WAIT_RESET EQU 15 DW P4WaitReset P4_READY EQU 16 DW P4Ready P5_WAIT_RESET EQU 17 DW P5WaitReset P5_WAIT_ENUMERATE EQU 18 DW P5WaitEnumerate P5_CHALLENGED EQU 19 DW P5Challenged P5_RESPONDED EQU 20 DW P5Responded P3_WAIT_DISCONNECT EQU 21 DW P3WaitDisconnect P3_DISCONNECTED EQU 22 DW P3Disconnected P5_WAIT_DISCONNECT EQU 23 DW P5WaitDisconnect P5_DISCONNECTED EQU 24 DW P5Disconnected P4_WAIT_DISCONNECT EQU 25 DW P4WaitDisconnect P4_DISCONNECTED EQU 26 DW P4Disconnected P1_WAIT_DISCONNECT EQU 27 DW P1WaitDisconnect P1_DISCONNECTED EQU 28 DW P1Disconnected P6_WAIT_RESET EQU 29 DW P6WaitReset P6_WAIT_ENUMERATE EQU 30 DW P6WaitEnumerate DONE EQU 31 DW JBDone P4_WAIT_ENUMERATE EQU 32 DW P4WaitEnumerate JIG_INIT EQU 33 DW JigInit ; DB " " ;to judge string length JBInit: DB "Init",0 WaitHubReady: DB "WaitHubReady",0 HubReady: DB "HubReady",0 P1WaitReset: DB "P1WaitReset",0 P1WaitEnumerate: DB "P1WaitEnum",0 P1Ready: DB "P1Ready",0 P2WaitReset: DB "P2WaitReset",0 P2WaitEnumerate: DB "P2WaitEnum",0 P2Ready: DB "P2Ready",0 P3WaitReset: DB "P3WaitReset",0 P3WaitEnumerate: DB "P3WaitEnum",0 P3Ready: DB "P3Ready",0 P2WaitDisconnect: DB "P2WaitDisconn",0 P4WaitConnect: DB "P4WaitConn",0 P4WaitReset: DB "P4WaitReset",0 P4Ready: DB "P4Ready",0 P5WaitReset: DB "P5WaitReset",0 P5WaitEnumerate: DB "P5WaitEnum",0 P5Challenged: DB "P5Challenged",0 P5Responded: DB "P5Responded",0 P3WaitDisconnect: DB "P3WaitDisconn",0 P3Disconnected: DB "P3Disconn",0 P5WaitDisconnect: DB "P5WaitDisconn",0 P5Disconnected: DB "P5Disconn",0 P4WaitDisconnect: DB "P4WaitDisconn",0 P4Disconnected: DB "P4Disconn",0 P1WaitDisconnect: DB "P1WaitDisconn",0 P1Disconnected: DB "P1Disconn",0 P6WaitReset: DB "P6WaitReset",0 P6WaitEnumerate: DB "P6WaitEnum",0 JBDone: DB "Done",0 P4WaitEnumerate: DB "P4WaitEnum",0 JigInit: DB "JigInit",0