RegressionTests__CompressionStreamTest.st
changeset 1793 f5625dd55555
child 1815 6b8e8ac5e2db
equal deleted inserted replaced
1792:6c1e59502722 1793:f5625dd55555
       
     1 "
       
     2  COPYRIGHT (c) 2002 by eXept Software AG
       
     3               All Rights Reserved
       
     4 
       
     5  This software is furnished under a license and may be used
       
     6  only in accordance with the terms of that license and with the
       
     7  inclusion of the above copyright notice.   This software may not
       
     8  be provided or otherwise made available to, or used by, any
       
     9  other person.  No title to or ownership of the software is
       
    10  hereby transferred.
       
    11 "
       
    12 "{ Package: 'stx:goodies/regression' }"
       
    13 
       
    14 "{ NameSpace: RegressionTests }"
       
    15 
       
    16 TestCase subclass:#CompressionStreamTest
       
    17 	instanceVariableNames:''
       
    18 	classVariableNames:''
       
    19 	poolDictionaries:''
       
    20 	category:'tests-Regression-Streams'
       
    21 !
       
    22 
       
    23 !CompressionStreamTest class methodsFor:'documentation'!
       
    24 
       
    25 copyright
       
    26 "
       
    27  COPYRIGHT (c) 2002 by eXept Software AG
       
    28               All Rights Reserved
       
    29 
       
    30  This software is furnished under a license and may be used
       
    31  only in accordance with the terms of that license and with the
       
    32  inclusion of the above copyright notice.   This software may not
       
    33  be provided or otherwise made available to, or used by, any
       
    34  other person.  No title to or ownership of the software is
       
    35  hereby transferred.
       
    36 "
       
    37 !
       
    38 
       
    39 documentation
       
    40 "
       
    41     extracted testCases from CompressionStream
       
    42 "
       
    43 ! !
       
    44 
       
    45 !CompressionStreamTest class methodsFor:'tests'!
       
    46 
       
    47 compress
       
    48     "
       
    49      self compress
       
    50     "
       
    51    |fileContents in zip out|
       
    52 
       
    53    fileContents := 'symbols.stc' asFilename contentsOfEntireFile.
       
    54 
       
    55    in  := fileContents readStream.
       
    56    out := FileStream newFileNamed:'YYY.gz'.
       
    57    out ifNil:[ ^ self ].
       
    58    [ 
       
    59       zip := ZipStream writeOpenOn:out.
       
    60 
       
    61      [in atEnd] whileFalse:[ |buf|
       
    62         buf := in nextAvailable:512.
       
    63         buf do:[:n|
       
    64             zip nextPut:n
       
    65         ]
       
    66      ].
       
    67    ] ensure:[
       
    68         zip notNil ifTrue:[ zip close ].
       
    69         out isOpen ifTrue: [ out close ].
       
    70    ].
       
    71 !
       
    72 
       
    73 compress:fn
       
    74     "
       
    75      self compress
       
    76     "
       
    77    |fileContents in zip out|
       
    78 
       
    79    fileContents := fn asFilename contentsOfEntireFile.
       
    80 
       
    81    in  := fileContents readStream.
       
    82    out := FileStream newFileNamed:'YYY.gz'.
       
    83    out ifNil:[ ^ self ].
       
    84    [ 
       
    85       zip := ZipStream writeOpenOn:out.
       
    86 
       
    87      [in atEnd] whileFalse:[ |buf|
       
    88         buf := in nextAvailable:512.
       
    89         buf do:[:n|
       
    90             zip nextPut:n
       
    91         ]
       
    92      ].
       
    93    ] ensure:[
       
    94         zip notNil ifTrue:[ zip close ].
       
    95         out close.
       
    96    ].
       
    97 !
       
    98 
       
    99 testUncompress
       
   100     "
       
   101      self testUncompress #(521755 686495 false)  #(521755 686495 false)
       
   102     "
       
   103     |stream zipStream contents contentsOfOriginal|
       
   104 
       
   105     [
       
   106         stream    := 'YYY.gz' asFilename readStream.
       
   107         zipStream := ZipStream readOpenOn:stream.
       
   108         contents  := zipStream contents.
       
   109     ] ensure:[
       
   110         zipStream notNil ifTrue:[zipStream close].
       
   111         stream    notNil ifTrue:[stream close].
       
   112     ]. 
       
   113     stream := 'symbols.stc' asFilename readStream.
       
   114     contentsOfOriginal := stream contentsOfEntireFile.
       
   115     stream close.
       
   116     ^ Array with: contents size
       
   117             with: contentsOfOriginal size
       
   118             with: contents = contentsOfOriginal.
       
   119 !
       
   120 
       
   121 testUncompress: fn
       
   122     "
       
   123      (self testUncompress: 'symbols.stc') inspect
       
   124     "
       
   125     |stream zipStream contents contentsOfOriginal|
       
   126 
       
   127     self compress: fn.
       
   128     [
       
   129         stream    := 'YYY.gz' asFilename readStream.
       
   130         zipStream := ZipStream readOpenOn:stream.
       
   131         contents  := zipStream contents.
       
   132     ] ensure:[
       
   133         zipStream notNil ifTrue:[zipStream close].
       
   134         stream    notNil ifTrue:[stream close].
       
   135     ]. 
       
   136     stream := fn asFilename readStream.
       
   137     contentsOfOriginal := stream contentsOfEntireFile.
       
   138     stream close.
       
   139     ^ Array with: contents size
       
   140             with: contentsOfOriginal size
       
   141             with: contents = contentsOfOriginal.
       
   142 !
       
   143 
       
   144 uncompress
       
   145     "
       
   146      self uncompress
       
   147     "
       
   148     |stream zipStream contents|
       
   149 
       
   150     [
       
   151         stream    := 'YYY.gz' asFilename readStream.
       
   152         zipStream := ZipStream readOpenOn:stream.
       
   153         contents  := zipStream contents.
       
   154     ] ensure:[
       
   155         zipStream notNil ifTrue:[zipStream close].
       
   156         (stream   notNil and: [stream isOpen]) ifTrue:[stream close].
       
   157     ].        
       
   158     ^ contents
       
   159 ! !
       
   160 
       
   161 !CompressionStreamTest class methodsFor:'ttt'!
       
   162 
       
   163 compress:fn toFileNamed:aName
       
   164     "
       
   165     self compress:'symbols.stc' toFileNamed:'YYY'.
       
   166     "
       
   167     |sourceFile in zip out zipFile|
       
   168 
       
   169     sourceFile := fn asFilename.
       
   170     sourceFile exists ifFalse:[self error].
       
   171 
       
   172     zipFile := aName asFilename.
       
   173     zipFile := zipFile withSuffix:'gz'.
       
   174     zipFile exists ifTrue:[ zipFile remove ].
       
   175 
       
   176     in  := sourceFile readStream.
       
   177     out := FileStream newFileNamed:zipFile.
       
   178 
       
   179     [ 
       
   180         in  := sourceFile readStream.
       
   181         in binary.
       
   182         out := FileStream newFileNamed:zipFile.
       
   183         out binary.
       
   184         zip := ZipStream writeOpenOn:out.
       
   185         zip binary.
       
   186 
       
   187         [in atEnd] whileFalse:[ |buf|
       
   188             buf := in nextAvailable:512.
       
   189             buf do:[:n|
       
   190                 zip nextPut:n
       
   191             ]
       
   192         ].
       
   193     ] ensure:[
       
   194         zip notNil ifTrue:[ zip close ].
       
   195         in  notNil ifTrue:[ in  close ].
       
   196         out notNil ifTrue:[ out close ].
       
   197 
       
   198     ].
       
   199     ^ zipFile
       
   200 !
       
   201 
       
   202 test
       
   203 "
       
   204 self test
       
   205 "
       
   206     |zipFile srcFile oldContents newContents s|
       
   207 
       
   208     srcFile := 'symbols.stc' asFilename.
       
   209     zipFile := 'YYY'.
       
   210 
       
   211     self compress:srcFile toFileNamed:zipFile.
       
   212     newContents := self uncompressFileNamed:zipFile.
       
   213     oldContents := srcFile binaryContentsOfEntireFile asString.
       
   214     newContents := newContents asString.
       
   215 
       
   216     oldContents keysAndValuesDo:[:i :v|
       
   217         s := newContents at:i ifAbsent:nil.
       
   218         v = s ifFalse:[
       
   219             Transcript showCR:'#ERROR#'.
       
   220 self halt.
       
   221             ^ self
       
   222         ].
       
   223         Transcript show:v.
       
   224     ].
       
   225     self halt.
       
   226 !
       
   227 
       
   228 uncompressFileNamed:aName
       
   229     "
       
   230     self uncompressFileNamed:'YYY'
       
   231     "
       
   232     |stream zipFile zipStream outStream c|
       
   233 
       
   234     zipFile := aName asFilename.
       
   235     zipFile := zipFile withSuffix:'gz'.
       
   236 
       
   237     zipFile exists ifFalse:[ self error ].
       
   238 
       
   239     [
       
   240         stream    := zipFile readStream.
       
   241         stream binary.
       
   242 
       
   243         zipStream := ZipStream readOpenOn:stream.
       
   244         zipStream binary.
       
   245 
       
   246         outStream := #[] writeStream.
       
   247 
       
   248         [ (c := zipStream next) notNil ] whileTrue:[
       
   249             outStream nextPut:c
       
   250         ].
       
   251     ] ensure:[
       
   252         zipStream notNil ifTrue:[zipStream close].
       
   253         stream    notNil ifTrue:[stream close].
       
   254     ]. 
       
   255     ^ outStream contents
       
   256 ! !
       
   257 
       
   258 !CompressionStreamTest methodsFor:'helpers'!
       
   259 
       
   260 doTest01:compressionStreamClass
       
   261     "
       
   262      ZipStream test
       
   263      self test01_ZipStream
       
   264     "
       
   265    |original compressed contents in out zip|
       
   266 
       
   267    original := 'smalltalk.rc' asFilename contentsOfEntireFile.
       
   268 
       
   269    in := original readStream.
       
   270 
       
   271    [ |b|
       
   272         out := WriteStream on:(ByteArray new:10).
       
   273         zip := compressionStreamClass writeOpenOn:out.
       
   274 
       
   275         [in atEnd] whileFalse:[
       
   276             zip nextPut:in next
       
   277         ]
       
   278    ] ensure:[ zip notNil ifTrue:[ zip close ] ].
       
   279 
       
   280    compressed := out contents.
       
   281    [ |b|
       
   282         zip := compressionStreamClass readOpenOn:(compressed readStream).
       
   283         out := String writeStream.
       
   284 
       
   285         [ (b := zip next) notNil ] whileTrue:[ out nextPut:b ]
       
   286 
       
   287    ] ensure:[
       
   288         zip notNil ifTrue:[ zip close ].
       
   289         contents := out contents.
       
   290 
       
   291         Transcript showCR:(contents   size).
       
   292         Transcript showCR:(compressed size).
       
   293    ].
       
   294 
       
   295    original = contents ifFalse:[
       
   296         self error:'contents differs'.
       
   297         ^ self
       
   298    ].
       
   299    Transcript showCR:'OK'.
       
   300 ! !
       
   301 
       
   302 !CompressionStreamTest methodsFor:'tests'!
       
   303 
       
   304 test01_ZipStream
       
   305     "
       
   306      ZipStream test
       
   307      self test01_ZipStream
       
   308     "
       
   309    self doTest01:ZipStream
       
   310 !
       
   311 
       
   312 test02_ZipStream
       
   313     "
       
   314      ZipStream testFile
       
   315     "
       
   316    |fileContents in zip out gzipCmd|
       
   317 
       
   318    fileContents := 'smalltalk.rc' asFilename contentsOfEntireFile.
       
   319 
       
   320    in  := fileContents readStream.
       
   321    out := FileStream newFileNamed:'YYY.gz'.
       
   322    out ifNil:[ ^ self ].
       
   323 
       
   324    [ 
       
   325       zip := ZipStream writeOpenOn:out.
       
   326 
       
   327      [in atEnd] whileFalse:[ |buf|
       
   328         buf := in nextAvailable:512.
       
   329         buf do:[:n|
       
   330             zip nextPut:n
       
   331         ]
       
   332      ].
       
   333    ] ensure:[
       
   334         zip notNil ifTrue:[ zip close ].
       
   335         out close.
       
   336    ].
       
   337    gzipCmd := 'gzip -dc YYY.gz > YYY; diff YYY smalltalk.rc'.
       
   338 
       
   339    Transcript showCR:gzipCmd.
       
   340    gzipCmd printCR.
       
   341 !
       
   342 
       
   343 test03_ZipStream_testUnixAgainstClass
       
   344     "
       
   345      CompressionStream doTestUnixAgainstClass
       
   346     "
       
   347    |stream time file zipCont cmdCont|
       
   348 
       
   349    file := '/boot/vmlinuz' asFilename.
       
   350    file isReadable ifFalse:[^ self error:'not existant'].
       
   351 
       
   352    time := Time millisecondsToRun:[ |zipStream|
       
   353         zipStream := stream := zipCont := nil.
       
   354         [
       
   355             stream    := file readStream.
       
   356             zipStream := BZip2Stream readOpenOn:stream.
       
   357             zipCont   := zipStream contents.
       
   358         ] ensure:[
       
   359             zipStream notNil ifTrue:[zipStream close].
       
   360             stream    notNil ifTrue:[stream close].
       
   361         ].
       
   362    ].
       
   363    Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(zipCont size)).
       
   364 
       
   365    time := Time millisecondsToRun:[ |command|
       
   366         cmdCont := stream := nil.
       
   367         [
       
   368             command := 'gunzip < ' , file pathName.
       
   369             stream  := PipeStream readingFrom:command.
       
   370             cmdCont := stream contentsOfEntireFile.
       
   371 
       
   372         ] ensure:[
       
   373             stream notNil ifTrue:[stream close].
       
   374         ]
       
   375    ].
       
   376    Transcript showCR:('UNIX  Time : %1  Size: %2' bindWith:time with:(cmdCont size)).
       
   377 
       
   378    cmdCont = zipCont ifTrue:[ Transcript showCR:'OK' ]
       
   379                     ifFalse:[ self error:'contents differs' ].
       
   380 !
       
   381 
       
   382 test04_ZipStream_NextN
       
   383     "
       
   384         CompressionStream doTestNextN
       
   385     "
       
   386    |stream time file zipCont nxtCont|
       
   387 
       
   388    file := '/boot/vmlinuz' asFilename.
       
   389    file isReadable ifFalse:[^ self error:'not existant'].
       
   390 
       
   391    time := Time millisecondsToRun:[ |zipStream|
       
   392         zipStream := stream := zipCont := nil.
       
   393         [
       
   394             stream    := file readStream.
       
   395             zipStream := BZip2Stream readOpenOn:stream.
       
   396             zipCont   := zipStream contents.
       
   397         ] ensure:[
       
   398             zipStream notNil ifTrue:[zipStream close].
       
   399             stream    notNil ifTrue:[stream close].
       
   400         ].
       
   401    ].
       
   402    Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(zipCont size)).
       
   403 
       
   404    time := Time millisecondsToRun:[ |zipStream wstream|
       
   405         zipStream := stream := nxtCont := nil.
       
   406         [
       
   407             stream    := file readStream.
       
   408             wstream   := String writeStream.
       
   409             zipStream := BZip2Stream readOpenOn:stream.
       
   410 
       
   411             [zipStream atEnd] whileFalse:[
       
   412                 wstream nextPutAll:(zipStream next:117)
       
   413             ].
       
   414             nxtCont := wstream contents.
       
   415         ] ensure:[
       
   416             zipStream notNil ifTrue:[zipStream close].
       
   417             stream    notNil ifTrue:[stream close].
       
   418         ].
       
   419    ].
       
   420    Transcript showCR:('NEXT  Time : %1  Size: %2' bindWith:time with:(nxtCont size)).
       
   421 
       
   422    nxtCont = zipCont ifTrue:[ Transcript showCR:'OK' ]
       
   423                     ifFalse:[ self error:'contents differs' ].
       
   424 !
       
   425 
       
   426 test04_ZipStream_SkipN
       
   427 "
       
   428     CompressionStream doTestSkipN
       
   429 "
       
   430    |stream time file skpCont nxtCont skip|
       
   431 
       
   432    file := '/boot/vmlinuz' asFilename.
       
   433    file isReadable ifFalse:[^ self error:'not existant'].
       
   434 
       
   435    skip := 6885379.
       
   436 
       
   437    time := Time millisecondsToRun:[ |zipStream wstream|
       
   438         zipStream := stream := nxtCont := nil.
       
   439         [
       
   440             stream    := file readStream.
       
   441             wstream   := String writeStream.
       
   442             zipStream := BZip2Stream readOpenOn:stream.
       
   443             skip timesRepeat:[ zipStream next ].
       
   444 
       
   445             [zipStream atEnd] whileFalse:[
       
   446                 wstream nextPutAll:(zipStream next:117)
       
   447             ].
       
   448             nxtCont := wstream contents.
       
   449         ] ensure:[
       
   450             zipStream notNil ifTrue:[zipStream close].
       
   451             stream    notNil ifTrue:[stream close].
       
   452         ].
       
   453    ].
       
   454 
       
   455    Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(nxtCont size)).
       
   456 
       
   457    time := Time millisecondsToRun:[ |zipStream wstream|
       
   458         zipStream := stream := skpCont := nil.
       
   459         [
       
   460             stream    := file readStream.
       
   461             wstream   := '' writeStream.
       
   462             zipStream := BZip2Stream readOpenOn:stream.
       
   463             zipStream skip:skip.
       
   464             [zipStream atEnd] whileFalse:[
       
   465                 wstream nextPutAll:(zipStream next:117)
       
   466             ].
       
   467             skpCont := wstream contents.
       
   468         ] ensure:[
       
   469             zipStream notNil ifTrue:[zipStream close].
       
   470             stream    notNil ifTrue:[stream close].
       
   471         ].
       
   472    ].
       
   473    Transcript showCR:('NEXT  Time : %1  Size: %2' bindWith:time with:(skpCont size)).
       
   474 
       
   475    nxtCont = skpCont ifTrue:[ Transcript showCR:'OK' ]
       
   476                     ifFalse:[ self error:'contents differs' ].
       
   477 ! !
       
   478 
       
   479 !CompressionStreamTest class methodsFor:'documentation'!
       
   480 
       
   481 version
       
   482     ^ '$Header$'
       
   483 !
       
   484 
       
   485 version_CVS
       
   486     ^ '$Header$'
       
   487 ! !
       
   488