File "waf.bas"

Path: /WAF - Wireless Android Framework/WAF_0.1_Windows/waf.bas
File size: 15.08 KB
MIME-type:
Charset: utf-8

#COMPILE EXE = "waf.exe"
#DIM ALL
#INCLUDE ONCE "windows.inc"

#RESOURCE ICON AICO,    "inu.ico"

$EXE  = "Wireless Android Framework"
$VER  = "v0.1"
$WEB  = "http://mougino.free.fr/waf"
%PORT = 6369

GLOBAL myname AS STRING
GLOBAL myip, bip, ss AS LONG

'--------------------------------------------------------------------------------
FUNCTION EXIST(BYVAL fileOrFolder AS STRING) AS LONG
    LOCAL Dummy&
    Dummy& = GETATTR(fileOrFolder)
    FUNCTION = (ERRCLEAR = 0)
END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION IP_STR(ip AS LONG) AS STRING
    LOCAL p AS BYTE PTR
    p = VARPTR(ip)
    FUNCTION = USING$("#_.#_.#_.#", @p, @p[1], @p[2], @p[3])
END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION IP_UNIQID(ip AS LONG) AS STRING
    LOCAL id, tbl AS STRING
    LOCAL i AS LONG
    RANDOMIZE ip
    tbl = "AGL-BTN-CKW-DHS-ERJ-FMP"
    id = UCASE$(HEX$(ip, 8))
    FOR i = 1 TO LEN(id)
        IF ASC(id, i) >= 65 THEN
            ASC(id, i) = ASC(tbl, 4 * (ASC(id, i) - 65) + RND(1,3))
        END IF
    NEXT
    REPLACE ANY "0O" WITH "ZZ" IN id
    FUNCTION = id
END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION UNIQID_IP(id AS STRING) AS LONG
    LOCAL e, tbl AS STRING
    LOCAL i, k AS LONG
    tbl = "AGL-BTN-CKW-DHS-ERJ-FMP"
    e = UCASE$(id)
    REPLACE ANY "Z" WITH "0" IN e
    FOR i = 1 TO 6
        REPLACE MID$(tbl, 4*i-2, 1) WITH MID$(tbl, 4*i-3, 1) IN e
        REPLACE MID$(tbl, 4*i-1, 1) WITH MID$(tbl, 4*i-3, 1) IN e
    NEXT
    FUNCTION = VAL("&H" + e)
END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION IP_LNG(ip AS STRING) AS LONG
    FUNCTION = 256^3 * VAL(PARSE$(ip, ".", 4)) _
             + 256^2 * VAL(PARSE$(ip, ".", 3)) _
             + 256^1 * VAL(PARSE$(ip, ".", 2)) _
             + 256^0 * VAL(PARSE$(ip, ".", 1))
END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION UDPdetect() AS LONG ' Send UDP-broadcast to detect server on LAN (if any)
    LOCAL hSocket, ip, pNum AS LONG
    LOCAL buf AS STRING

    hSocket = FREEFILE
    UDP open AS #hSocket TIMEOUT 500
    UDP SEND #hSocket, AT bip, %PORT, "Ping"
    UDP RECV #hSocket, FROM ip, pNum, buf
    UDP CLOSE #hSocket

    IF ERR THEN FUNCTION = 0 ELSE FUNCTION = ip
END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
SUB TCP_RECV(sktNum AS LONG, buf AS STRING)
    LOCAL e AS STRING
    RESET buf
    DO
        TCP RECV #sktNum, 1024, e
        buf += e
    LOOP WHILE LEN(e) AND ISFALSE ERR
END SUB
'--------------------------------------------------------------------------------

'------------------------------------------------------------------------------
MACRO LinuxName(tx) = PARSE$(tx, "/", PARSECOUNT(tx, "/"))
'------------------------------------------------------------------------------

'------------------------------------------------------------------------------
MACRO LinuxPath(tx) = LEFT$(tx, INSTR(-1, tx, "/"))
'------------------------------------------------------------------------------

