i could not stand the thought of this program not dealing with large files well and not being able to use this program in the future, so i revised it.
the main program has been changed and the zipped version changed as well.
this program now will read a file in blocks and save the file into chucks called sections in the p64 file it creates.
the default block(chuck) is 10MB and the block size can be adjusted on the command line as well, with a minimum block of 4MB and no maximum block size.
this will now allow just about any old computer with low memory to run this program on any large file.
actually the block sizes are faster when they are below 25MB and the cpu usage is much better as it turns out.
just place /blocksize=### on the command line along with the file name to make a change in the block size used but the program will not allow you go below a 4MB minimum. ### is in MBs
i believe i am now done with the program that saves a file to a base64 file unless there is an error i have not seen.
the way i have created sections into the base64 code should make it easy for any other program to read the base64 code file and rebuild the original file. there is a header line line before all base64 code and a trailer line after all base64 code, with each section having it's own header line and trailer line as well.
the first code worked and i have not done any testing with the new code but it should work fine.
Announcement
Collapse
save a file in base64 format then convert back to original format
Collapse
X
-
the files and exe, along with Greg Turgeon's original sha256.inc file
this program was made mostly to work on smaller files you do not want leave hanging around in their normal format, like an exe format that you do not want somebody accidentally executing.
the .p64 file that is created, has the original file dates, file size, file name, a 256 bit checksum for rebuilding back to the original format and a warnings for those people who seem to want to edit files, it has text in the header and trailer that says "DO NOT EDIT THIS FILE" or something close to it.
the file information was placed at the bottom of the file in the case somebody tries to edit the file and the editor does not read all the file and saves only part of the file back to disk. it will be more easily detected that not all the file is there.Attached FilesLast edited by Paul Purvis; 26 May 2008, 06:43 PM.
Leave a comment:
-
the sha256p64.inc file
this code came from Greg Turgeon in the source code section
thanks to Greg for his work and i hope he is please seeing his routines being used
the original listing was named sha256.inc
i made 4 changes to the original file and created sha256p64.inc
1 i removed the section that tested for a file's existence, i felt that should be done before this routine is executed and where long listing of files are made it, leaving the as was would slow the whole process down of doing working with many files.
2 i removed a the return of 53 of where files did not exist, now there should only be two returned values, 0 and 1.
3 i made the program read larger files than 2GB. mostly for other future purposes than this program. because of the fact this program reads all the information into memory then processes it, well those large files being converted to base64 will never fit into memory anyway, but this routine will check large files any how. this routine does not use much memory itself.
4 i inserted a sleep statement with variable sleep times depending on the size of the file being computed. the program was hogging the cpu on larger files and e i wanted to reduce the cpu load on longer time periods. the program is now slower but will not bring down your computer system if you are running other cpu intensive programs, maybe a web server. so now you can do those large nix iso images you have been downloading, or check a large file with data you have archived.
Code:'===================================================================== '-- SHA256P64.INC '-- WIN32 API not required '-- Uses no global data '===================================================================== TYPE tSHA_STATE state0 AS DWORD state1 AS DWORD state2 AS DWORD state3 AS DWORD state4 AS DWORD state5 AS DWORD state6 AS DWORD state7 AS DWORD pbuf AS BYTE PTR buflen AS LONG pstate AS DWORD PTR k_array AS LONG PTR END TYPE %PBUF_OFFSET = 32 %BLOCKSIZE = 64 'bytes %FILE_BUFFERSIZE = 32000 'bytes DECLARE SUB SHA_Buffer(BYVAL pBuffer AS BYTE PTR, BYVAL Length&, BYVAL Hash AS DWORD PTR) DECLARE FUNCTION SHA_File&(File_Name$, Hash$) DECLARE SUB SHA_Init(BYVAL pSHA_STATE AS tSHA_STATE PTR) DECLARE SUB SHA_Compress(BYVAL pSHA_State AS tSHA_STATE PTR) DECLARE FUNCTION MakePadding$(BYVAL TotalBytes&) '==================== SUB SHA_Init(BYVAL pSHA_STATE AS tSHA_STATE PTR) LOCAL p& @pSHA_STATE.k_array = CODEPTR(K_Array_Data) p& = CODEPTR(Init_Values) @pSHA_STATE.pstate = pSHA_STATE ! push esi ! push edi ! mov esi, p& ! mov edi, pSHA_STATE ! mov ecx, 8 ! cld ! rep movsd ! pop edi ! pop esi EXIT SUB '============ Init_Values: ! DD &h6A09E667???, &hBB67AE85???, &h3C6EF372???, &hA54FF53A??? ! DD &h510E527F???, &h9B05688C???, &h1F83D9AB???, &h5BE0CD19??? K_Array_Data: ! DD &h428a2f98???, &h71374491???, &hb5c0fbcf???, &he9b5dba5???, &h3956c25b???, &h59f111f1??? ! DD &h923f82a4???, &hab1c5ed5???, &hd807aa98???, &h12835b01???, &h243185be???, &h550c7dc3??? ! DD &h72be5d74???, &h80deb1fe???, &h9bdc06a7???, &hc19bf174???, &he49b69c1???, &hefbe4786??? ! DD &h0fc19dc6???, &h240ca1cc???, &h2de92c6f???, &h4a7484aa???, &h5cb0a9dc???, &h76f988da??? ! DD &h983e5152???, &ha831c66d???, &hb00327c8???, &hbf597fc7???, &hc6e00bf3???, &hd5a79147??? ! DD &h06ca6351???, &h14292967???, &h27b70a85???, &h2e1b2138???, &h4d2c6dfc???, &h53380d13??? ! DD &h650a7354???, &h766a0abb???, &h81c2c92e???, &h92722c85???, &ha2bfe8a1???, &ha81a664b??? ! DD &hc24b8b70???, &hc76c51a3???, &hd192e819???, &hd6990624???, &hf40e3585???, &h106aa070??? ! DD &h19a4c116???, &h1e376c08???, &h2748774c???, &h34b0bcb5???, &h391c0cb3???, &h4ed8aa4a??? ! DD &h5b9cca4f???, &h682e6ff3???, &h748f82ee???, &h78a5636f???, &h84c87814???, &h8cc70208??? ! DD &h90befffa???, &ha4506ceb???, &hbef9a3f7???, &hc67178f2??? END SUB '==================== SUB SHA_Compress(BYVAL pST AS tSHA_STATE PTR) LOCAL s_array&(), w_array&() LOCAL s AS LONG PTR, w AS LONG PTR LOCAL pk_array&, t0&, t1&, wi&, ki&, i& REDIM w_array&(63) : w = VARPTR(w_array&(0)) REDIM s_array&(7) : s = VARPTR(s_array&(0)) '-- Copy for inline assembler pk_array& = @pST.k_array ! push esi ! push edi ! push ebx '-- Copy current state into s&() ! mov esi, pST ;esi -> pST.state0 ! mov edi, s ! push esi ! mov ecx, 8 ! cld ! rep movsd '-- Copy current data block to w&() w/little-to-big endian conversion ! pop esi ;esi -> st.state0 ! add esi, %PBUF_OFFSET ;esi -> st.buf ! mov edi, w ! mov eax, [esi] ! mov esi, eax ! mov ecx, 16*4 SwapCopyTop: ! sub ecx, 4 ! mov eax, [esi+ecx] ! bswap eax ! mov [edi+ecx], eax ! test ecx, ecx ! jnz SwapCopyTop '-- Fill W[16to63] ! mov esi, w ! push ebp ! mov ebp, 16 FillTop: ! mov ebx, ebp ! sub ebx, 2 ! mov eax, [esi]+[ebx*4] ! mov ecx, eax ! mov edx, ecx ! sub ebx, 13 ;prep for next access: (-2)+(-13) = -15 ! ror eax, 17 ! ror ecx, 19 ! shr edx, 10 ! xor eax, ecx ! xor eax, edx ! mov edi, eax ;edi = temp total ! mov eax, [esi]+[ebx*4] ! mov ecx, eax ! mov edx, ecx ! ror eax, 7 ! ror ecx, 18 ! shr edx, 3 ! add ebx, 8 ;= (-15)+8 = -7 ! xor eax, ecx ! xor eax, edx ! add edi, eax ! mov eax, [esi]+[ebx*4] ! sub ebx, 9 ;= (-7)+(-9) = -16 ! add edi, eax ! mov eax, [esi]+[ebx*4] ! mov ebx, ebp ! add eax, edi ! inc ebp ! mov [esi]+[ebx*4], eax ! cmp ebp, 63 ! jg FillDone ! jmp FillTop FillDone: ! pop ebp '-- Compress: i& = 0 to 63 ! xor eax, eax ! mov esi, s ;here to CompressDone & END SUB: esi -> s[0] ! mov i&, eax CompressTop: ! mov ebx, eax ! mov edx, w ! mov eax, [edx]+[ebx*4] ! mov wi&, eax ! mov edx, pk_array& ! mov eax, [edx]+[ebx*4] ! mov ki&, eax ! mov eax, [esi+16] ! mov ecx, [esi+20] ! mov ebx, eax ! mov edx, eax ! and eax, [esi+20] ! not edx ! and edx, [esi+24] ! xor eax, edx ! mov ecx, ebx ! mov ebx, eax ! mov eax, ecx ! mov edx, ecx ! ror eax, 6 ! ror ecx, 11 ! ror edx, 25 ! add ebx, ki& ! xor eax, ecx ! add ebx, wi& ! xor eax, edx ! add eax, ebx ! add eax, [esi+28] ! mov t0&, eax ! mov eax, [esi] ! mov ecx, [esi+4] ! mov ebx, eax ! mov edx, eax ! and eax, ecx ! and edx, [esi+8] ! xor eax, edx ! and ecx, [esi+8] ! xor eax, ecx ! mov edx, eax ! mov eax, ebx ! mov ecx, ebx ! ror eax, 2 ! ror ecx, 13 ! ror ebx, 22 ! xor eax, ecx ! xor eax, ebx ! add eax, edx ! mov t1&, eax ' @s[7] = @s[6] : @s[6] = @s[5] : @s[5] = @s[4] : @s[4] = @s[3] + t0& ' @s[3] = @s[2] : @s[2] = @s[1] : @s[1] = @s[0] : @s[0] = t0& + t1& ! mov edi, esi ! mov ecx, t0& ! mov eax, [esi+24] ;@s[7] = @s[6] ! mov ebx, [esi+20] ;@s[6] = @s[5] ! mov edx, [esi+16] ;@s[5] = @s[4] ! mov [edi+28], eax ! mov [edi+24], ebx ! mov [edi+20], edx ! mov eax, [esi+12] ;@s[4] = @s[3] + T0& ! mov ebx, [esi+8] ;@s[3] = @s[2] ! add eax, ecx ! mov edx, [esi] ;@s[1] = @s[0] ! mov [edi+12], ebx ! mov [edi+16], eax ! mov ebx, ecx ;@s[0] = T0& + T1& ! mov eax, [esi+4] ;@s[2] = @s[1] ! mov [edi+4], edx ! add ebx, t1& ! mov [edi+8], eax ! mov [edi], ebx ! mov eax, i& ! inc eax ! cmp eax, 63 ! jg CompressDone ! mov i&, eax ! jmp CompressTop CompressDone: '-- Add current state s() to context ' for i& = 0 to 7 : @[email protected][i&] = @[email protected][i&] + @s[i&] : next i& ! mov edi, pST ! mov ecx, 8*4 AddCopyTop: ! sub ecx, 4 ! mov eax, [edi+ecx] ! add eax, [esi+ecx] ! mov [edi+ecx], eax ! test ecx, ecx ! jnz AddCopyTop ! pop ebx ! pop edi ! pop esi END SUB '==================== SUB SHA_Buffer(BYVAL DataBuffer AS BYTE PTR, BYVAL Length&, BYVAL Hash AS DWORD PTR) EXPORT '-- Expects parameter Hash to point to buffer of correct size of 32 bytes (256bits \ 8) REGISTER i& LOCAL lastbuff$ LOCAL st AS tSHA_STATE, p& i& = Length& AND (%BLOCKSIZE-1) lastbuff$ = PEEK$((DataBuffer + Length&) - i&, i&) lastbuff$ = lastbuff$ + MakePadding$(Length&) SHA_Init BYVAL VARPTR(st) st.buflen = Length& st.pbuf = DataBuffer i& = Length& AND (NOT %BLOCKSIZE-1) DO WHILE i& SHA_Compress BYVAL VARPTR(st) st.pbuf = st.pbuf + %BLOCKSIZE i& = i& - %BLOCKSIZE LOOP st.buflen = LEN(lastbuff$) st.pbuf = STRPTR(lastbuff$) DO WHILE st.buflen SHA_Compress BYVAL VARPTR(st) st.pbuf = st.pbuf + %BLOCKSIZE st.buflen = st.buflen - %BLOCKSIZE LOOP '-- Copy current state (as dwords) from s&() to Hash ' for i& = 0 to 7 : @Hash[i&] = [email protected][i&] : next i& p& = st.pstate ! push esi ! push edi ! mov esi, p& ;esi -> st.state0 ! mov edi, Hash ! mov ecx, 8 ! cld ! rep movsd ! pop edi ! pop esi END SUB '==================== FUNCTION SHA_File&(File_Name$, Hash$) EXPORT '-- Returns 0 on success, or PB (not OS) error code REGISTER i& REGISTER ilinecount AS LONG LOCAL ibreaktosleep AS LONG LOCAL bytesleft&& LOCAL buffer$, padding$ LOCAL st AS tSHA_STATE, phash AS DWORD PTR LOCAL infile&, ecode&, lastpass&, maxstring& '-- If file not found, return PB error code 'IF LEN(DIR$(File_Name$)) = 0 THEN ' FUNCTION = 53 : EXIT FUNCTION 'END IF buffer$ = STRING$(%FILE_BUFFERSIZE, 0) maxstring& = %FILE_BUFFERSIZE st.buflen = %BLOCKSIZE SHA_Init BYVAL VARPTR(st) infile& = FREEFILE OPEN File_Name$ FOR BINARY LOCK SHARED AS infile& BASE=0 IF ERR THEN GOTO SHA_File_Error bytesleft&& = LOF(infile&) ibreaktosleep=50& IF bytesleft&&>50000000 THEN ibreaktosleep=40& IF bytesleft&&>100000000 THEN ibreaktosleep=30& IF bytesleft&&>200000000 THEN ibreaktosleep=25& IF bytesleft&&>300000000 THEN ibreaktosleep=20& padding$ = MakePadding$(bytesleft&&) DO 'Resize if necessary & flag final buffer IF bytesleft&& =< maxstring& THEN maxstring& = bytesleft&& buffer$ = STRING$(maxstring&, 0) INCR lastpass& END IF INCR ilinecount IF ilinecount=ibreaktosleep THEN ilinecount=0:SLEEP 20 GET infile&,, buffer$ : IF ERR THEN GOTO SHA_File_Error IF lastpass& THEN buffer$ = buffer$ + padding$ st.pbuf = STRPTR(buffer$) FOR i& = 1 TO (LEN(buffer$) \ %BLOCKSIZE) SHA_Compress BYVAL VARPTR(st) st.pbuf = st.pbuf + %BLOCKSIZE NEXT i& bytesleft&& = bytesleft&& - maxstring& LOOP UNTIL lastpass& CLOSE infile& : IF ERR THEN GOTO SHA_File_Error '-- Copy current state (as dwords) from s&() to Hash$ 'for i& = 0 to 7 : @Hash[i&] = [email protected][i&] : next i& Hash$ = STRING$(32,0) phash = STRPTR(Hash$) lastpass& = st.pstate ! push esi ! push edi ! mov esi, lastpass& ;esi -> st.state0 ! mov edi, phash ! mov ecx, 8 ! cld ! rep movsd ! pop edi ! pop esi Exit_SHA_File: FUNCTION = ecode& EXIT FUNCTION '============ SHA_File_Error: IF ERR THEN ecode& = ERRCLEAR ELSE ecode& = -1 END IF RESUME Exit_SHA_File END FUNCTION '========================= FUNCTION MakePadding$(BYVAL TotalBytes&) '-- Creates the necessary string to append to buffer being hashed LOCAL buffbits&&, padding$ LOCAL pbyte1 AS BYTE PTR, pbyte2 AS BYTE PTR, padbytes&, i& buffbits&& = TotalBytes& * 8 padding$ = STRING$(8,0) pbyte1 = STRPTR(padding$) : pbyte2 = VARPTR(buffbits&&) '-- Copy bytes in reverse FOR i& = 0 TO 7 @pbyte1[i&] = @pbyte2[7 - i&] NEXT i& padbytes& = %BLOCKSIZE - ((TotalBytes&+9) AND (%BLOCKSIZE-1)) FUNCTION = CHR$(&h80) + STRING$(padbytes&,0) + padding$ END FUNCTION '-- END SHA256P64.INC ---------------------------------------------------
Last edited by Paul Purvis; 26 May 2008, 12:37 PM.
Leave a comment:
-
save a file in base64 format then convert back to original format
here is the first program of two programs i had written to save a file in base64 format
the second program to convert back from a base64 format to an original format is not yet written but will not take as long as the first part.
i am placing the file here to convert to base64 format first.
because i am including more information into the file than just the base64 code, i am call this format base64p and it will have an file extension of .p64
well it should not be that hard to guess where the p comes from.
i will make more comments on this later, it is late and i need some rest.
Code:'file2p64.bas 'written in pbcc 4.04 'this program converts a file into base64p format. 'base64p format is extended format from base64 created by p purvis ' 'full credit goes to Semen Matusovski for his base64 routines ' #COMPILE EXE #DIM ALL #REGISTER NONE GLOBAL gsfiledatetime1 AS STRING GLOBAL gsfiledatetime2 AS STRING GLOBAL gsfiledatetime3 AS STRING GLOBAL gsfiledatetime4 AS STRING GLOBAL gsfiledatetime5 AS STRING GLOBAL gsfiledatetime6 AS STRING GLOBAL gqinputfilesize AS QUAD #INCLUDE "WIN32API.INC" #INCLUDE "SHA256P64.INC" DECLARE FUNCTION PathMatchSpec LIB "SHLWAPI.DLL" ALIAS "PathMatchSpecA"(pszFile AS ASCIIZ, pszSpec AS ASCIIZ) AS LONG ' OutBuf is not necessary to allocate ' $CRLF after each nGroups per 3 input bytes FUNCTION Encode_BASE64(BYREF InBuf AS STRING, BYVAL nGroups AS LONG, OutBuf AS STRING) AS LONG #REGISTER NONE LOCAL qtemp AS QUAD qtemp=(4 * FIX((LEN(InBuf) + 2) / 3) + 2 * FIX(LEN(InBuf) / (3 * nGroups))) OutBuf = SPACE$(qtemp) ! PUSH EBX ! LEA EBX, Encode_BASE64_Trt ! MOV EDI, OutBuf ! MOV EDI, [EDI] ' StrPtr(OutBuf) ! MOV ESI, InBuf ! MOV ESI, [ESI] ' StrPtr(InBuf) ! MOV EDX, ESI ! Sub EDX, 4 ! MOV EDX, [EDX] ' Len(InBuf) ! MOV ECX, nGroups Encode_BASE64_Lb1: INCR qtemp ! CMP EDX, 0 ! JLE Encode_BASE64_Lb4 ! MOV AL, [ESI] ! SHR AL, 2 ! XLATB ! MOV [EDI], AL ! INC EDI ! MOV AL, [ESI + 1] ! MOV AH, [ESI] ! SHR AX, 4 ! And AL, &H3F ! XLATB ! MOV [EDI], AL ! INC EDI ! CMP EDX, 1 ! JNE Encode_BASE64_Lb2 ! MOV AL, 61 ' Add == ! MOV [EDI], AL ! INC EDI ! MOV [EDI], AL ! INC EDI ! JMP Encode_BASE64_Lb4 Encode_BASE64_Lb2: ! MOV AL, [ESI + 2] ! MOV AH, [ESI + 1] ! SHR AX, 6 ! And AL, &H3F ! XLATB ! MOV [EDI], AL ! INC EDI ! CMP EDX, 2 ! JNE Encode_BASE64_Lb3 ! MOV AL, 61 ' Add = ! MOV [EDI], AL ! INC EDI ! JMP Encode_BASE64_Lb4 Encode_BASE64_Lb3: ! MOV AL, [ESI + 2] ! And AL, &H3F ! XLATB ! MOV [EDI], AL ! INC EDI ! Add ESI, 3 ! Sub EDX, 3 ! DEC ECX ! CMP ECX, 0 ! JNE Encode_BASE64_Lb1 ! MOV AL, 13 ' Add $CRLF ! MOV [EDI], AL ! MOV AL, 10 ! MOV [EDI + 1], AL ! Add EDI, 2 ! MOV ECX, nGroups ! JMP Encode_BASE64_Lb1 Encode_BASE64_Lb4: ! POP EBX EXIT FUNCTION Encode_Base64_Trt: ! DB 65, 66, 67, 68, 69, 70, 71, 72, 73, 74, 75, 76, 77, 78, 79, 80, 81, 82, 83, 84, 85, 86, 87, 88, 89, 90 ! DB 97, 98, 99,100,101,102,103,104,105,106,107,108,109,110,111,112,113,114,115,116,117,118,119,120,121,122 ! DB 48, 49, 50, 51, 52, 53, 54, 55, 56, 57, 43, 47 END FUNCTION FUNCTION FileTimeToInternationalTime(File_Time AS FILETIME) AS STRING LOCAL Sys_Time AS SystemTime FileTimeToSystemTime File_Time, Sys_Time FUNCTION = _ FORMAT$(Sys_Time.wyear, "0000") & "-" & FORMAT$(Sys_Time.wMonth, "00") & "-" & _ FORMAT$(Sys_Time.wDay, "00") & " " & FORMAT$(Sys_Time.wHour, "00") & ":" & _ FORMAT$(Sys_Time.wMinute, "00") & ":" & FORMAT$(Sys_Time.wSecond, "00") END FUNCTION FUNCTION FileTimeToLocal(File_Time AS FILETIME) AS STRING LOCAL Sys_Time AS SystemTime FileTimeToSystemTime File_Time, Sys_Time FUNCTION = _ FORMAT$(Sys_Time.wyear, "0000") & "-" & FORMAT$(Sys_Time.wMonth, "00") & "-" & _ FORMAT$(Sys_Time.wDay, "00") & " " & FORMAT$(Sys_Time.wHour, "00") & ":" & _ FORMAT$(Sys_Time.wMinute, "00") & ":" & FORMAT$(Sys_Time.wSecond, "00") END FUNCTION FUNCTION getinputfileinfointoglobalvar(somefile AS STRING) AS LONG LOCAL hFile AS DWORD LOCAL FindData AS WIN32_FIND_DATA LOCAL lsys AS systemtime LOCAL SYS_TIME AS SYSTEMTIME FUNCTION=0 hFile = FindFirstFile(BYVAL STRPTR(SomeFile), FindData) 'Get file data, file time included IF hFile <> %INVALID_HANDLE_VALUE THEN 'We have an handle coresponding to the file gqinputfilesize= FindData.nFileSizeHigh * (%MAXDWORD + 1) + FindData.nFileSizeLow FileTimeToSystemTime FindData.ftCreationTime, Lsys gsfiledatetime1=FileTimeToInternationalTime(FindData.ftCreationTime) gsfiledatetime2=FileTimeToInternationalTime(FindData.ftLastAccessTime) gsfiledatetime3=FileTimeToInternationalTime(FindData.ftLastWriteTime) FileTimeToLocalFileTime FindData.ftCreationTime, FindData.ftCreationTime FileTimeToLocalFileTime FindData.ftLastAccessTime, FindData.ftLastAccessTime FileTimeToLocalFileTime FindData.ftLastWriteTime, FindData.ftLastWriteTime gsfiledatetime4=FileTimeToLocal(FindData.ftCreationTime) gsfiledatetime5=FileTimeToLocal(FindData.ftLastAccessTime) gsfiledatetime6=FileTimeToLocal(FindData.ftLastWriteTime) FUNCTION=1 END IF END FUNCTION FUNCTION PBMAIN () AS LONG LOCAL sinputfilename AS STRING LOCAL soutputfilename AS STRING LOCAL sbase64p AS STRING 'string build from file to pass to decodebase64 routine LOCAL sunbase64p AS STRING 'string returned from decodebase64 routine LOCAL qlengthinputfile AS QUAD 'sets the array size for reading file in increments LOCAL sinputfilechecksummethod AS STRING LOCAL sinputfilechecksumvalue AS STRING LOCAL stempinputfilename AS STRING LOCAL isha256errorcode AS LONG LOCAL psha256binarystringptr AS DWORD PTR LOCAL ssha256alphastring AS STRING LOCAL ssha256binarystring AS STRING LOCAL qbyteslefttoread AS QUAD LOCAL ibytestoread AS LONG LOCAL qbytestoreadinblock AS QUAD LOCAL iblockprocessing AS LONG LOCAL itemp AS LONG LOCAL stemp AS STRING FUNCTION=2 'get file name or display help message from the command line sinputfilename=TRIM$(COMMAND$) IF LEN(sinputfilename)=0 THEN GOTO nocommandlinegiven IF INSTR(sinputfilename,"?")<>0 THEN GOTO nocommandlinegiven qbytestoreadinblock=10485760&& sinputfilename=sinputfilename+" " stemp=UCASE$(sinputfilename) itemp=INSTR(stemp,"/BLOCKSIZE=") IF itemp THEN stemp=MID$(sinputfilename,itemp,(INSTR(itemp,sinputfilename," ")-itemp)) REPLACE stemp WITH "" IN sinputfilename itemp=LEN(stemp)- INSTR(stemp,"=") qbytestoreadinblock=VAL(RIGHT$(stemp,itemp)) IF qbytestoreadinblock THEN qbytestoreadinblock=qbytestoreadinblock*1048576&& END IF sinputfilename=TRIM$(sinputfilename) 'set the output file name soutputfilename=sinputfilename+".p64" sinputfilechecksummethod="none" sinputfilechecksumvalue="" IF qbytestoreadinblock<4194304&& THEN qbytestoreadinblock=4194304&& STDOUT "convert file to base64p format" STDOUT "file from commmand line " STDOUT "["+sinputfilename+"]" STDOUT "checking if file exist" itemp=getinputfileinfointoglobalvar(sinputfilename) IF itemp=0 THEN GOTO errorfiledoesnotexist STDOUT "length of file is "+TRIM$(STR$(gqinputfilesize)) IF gqinputfilesize =0 THEN GOTO createbase64pfile END IF STDOUT "calculating checksum of file" TRY OPEN sinputfilename FOR INPUT AS #1 CLOSE #1 CATCH GOTO errorinreadingfile END TRY isha256errorcode = SHA_File&(sinputfilename, ssha256binarystring) IF isha256errorcode =0 THEN psha256binarystringptr = STRPTR(ssha256binarystring) ssha256alphastring="" FOR itemp = 0 TO 7 ssha256alphastring = ssha256alphastring + HEX$(@psha256binarystringptr[itemp], 8) NEXT itemp sinputfilechecksummethod="sha256" sinputfilechecksumvalue=ssha256alphastring ELSE 'PRINT "sha256p64 error" END IF STDOUT "calculating done" STDOUT "opening input file "+sinputfilename TRY OPEN sinputfilename FOR BINARY ACCESS READ WRITE LOCK READ WRITE AS #1 CATCH GOTO errorinreadingfile END TRY qlengthinputfile=LOF(#1) IF qlengthinputfile<>gqinputfilesize THEN GOTO errorinreadingfile qbyteslefttoread=qlengthinputfile STDOUT "opening output file "+soutputfilename TRY OPEN soutputfilename FOR OUTPUT AS #2 PRINT #2,""; CLOSE #2 CATCH GOTO errorinwritingfile END TRY STDOUT "block size used"+STR$(qbytestoreadinblock/1048576)+"Mb" STDOUT "processing"+STR$((qbyteslefttoread\qbytestoreadinblock)+1)+" block(s)" 'read the file convert then save the base64 code into the file GOTO createbase64pfile 'processing blocks of data in the input file readsectionofinputfile: sunbase64p="" sbase64p="" IF qbyteslefttoread=0 THEN GOTO wrapupbasep64file IF qbyteslefttoread>qbytestoreadinblock THEN ibytestoread=qbytestoreadinblock ELSE ibytestoread=qbyteslefttoread END IF qbyteslefttoread=qbyteslefttoread-ibytestoread TRY GET$ #1, ibytestoread,sunbase64p IF LEN(sunbase64p)=0 THEN GOTO errorinreadingfile CATCH GOTO errorinreadingfile END TRY Encode_BASE64(sunbase64p, 18, sbase64p) sunbase64p="" GOTO updatebasep64file createbase64pfile: stempinputfilename=STRREVERSE$("\"+sinputfilename) itemp=INSTR(stempinputfilename, ANY "\:") stempinputfilename=LEFT$(stempinputfilename,itemp-1) stempinputfilename=STRREVERSE$(stempinputfilename) TRY OPEN soutputfilename FOR BINARY ACCESS READ WRITE LOCK READ WRITE AS #2 PUT$ 2, "start of file marker WARNING DO NOT EDIT ANY OF THIS FILE"+$CRLF PUT$ 2, "any editing could and should and will destroy the use of this file"+$CRLF+$CRLF IF gqinputfilesize =0 THEN PUT$ 2, "**base64pstartbase64pstartbase64pstart"+$CRLF PUT$ 2, "*sectionstartsectionstartsectionstart"+$CRLF PUT$ 2, "*sectonendsectionendsectionend"+$CRLF GOTO wrapupbasep64file PUT$ 2, REPEAT$(72,"0") END IF PUT$ 2, "**base64pstartbase64pstartbase64pstart"+$CRLF CATCH GOTO errorinwritingfile END TRY GOTO readsectionofinputfile updatebasep64file: TRY PUT$ 2, "*sectionstartsectionstartsectionstart"+$CRLF PUT$ 2, sbase64p+$CRLF PUT$ 2, "*sectonendsectionendsectionend"+$CRLF IF qbyteslefttoread THEN PUT$ 2, $CRLF CATCH GOTO errorinwritingfile END TRY GOTO readsectionofinputfile wrapupbasep64file: TRY PUT$ 2, "**base64pendbase64pendbase64pend"+$CRLF PUT$ 2, $CRLF+$CRLF PUT$ 2, "filename:"+LCASE$(stempinputfilename)+$CRLF PUT$ 2, "filesize:"+TRIM$(STR$(gqinputfilesize))+$CRLF PUT$ 2, "filetimecreationutc:"+gsfiledatetime1+$CRLF PUT$ 2, "filetimelastaccessedutc:"+gsfiledatetime2+$CRLF PUT$ 2, "filetimelastwriteutc:"+gsfiledatetime3+$CRLF PUT$ 2, "checksummethod:"+LCASE$(sinputfilechecksummethod)+$CRLF PUT$ 2, "checkvl:"+LCASE$(sinputfilechecksumvalue)+$CRLF+$CRLF PUT$ 2, "local date/time creation last accessed last write"+$CRLF PUT$ 2, " "+gsfiledatetime1+" "+gsfiledatetime2+" "+gsfiledatetime3+$CRLF+$CRLF PUT$ 2, "end of file marker WARNING DO NOT EDIT ANY OF THIS FILE"+$CRLF PUT$ 2, "any editing could and should and will destroy the use of this file"+$CRLF+$CRLF CLOSE #2 CATCH GOTO errorinwritingfile END TRY STDOUT "completed conversion" STDOUT "DOS ERRLEVEL returned 10" FUNCTION=10 GOTO finish nocommandlinegiven: STDOUT "program converts a file into base64 format" STDOUT "place the file to convert on the commandline" STDOUT "the default block size used in coverting is 10MB, with a of mimium of 4MB" STDOUT "to change block size in MBs, add /blocksize=### on the comammandline" STDOUT "the output file name will have .p64 added to the file on the command line" STDOUT "this program does not validate the input file for a base64 format" STDOUT "DOS ERRLEVEL returned for batch processing or returning to a program" STDOUT " 0=program failure" STDOUT " 1=no command line given or viewing of this screen with ? on command line" STDOUT " 2=program failure" STDOUT " 3=error in reading input file" STDOUT " 4=error in reading no commandline given or viewing of this screen" STDOUT " 10=program completed: input file has no blank lines at end of file" STDOUT " 11=program completed: read input file successfully" STDOUT "pausing for 10 seconds" FUNCTION=1 SLEEP 10000 GOTO finish errorinreadingfile: CLOSE #1 sunbase64p="" sbase64p="" STDOUT "error! error! error!" STDOUT "error-in reading the input file "+sinputfilename STDOUT "error-no specfic error given" STDOUT " make sure the file exist" STDOUT " if file exist make sure the file is not being used by another program" STDOUT " if file exist make sure the file is not filled with spaces STDOUT "pausing for 10 seconds" FUNCTION=3 SLEEP 10000 GOTO finish errorinwritingfile: CLOSE #1 sunbase64p="" sbase64p="" STDOUT "error! error! error!" STDOUT "error-in writing the output file "+soutputfilename STDOUT "error-no specfic error given" STDOUT " make sure the file is not being used by another program" STDOUT " make sure there is disk space available" STDOUT " make sure there is file block space available" STDOUT " make sure there is enough memory in comptuer" STDOUT "pausing for 10 seconds" FUNCTION=4 SLEEP 10000 GOTO finish errorfiledoesnotexist: STDOUT "error! error! error!" STDOUT "cannot locate the file "+sinputfilename STDOUT "pausing for 10 seconds" FUNCTION=4 SLEEP 10000 GOTO finish FINISH: 'stdout "press any key to continue" 'sbase64p="" 'sunbase64p="" 'waitkey$ END FUNCTION
Last edited by Paul Purvis; 26 May 2008, 06:41 PM.Tags: None
Leave a comment: