Announcement

Collapse

Forum Guidelines

This forum is for finished source code that is working properly. If you have questions about this or any other source code, please post it in one of the Discussion Forums, not here.
See more
See less

Move over filecache, I'm coming through.

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • Move over filecache, I'm coming through.

    In a couple of threads lately the filecache has gotten in the way of making reliable timings of code snippets under test.

    Whatever size of filecache we have, writing a sufficiently large file will only purge the head of the file, the tail will remain in the file cache. Random access will probably see some hits and affect the timings.

    One way to ensure that the file, or part of a file, is not in the filecache is to restart the system before another trial. A pain if ever there was one. We now have another way.

    During one of the aforementioned threads I was playing around with a Createfile/Readfile combo in a working app and noticed that on running another routine a particular file, which had been read previously by that routine, came in as if read for the first time; that is read from the hard drive and not the filecache. On another read it came in very quickly, as expected. However, when I ran the Createfile/Readfile combo again and followed by running the other routine again the file came in, again, as if read for the first time.

    The Createfile implemented the FILE_FLAG_NO_BUFFERING flag which effectively allows a file to come in, and out, without being buffered. It also seems that if any part or all of a particular file coming in that way is in the filecache it gets purged. This is clearly by design but I have yet to find any evidence to support this. Paul Purvis also spotted this behaviour and suggested I put something in the Source Code forum. I didn't but after the most recent thread I thought I've give it a closer look as I was getting fed up of rebooting and I now reckon that it is worth a mention.

    I also reckon that some, if not many, of you may have also spotted this behaviour but didn't think it had any value.

    Anyway, lets try it.

    If the following code is run as is, a 100MB file is written to the root of C: and then read twice. The file is cached on writing so the two reads are completed quite quickly, 0.20s and 0.17s on my machine. If you have a small filecache then try a 50MB file or whatever - the point being all of the file should be accommodated by the filecache.

    If the first ClearFileCache is uncommented and the app run again I get 2.26s and 0.19s. The file is purged from the filecache before the first read but gets cached on that read so 'belts' through on the second read.

    If we uncomment the second ClearFileCache and run again I get 2.30s and 2.75s. That is, neither read gets the benefit of caching.

    At this point the file is still in the filecache so if we now comment the first ClearFileCache and run again I get 0.19s and 2.23s, the second read is now being derived of caching.

    So far so good.

    I don't persuade easy so I rebooted and simply read the file. The filecache hadn't seen the file yet and it came in at 2.24s.

    So, there you have it. If you want to time test some 'input/number crunching' routines and want to avoid the agony of rebooting every flaming time give this a whirl.

    Added: A 2 crept into the code somehow. Conclusions are the same - the timings above have been changed to accommodate the correction of code.

    Ignore the following listing. The idea is OK but it is poorly implemented. I should remove it but I'll not hide from the fact that it is flawed.

    Go straight to ClearFileCache2 - I'm close to being happy with that. We're never really happy are we?

    Code:
    #Compile  Exe ' 8.04
    #Register None
    #DIM      ALL
    #TOOLS    OFF
    
    %NOMMIDS = 1
    %NOGDI = 1
    
    #Include "WIN32API.inc" ' 1 November 2006
    
    $sFile = "c:\test"
    
    Sub ClearFileCache(sFile As String , Buffer As String)
    Local hFile, Chunk, nbLoaded As Long, ptrBuffer As Dword Ptr
    Dim zFile As Asciiz * 256
    
    zFile = sFile
    hFile = CreateFile(zFile, %GENERIC_READ, 0, ByVal 0, %OPEN_EXISTING, %FILE_FLAG_SEQUENTIAL_SCAN Or %FILE_FLAG_NO_BUFFERING, ByVal 0)
    Chunk = Len(Buffer)
    ptrBuffer = StrPtr(Buffer)
    Do
      ReadFile( hFile, ByVal ptrBuffer, ByVal Chunk, nbLoaded, ByVal 0 )
    Loop Until nbLoaded = 0
    CloseHandle(hFile)
    End Sub
    
    Function PBMain( ) As Long
    Dim strNull As String
    Local i As Long, t1, t2 As Ext
    
    strNull = Nul$(1048576) ' 1 MB
    
    If Dir$($SFile) = "" Then
      ' Write a 100MB file
      Open $sFile For Binary As #1
      For i = 1 To 100
        Put$ #1, strNull
      Next
      Close #1
    End If
    
    ' Clear filecache after creation, if done, and before before first read
    'ClearFileCache($sFile, strNull)  
    
    ' Read file
    t1 = Timer
    t1 = Timer
    Open $sFile For Binary As #1
    For i = 1 To 100
      Get$ #1, 10[COLOR="Red"]2[/COLOR]48576, strNull ' Remove the [COLOR="Red"]2[/COLOR]
    Next
    Close #1
    t1 = Timer - t1
    
    ' Clear filecache after first reading and before second read
    'ClearFileCache($sFile, strNull)
    
    ' Read file again
    t2 = Timer
    Open $sFile For Binary As #1
    For i = 1 To 100
    Get$ #1, 10[COLOR="Red"]2[/COLOR]48576, strNull ' Remove the [COLOR="Red"]2[/COLOR]
    Next
    Close #1
    t2 = Timer - t2
    
    MsgBox Using$("##.##",t1) + " " + Using$("##.##",t2)
    
    END FUNCTION
    Last edited by David Roberts; 25 Oct 2007, 09:00 PM.

  • #2
    ClearFileCache was tailored to suit the form of getting data in PBMain ie it is string based.

    ClearFileCache2 is generic - it only needs the filename.

    FILE_FLAG_NO_BUFFERING has certain requirements which were ignored in ClearFileCache. I'm not sure of the implications of ignorance but CleaFileCache2 satisfies the requirements. ClearFileCache2 was also written a little more robustly than ClearFileCache.

    Code:
    #COMPILE EXE
    ' 8.04
    #REGISTER NONE
    #DIM ALL
    #TOOLS OFF
    #INCLUDE "WIN32API.inc" ' 1 November 2006
    
    %NOMMIDS          = 1
    %NOGDI            = 1
    %FILE_BUFFERSIZE  = 65536 ' Base size
    %OneMB            = 1048576 ' Avoids typing errors <smile>
    
    $sFile            = "c:\test"
    
    FUNCTION ClearFileCache( sFile AS STRING ) AS LONG
    LOCAL hSys, hPB, Chunk, lRes AS LONG
    LOCAL Buffer    AS DWORD PTR
    LOCAL FileSize  AS QUAD
    LOCAL nbLoaded  AS DWORD
    DIM zFile       AS ASCIIZ * 256
    
      zFile = sFile
      ' Open file without buffering - ie bypass the filecache
      hSys = CreateFile( zFile, %GENERIC_READ, 0, BYVAL 0, %OPEN_EXISTING, %FILE_FLAG_SEQUENTIAL_SCAN OR %FILE_FLAG_NO_BUFFERING, BYVAL 0 )
      IF hSys < 0 THEN
        lRes = GetLastError
        IF lRes = %ERROR_FILE_NOT_FOUND THEN
          MSGBOX "Unable to find" + " " + sFile
        ELSE
          MSGBOX STR$( lRes ) + " " + "Unknown error on opening file"
        END IF
        FUNCTION = %True
        EXIT FUNCTION
      END IF
    
      hPB = FREEFILE
      OPEN HANDLE hSys AS #hPB ' from a RTFMish remark by MCM
        FileSize = LOF( #hPB )
      CLOSE #hPB
    
      ' Chunk reading set to file size rounded up to
      ' next 64KB if file size less than 8MB else set to 8MB.
      IF FileSize < 128 * %FILE_BUFFERSIZE THEN ' ie 8MB
        Chunk = ( FileSize\65536 - 1 * ( FileSize MOD 65536 > 0 ) ) * %FILE_BUFFERSIZE ' multiples of 64KB
      ELSE
        Chunk = 128 * %FILE_BUFFERSIZE ' ie 8Mb
      END IF
    
      ' Allocate a buffer for reading - start at Chunk size and reduce, if necessary
      DO
        Buffer = VirtualAlloc( BYVAL %Null, Chunk, %MEM_RESERVE OR %MEM_TOP_DOWN, %PAGE_READWRITE )
        IF Buffer = 0 THEN
          lRes = GetLastError
          IF lRes = %ERROR_NOT_ENOUGH_MEMORY THEN
            Chunk = Chunk\2
            IF Chunk = %FILE_BUFFERSIZE / 2 THEN ' => 32KB buffer, we need a 64KB buffer minimum
              MSGBOX "Not enough memory for file reading"
              FUNCTION = %True
              EXIT FUNCTION
            END IF
          ELSE
            MSGBOX STR$( lRes ) + " " + "Unknown error allocating memory for file reading"
            FUNCTION = %True
            EXIT FUNCTION
          END IF
        ELSE
          VirtualAlloc BYVAL Buffer, Chunk, %MEM_COMMIT, %PAGE_READWRITE
          EXIT LOOP
        END IF
      LOOP
      ' OK, lets read the file
      DO
        IF ISFALSE ReadFile( hSys, BYVAL Buffer, BYVAL Chunk, nbLoaded, BYVAL 0 ) THEN
          MSGBOX "Error on reading file"
          FUNCTION = %True
          EXIT FUNCTION
        END IF
      'LOOP UNTIL nbLoaded = 0
      LOOP UNTIL nbLoaded < Chunk ' Saves a ReadFile
      CloseHandle( hSys )
      VirtualFree BYVAL Buffer, %Null, %MEM_RELEASE
    
    END FUNCTION
    
    FUNCTION PBMAIN( ) AS LONG
    DIM strNull     AS STRING
    LOCAL i AS LONG, t1, t2 AS EXT
    
      strNull = NUL$( %OneMB )
    
      IF DIR$( $SFile ) = "" THEN
        ' Write a 100MB file
        OPEN $sFile FOR BINARY AS #1
        FOR i = 1 TO 100
          PUT$ #1, strNull
        NEXT
        CLOSE #1
      END IF
    
      ' Clear filecache after creation, if done, and before before first read
      'If IsTrue ClearFileCache( $sFile ) Then Exit Function
    
      ' Read file
      t1 = TIMER ' With any timing function I always start the ball rolling with a duplicate - suspect otherwise
      t1 = TIMER
      OPEN $sFile FOR BINARY AS #1
      FOR i = 1 TO 100
        GET$ #1, %OneMB, strNull
      NEXT
      CLOSE #1
      t1 = TIMER - t1
    
      ' Clear filecache after first reading and before second read
      'If IsTrue ClearFileCache( $sFile ) Then Exit Function
    
      ' Read file again
      t2 = TIMER
      OPEN $sFile FOR BINARY AS #1
      FOR i = 1 TO 100
        GET$ #1, %OneMB, strNull
      NEXT
      CLOSE #1
      t2 = TIMER - t2
    
      MSGBOX USING$( "##.##", t1 ) + " " + USING$( "##.##", t2 )
    
    END FUNCTION
    Last edited by David Roberts; 25 Oct 2007, 04:10 PM.

    Comment


    • #3
      Seven years have past since I wrote this and Paul Purvis has come up with a faster method.

      The secret is still to use CreateFile with %FILE_FLAG_NO_BUFFERING but instead of reading the file we simply close it.

      Needless to say it is blinding fast.

      Thanks, Paul.

      Code:
      Function ClearFileCache3( sFile As String ) As Long
      Local hSys,lRes As Long
      Dim zFile       As Asciiz * 256
      
        zFile = sFile
        ' Open file without buffering - ie bypass the filecache
        hSys = CreateFile( zFile, %GENERIC_READ, 0, ByVal 0, %OPEN_EXISTING, %FILE_FLAG_SEQUENTIAL_SCAN Or %FILE_FLAG_NO_BUFFERING, ByVal 0 )
        If hSys < 0 Then
          lRes = GetLastError
          If lRes = %ERROR_FILE_NOT_FOUND Then
            MsgBox "Unable to find" + " " + sFile
          Else
            MsgBox Str$( lRes ) + " " + "Unknown error on opening file"
          End If
          Function = %True
          Exit Function
        End If
      
        CloseHandle( hSys )
      
      End Function
      Last edited by David Roberts; 1 Dec 2014, 09:22 AM. Reason: A 'l' was missng from a 'lRes'

      Comment


      • #4
        Originally posted by David Roberts View Post
        Seven years have past since I wrote this and Paul Purvis has come up with a faster method.
        I thought this was just a followup in regards to the work you and Paul have been doing over recent weeks ... didn't realise you boys have been at it for seven years now, come on I would've hoped for a crystal clear solution by now
        all jokes aside though excellent work you two! i've been following with keen interest, namely because caching is something that affects, well, every developer, and is an area where optimisations can be won and lost so like yourself I consider it important

        [edit] ugh, apologies, didn't notice this was in Source Code
        Last edited by Wayne Diamond; 1 Dec 2014, 02:42 PM.
        -

        Comment


        • #5
          Thanks, Wayne. Shouldn't really comment in the Source Code Forum otherwise Gary will put his Fire Marshall hat on.

          Comment

          Working...
          X