'------------------------------------------------------------------------------
MACRO WindowsName(tx) = PARSE$(tx, "\", PARSECOUNT(tx, "\"))
'------------------------------------------------------------------------------

'------------------------------------------------------------------------------
MACRO WindowsPath(tx) = LEFT$(tx, INSTR(-1, tx, "\"))
'------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION SplitArgs(command AS STRING, src AS STRING, tgt AS STRING) AS LONG
    LOCAL cmd AS STRING
    LOCAL i AS LONG

    cmd = command
    IF TALLY(cmd, $SPC) = 0 THEN ' pull|push simpleRemotePath
        cmd = REMOVE$(cmd, $DQ)
        src = cmd
        tgt = EXE.PATH$ + LinuxName(src)
    ELSEIF TALLY(cmd, $SPC) = 1 THEN ' pull|push simpleRemotePath simpleLocalPath
        cmd = REMOVE$(cmd, $DQ)
        src = LEFT$(cmd, INSTR(cmd, $SPC)-1)
        tgt = MID$ (cmd, INSTR(cmd, $SPC)+1)
    ELSEIF TALLY(cmd, $DQ) = 2 THEN
        IF LEFT$(cmd, 1) = $DQ THEN ' pull|push "remote path with space" simpleLocalPath
            tgt = MID$(cmd, INSTR(-1, cmd, $SPC)+1)
            cmd = REMOVE$(cmd, $SPC + tgt)
            src = REMOVE$(cmd, $DQ)
        ELSEIF RIGHT$(cmd, 1) = $DQ THEN ' pull|push simpleRemotePath "local path with space"
            src = LEFT$(cmd, INSTR(cmd, $SPC)-1)
            cmd = REMOVE$(cmd, src + $SPC)
            tgt = REMOVE$(cmd, $DQ)
        ELSE
            FUNCTION = 0 ' misplaced double quotes
            EXIT FUNCTION
        END IF
    ELSEIF TALLY(cmd, $DQ) = 4 THEN
        i = INSTR(cmd, $DQ + $SPC + $DQ)
        IF i = 0 THEN
            FUNCTION = 0  ' misplaced double quotes
            EXIT FUNCTION
        END IF
        src = LTRIM$(LEFT$(cmd, i-1), $DQ)
        tgt = RTRIM$(MID$ (cmd, i+3), $DQ)
    ELSEIF TALLY(cmd, $DQ) <> 0 THEN
        FUNCTION = 0 ' illegal number of double quotes
        EXIT FUNCTION
    END IF

    FUNCTION = 1

END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION SendCommand(cmd AS STRING) AS STRING ' Send remote command over TCP/IP
    LOCAL answer AS STRING

    TCP PRINT #ss, myname + "``" + cmd
    TCP_RECV   ss, answer
    IF answer = "" THEN TCP_RECV ss, answer

    FUNCTION = answer
END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION CTR(lbl AS STRING) AS STRING
    LOCAL n AS LONG
    LOCAL r AS STRING
    n = (40 - LEN(lbl)) \ 2
    r = SPACE$(n) + lbl
    FUNCTION = r + SPACE$(40 - LEN(r))
END FUNCTION
'--------------------------------------------------------------------------------

'--------------------------------------------------------------------------------
FUNCTION PBMAIN () AS LONG
    LOCAL cmd, ans, src, tgt, kw(), file, mail, pwd AS STRING
    LOCAL i, servip, cursiz, curpos AS LONG
    LOCAL t0, tf AS DOUBLE

    ' Prepare command
    cmd = COMMAND$
    IF TRIM$(LCASE$(cmd)) = "changelog" THEN                ' CHANGELOG
        STDOUT "WAF Desktop changelog:"
        STDOUT "v0.1 - initial release"
        STDOUT ""

    ELSEIF TRIM$(LCASE$(cmd)) = "logcat" THEN               ' LOGCAT
        cmd = "shell logcat"

    ELSEIF TRIM$(LCASE$(cmd)) = "version" THEN              ' VERSION
        STDOUT "WAF Desktop " + $VER

    ELSEIF INSTR(LCASE$(cmd), "pull ") = 1 THEN             ' PULL
        IF SplitArgs(TRIM$(MID$(cmd, 6)), BYREF src, BYREF tgt) = 0 THEN
            STDOUT "Argument error. Expected: pull <android-remote> <pc-local>"
            STDOUT "                If your paths have space in them, use double"
            STDOUT "                quotes.   E.g. ""/sdcard/new folder/my file"""
            EXIT FUNCTION
        END IF
        IF tgt = "." THEN tgt = EXE.PATH$ + LinuxName(src)
        cmd = "pull " + src

    ELSEIF INSTR(LCASE$(cmd), "push ") = 1 THEN             ' PUSH
        IF SplitArgs(TRIM$(MID$(cmd, 6)), BYREF src, BYREF tgt) = 0 THEN
            STDOUT "Argument error. Expected: push <pc-local> <android-remote>"
            STDOUT "                If your paths have space in them, use double"
            STDOUT "                quotes. E.g. ""C:\My Programs\example\file.ext"""
            EXIT FUNCTION
        END IF
        IF NOT EXIST(src) THEN
            STDOUT "Error: " + $DQ + src + $DQ + " does not exist"
            EXIT FUNCTION
        END IF
        i = FREEFILE
        OPEN src FOR BINARY AS #i
            GET$ #i, LOF(#i), file
        CLOSE #i
        cmd = "push " + tgt + ">" + TRIM$(LEN(file))

    ELSEIF INSTR(LCASE$(cmd), "install ") = 1 THEN          ' INSTALL
        src = MID$(cmd, 9)
        IF NOT EXIST(src) THEN
            STDOUT "Error: " + $DQ + src + $DQ + " does not exist"
            EXIT FUNCTION
        END IF
        i = FREEFILE
        OPEN src FOR BINARY AS #i
            GET$ #i, LOF(#i), file
        CLOSE #i
        cmd = "install " + TRIM$(LEN(file))

    ELSEIF INSTR(LCASE$(cmd), "vibrate ") = 1 THEN          ' VIBRATE
        IF REMOVE$(MID$(cmd, 9), ANY ".- ") <> "" THEN
            STDOUT "Wrong vibrate scheme. Use dot ""."" dash ""-"" and pause "" "" (space)"
            EXIT FUNCTION
        ELSEIF MID$(cmd, 9) = "" THEN
            STDOUT "Empty vibrate scheme. Use dot ""."" dash ""-"" and pause "" "" (space)"
            EXIT FUNCTION
        END IF

    ELSEIF TRIM$(LCASE$(cmd)) = "help" THEN                 ' HELP
        STDOUT "Usage: waf <name-of-command>"
        STDOUT ""
        STDOUT "List of commands:"
        STDOUT "- devices*"
        STDOUT "- help*"
        STDOUT "- version*"
        STDOUT "- changelog"
        STDOUT "- logcat*"
        STDOUT "- install <pc-path-to-apk>*"
        STDOUT "- listapps"
        STDOUT "- uninstall <app-package>"
        STDOUT "- launch <app-package>/<.activity>"
        STDOUT "- pull <android-remote> <pc-local>*"
        STDOUT "- push <pc-local> <android-remote>*"
        STDOUT "- start-server*"
        STDOUT "- kill-server*"
        STDOUT "- shell <shell-command>*"
        STDOUT "- popup <some-text>"
        STDOUT "- vibrate <.|-| > (dot|dash|pause Morse code)"
        STDOUT "- browse <url|android-file>"
        STDOUT ""
        STDOUT "    * see http://developer.android.com/tools/help/adb.html"
        EXIT FUNCTION

    ELSE                                                    ' CHECK INSTRUCTION VS LIST OF AUTHORIZED KEYWORDS
        DIM kw(1 TO 16)
        ARRAY ASSIGN kw() = "devices", "version", "changelog", "logcat", "install ", "listapps", _
                            "uninstall ", "launch ", "pull ", "push ", "start-server", "kill-server", _
                            "shell ", "popup ", "vibrate ", "browse "
        FOR i = 1 TO UBOUND(kw)
            IF INSTR(LCASE$(cmd), TRIM$(kw(i))) = 1 THEN
                ans = TRIM$(i)
                EXIT FOR
            END IF
        NEXT
        IF ans = "" THEN
            STDOUT "Incorrect keyword. Please use ""waf help"" for a list of valid commands"
            EXIT FUNCTION
        ELSEIF INSTR(LCASE$(cmd), kw(i)) = 0 THEN
            STDOUT "Incorrect usage of keyword. Parameters missing. Please type ""waf help"""
            EXIT FUNCTION
        END IF
    END IF

    ' Check premium account Vs normal account with captcha
'    ShellExecute(%NULL, "open", "http://mougino.free.fr/waf.html", "", "", %SW_SHOW)
'    CON.COLOR 14, 1
'    STDOUT CTR("Type e-mail address used with Paypal")
'    STDOUT CTR("(Press Enter to ignore)")
'    STDOUT CTR("")
'    STDOUT CTR("")
'    cursiz = CON.CURSOR : curpos = CON.CELL.ROW
'    CON.CELL = curpos - 2, 5 : CON.COLOR 0, 15, 30 : CON.CURSOR = 100 : CON.LINE.INPUT mail
'    IF LEN(mail) THEN
'    ELSE
'        RANDOMIZE TIMER
'        FOR i = 1 TO 8 : mail += CHR$(RND(97,122)) : NEXT
'        CON.CELL = curpos - 4, 1 : CON.COLOR 14, 1
'        STDOUT CTR("Type the following captcha into the box")
'        STDOUT CTR(mail + $SPC)
'        STDOUT CTR("")
'        CON.CELL = curpos - 2, 16 : CON.COLOR 0, 15, 8 : CON.CURSOR = 100 : CON.LINE.INPUT pwd
'        IF pwd <> mail THEN
'            CON.COLOR 7, 0
'            CON.CURSOR = cursiz : CON.CELL = curpos, 1
'            STDOUT "Wrong captcha"
'            EXIT FUNCTION
'        END IF
'    END IF
'    CON.COLOR 7, 0
'    CON.CURSOR = cursiz : CON.CELL = curpos, 1

'    cmd = DATE$
'    cmd = RIGHT$(cmd,4) + LEFT$(cmd,2) + MID$(cmd,4,2)
'    IF cmd > "20140430" THEN
'        STDOUT "Beta expired. Thanks for your help"
'        EXIT FUNCTION
'    END IF

    ' Get TCP/IP info about this PC
    HOST NAME 0 TO myname
    HOST ADDR myname TO myip
    bip = (myip OR &HFF000000) ' broadcast IP

    ' Detect WAF server on Android device via UDP broadcasting
    FOR i = 1 TO 4
        servip = UDPdetect()
        IF servip <> 0 THEN EXIT FOR
    NEXT
    IF servip = 0 THEN
        STDOUT "No Android device detected"
        EXIT FUNCTION
    END IF

    ' Server detected - Open TCP/IP connection
    ss = FREEFILE ' ss = server socket
    TCP OPEN PORT %PORT AT IP_STR(servip) AS #ss TIMEOUT 500

    ' Send command
    t0 = TIMER
    ans = SendCommand(cmd)
    IF LEN(file) THEN  ' PUSH file content
        IF ans <> "" THEN
            file = ""  ' Error before transfer (wrong file path/name)
        ELSE
            i = 1
            DO
                TCP SEND #ss, MID$(file, i, 1024)
                i += 1024
            LOOP UNTIL i > LEN(file) OR ISTRUE ERR
        END IF
    END IF
    tf = TIMER - t0
    TCP CLOSE #ss

    ' Analyze result
    IF INSTR(LCASE$(cmd), "pull ") = 1 THEN                         ' Pull
        IF LEN(ans) > 0 AND INSTR(ans, "Wrong Android path") <> 1 AND INSTR(ans, "No such file") <> 1 THEN
            KILL tgt
            i = FREEFILE
            OPEN tgt FOR BINARY AS #i
            PUT$ #i, ans
            CLOSE #i
            ans = FORMAT$(LEN(ans), "#,") + " bytes transfered in " _
                + FORMAT$(tf, "#.000") + " second" + IIF$(tf <= 1, "", "s")
        END IF

    ELSEIF INSTR(LCASE$(cmd), "devices") = 1 THEN                   ' Devices
        STDOUT "List of devices attached"
        ans = IP_UNIQID(servip) + $TAB + ans + " (" + IP_STR(servip) + ")"

    ELSEIF LEN(file) THEN                                           ' Push & Install
        ans = FORMAT$(LEN(file), "#,") + " bytes transfered in " _
            + FORMAT$(tf, "#.000") + " second" + IIF$(tf <= 1, "", "s")
        IF INSTR(LCASE$(cmd), "install ") = 1 THEN ans += ". Install initiated"
    END IF

    IF TRIM$(ans, $LF) = "" THEN
        IF INSTR(LCASE$(cmd), "uninstall ") = 1 THEN                ' Uninstall
            ans = "Uninstall initiated"
        ELSEIF INSTR(LCASE$(cmd), "launch ") = 1 THEN               ' Launch
            ans = "Launch initiated"
        ELSEIF INSTR(LCASE$(cmd), "browse ") = 1 THEN               ' Browse
            ans = "Browse initiated"
        ELSE
            ans = "No result"
        END IF
    END IF

    STDOUT RTRIM$(ans, $LF)

END FUNCTION
'--------------------------------------------------------------------------------