IT練習ノート

IT関連で調べたこと(実際は嵌ったこと)を書いています。

PutをBitPutにするとflushされてしまう

Binary処理が定義されているとします。

例えば、下記は1Byteの処理です。

 > :t example_ColFlags
example_ColFlags :: ColFlags
 > :t put example_ColFlags
put example_ColFlags :: Put
 >
 > BSL.writeFile "work\\colflags.bin" (runPut $ put example_ColFlags)
 >
  Offset: 00 01 02 03 04 05 06 07 08 09 0A 0B 0C 0D 0E 0F    
00000000: FF                                                 .

このようなPutが定義されているときに、前後にbit単位の処理を追加することを考えます。

joinPutを使うと、直掩までのBit処理がflushされてしまいます。

 > let foo = putBool True >> (joinPut $ put (example_ColFlags ::ColFlags)) >> putBool True
 > BSL.writeFile "work\\colflags.bin" (runPut $ runBitPut foo)
 >

ここでは、1bitを出しているので、ゼロフィルされて80が出力されてしまいます。この挙動はドキュメントに記載されています。

Run a Put inside BitPut. Any partially written bytes will be flushed before Put executes to ensure byte alignment.

  Offset: 00 01 02 03 04 05 06 07 08 09 0A 0B 0C 0D 0E 0F    
00000000: 80 FF 80                                           ...

flushを避けるため、仕方がないので、バイト単位の処理はいったんByteStringにして、それをBit処理しました。

 > let foo = putBool True >> (Bit.putByteString $ BSL.toStrict $ runPut $ put (example_ColFlags ::ColFlags)) >> putBool True
 > BSL.writeFile "work\\colflags.bin" (runPut $ runBitPut foo)
  Offset: 00 01 02 03 04 05 06 07 08 09 0A 0B 0C 0D 0E 0F    
00000000: FF C0                                              .@

いつも忘れるのでHaskellのテストの最小のひな型をメモ

package.yaml

tastyだけでなくtastyから利用するテストパッケージもdependenciesに追加する。(これを忘れていつも嵌る)

tests:
  testproj-test:
    main:                Test.hs
    source-dirs:         test
    ghc-options:
    - -threaded
    - -rtsopts
    - -with-rtsopts=-N
    dependencies:
    - testproj
    - tasty
    - tasty-discover
    - tasty-hunit
    - tasty-hspec
    - tasty-quickcheck
    - tasty-smallcheck
    - bytestring 

Hspecのひな型

テストされる側のファイルとテストファイルは同じ名前にはできない。 sは小文字

module Foo.Bar.TestBuzz

where

-- test
import Test.Tasty
import Test.Tasty.Hspec

-- my library
import Foo.Bar.Buzz

getContext = return "dummy"

spec_template = do
    before getContext $ do
      describe "some descriptions" $ do
        it "descripe it" $ \_-> True `shouldBe` True

ghciをテスト側で呼び出す

stack ghci :testproj-test

実行方法

*> hspec spec_template

some descriptions
  descripe it FAILED [1]

Failures:

  test\Foo\Bar\TestBuzz.hs:17:
  1) some descriptions descripe it
       expected: True
        but got: False

Randomized with seed 285726028

Finished in 0.0081 seconds
1 example, 1 failure
*** Exception: ExitFailure 1

Haskellタプルは実質15個まで

タプルでshoweqが定義されているのは15個まで

タプル15個

 > type Foo = (Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool)
  > (True, False, True, True, True, True, True, True, True, True, True, True, True, True, True) :: Foo
(True,False,True,True,True,True,True,True,True,True,True,True,True,True,True)

タプル16個

> type Foo = (Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool, Bool)
 > (True, False, True, True, True, True, True, True, True, True, True, True, True, True, True, True) :: Foo

<interactive>:65:1: error:
    ? No instance for (Show Foo) arising from a use of ‘print’
    ? In a stmt of an interactive GHCi command: print it
 >

HaskellのBitの取り扱い

処理の流れ

Binary.BitsからBinaryに直してBinary側でrunする。

パッケージで言えば

Data.Binary.Bits.Put -> Data.Binary.Put -> Data.ByteString.Lazy

Data.Binary.Bits.Get -> Data.Binary.Get -> Data.ByteString.Lazy

動作例

> BL.writeFile "work\\bit01.bin" $ runPut $ runBitPut $ putBool True
  Offset: 00 01 02 03 04 05 06 07 08 09 0A 0B 0C 0D 0E 0F    
00000000: 80   
> let tttt = putBool True >> putBool True >> putBool True >> putBool True
> BL.writeFile "work\\bit01.bin" $ runPut $ runBitPut tttt
>
  Offset: 00 01 02 03 04 05 06 07 08 09 0A 0B 0C 0D 0E 0F    
00000000: F0                                                 p

QuickCheckで固定長文字列を作る

*> sample' (vectorOf 4 $ choose ('a','z'))
["jvnv","ylqf","aoud","bdha","lekn","ahoy","yzdp","nyso","zzlo","gjii","cyjg"]

Ascii文字列とかUnicode文字列とか生成する機能があります。一度しっかりドキュメントを読んでおくとお釣りか来る感じ。

*> sample' (arbitrary :: Gen ASCIIString)
[ASCIIString {getASCIIString = ""},ASCIIString {getASCIIString = "$"},ASCIIString {getASCIIString = "j6&,"},ASCIIString {getASCIIString = "oK\r"},ASCIIString {getASCIIString = "<C\RSed"},ASCIIString {getASCIIString = "\ETX"},ASCIIString {getASCIIString = "UW%\\0,\EM"},ASCIIString {getASCIIString = "\GS\n\ETB229\\|6"},ASCIIString {getASCIIString = "]4"},ASCIIString {getASCIIString = "hS~\ETB0,6=#=AR\SUBk|\b\a-"},ASCIIString {getASCIIString = "Wc\f\r\aj`\t%"}]
*> sample' (arbitrary :: Gen UnicodeString)
[UnicodeString {getUnicodeString = ""},UnicodeString {getUnicodeString = "\1034127\1073198"},UnicodeString {getUnicodeString = "\81677\1040544\831699"},UnicodeString {getUnicodeString = "\1113493\21462"},UnicodeString {getUnicodeString = "\334309\608748\266552\817694\1089443\918361"},UnicodeString {getUnicodeString = "\1057239\620355\610231\833658\1060579\1092217\532093\541595\1046677"},UnicodeString {getUnicodeString = "\996908\202855\651934\1027497"},UnicodeString {getUnicodeString = "\2950\849693\955293\894527\161271\801140\977486\785568\832124\322455\534586"},UnicodeString {getUnicodeString = ""},UnicodeString {getUnicodeString = "\97513\904222\107840\484931\1105\738793\459023\934071"},UnicodeString {getUnicodeString = "\744355\735021\421255\647867\959520\264100\912824\769664\548809\993941\585201\662346\949657"}]