2014年3月2日日曜日

開発環境

Real World Haskell―実戦で学ぶ関数型言語プログラミング(Bryan O'Sullivan (著)、 John Goerzen (著)、 Don Stewart (著)、山下 伸夫 (翻訳)、伊東 勝利 (翻訳)、株式会社タイムインターメディア (翻訳)、オライリージャパン)の10章(コード事例研究: バイナリデータフォーマットの構文解析)、10.4(暗黙の状態)、10.4.1(恒等構文解析器)、10.4.4(解析状態の取得と変更)、10.4.5(構文解析エラーの報告)、10.9(今後の方向性)の練習問題 2.を解いてみる。

その他参考書籍

練習問題 2.

前回までのコード

コード(BBEdit, Emacs)

ParseP5.hs

{-# OPTIONS -Wall -Werror #-}
module ParseP5 where

import Data.Char (isSpace)
import qualified Data.ByteString.Lazy as L
import System.Environment (getArgs)
import BeforeParseP5 (parseWhileWith,
                      (==>),
                      w2c,
                      skipSpaces,
                      (==>&),
                      assert,
                      parseNat,
                      parseByte,
                      parseOneBytes,
                      identity,
                      GreymapP5 (..),
                      getState,
                      putState,
                      ParseState (..),
                      Parse (..))

main :: IO ()
main = do
    (filename:_) <- getArgs
    contents <- L.readFile filename
    let g = runParse parseRawPGM $ ParseState contents 0
    print $ fmap fst g

parseRawPGM :: Parse GreymapP5
parseRawPGM =
    parseWhileWith w2c (not . isSpace) ==> \header -> skipSpaces ==>&
    assert (header == "P5") "invalid raw header" ==>&
    parseNat ==> \width -> skipSpaces ==>&
    parseNat ==> \height -> skipSpaces ==>&
    parseNat ==> \maxGrey -> parseByte ==>&
    assert (maxGrey <= 65535) "max grey over 65535" ==>&
    (if maxGrey < 256
     then parseOneBytes (width * height)
     else parseTwoBytes (width* height)) ==> \bitmap ->
    identity (GreymapP5 width height maxGrey bitmap)

parseTwoBytes :: Int -> Parse L.ByteString
parseTwoBytes n =
    getState ==> \st ->
    let n' = fromIntegral n
        (h, t) = L.splitAt (2 * n') (string st)
        st' = st { offset = offset st + L.length h, string = t }
    in putState st' ==>&
       assert (L.length h == 2 * n') "end of input" ==>&
       identity h

入出力結果(Terminal, runghc)

$ runghc ParseP5.hs test_p5_1.pgm 
Right GreymapP5 100x200 255
$ runghc ParseP5.hs test_p5_2.pgm 
Right GreymapP5 100x200 1024
$ runghc ParseP5.hs test_p2.pgm 
Left "byte offset 3: invalid raw header"
$ runghc ParseP5.hs temp.pgm 
Left "byte offset 376: end of input"
$

0 コメント:

コメントを投稿