2014年2月27日木曜日

開発環境

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

その他参考書籍

練習問題 1.

前回までのコード

コード(BBEdit, Emacs)

ParseP2.hs

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

import Control.Applicative ((<$>))
import Data.Char (isSpace, isDigit)
import System.Environment (getArgs)

main :: IO ()
main = do
    (a:_) <- getArgs
    contents <- readFile a
    let g = runParse parseP2 $ ParseState contents
    print $ fmap fst g
    putStrLn "データ"
    print $ greyData <$> fst <$> g

data GreymapP2 = GreymapP2 {greyWith :: Int,
                            greyHeight :: Int,
                            greyMax :: Int,
                            greyData :: [Int]}
                 deriving (Eq)

instance Show GreymapP2 where
    show (GreymapP2 w h m _) = "GreymapP2 " ++ show w ++ "x" ++ show h ++
                               " " ++ show m

data ParseState = ParseState {string :: String} deriving (Show)

newtype Parse a = Parse {runParse :: ParseState -> Maybe (a, ParseState)}

-- 各構文解析器の作成に使うk共通の関数を定義
-- 恒等構文解析器
identity :: a -> Parse a
identity a = Parse $ \s -> Just (a, s)

nothing :: a -> Parse a
nothing _ = Parse $ \_ -> Nothing

-- 解析状態の取得と変更
getState :: Parse ParseState
getState = Parse $ \s -> Just (s, s)

putState :: ParseState -> Parse ()
putState s = Parse $ \_ -> Just ((), s)

parseP2 :: Parse GreymapP2
parseP2 =
    parseHeader ==> \header -> skipSpaces ==>&
    assert (header == "P2")               ==>&
    parseNat ==> \width -> skipSpaces     ==>&
    parseNat ==> \height -> skipSpaces    ==>&
    parseNat ==> \maxGrey -> skipSpaces   ==>&
    assert (maxGrey <= 255)               ==>&
    parseInts (width * height) ==> \ns -> 
       identity (GreymapP2 width height maxGrey ns)

(==>) :: Parse a -> (a -> Parse b) -> Parse b
firstParser ==> secondParser = Parse chainedParser
    where chainedParser initState =
              case runParse firstParser initState of
                   Nothing -> Nothing
                   Just (firstResult, newState) ->
                       runParse (secondParser firstResult) newState

(==>&) :: Parse a -> Parse b -> Parse b
p ==>& f = p ==> \_ -> f

assert :: Bool -> Parse ()
assert True = identity ()
assert False = nothing undefined

-- 構文解析器
skipSpaces :: Parse ()
skipSpaces =
    getState ==> \initState ->
        putState $
            initState {string = (dropWhile isSpace (string initState))}

parseHeader :: Parse String
parseHeader =
    getState ==> \initState ->
        let str = string initState
            header = takeWhile (not . isSpace) str
            newState = initState {
                string = drop (length header) str}
        in putState newState ==> \_ ->
               identity header

parseNat :: Parse Int
parseNat =
    getState ==> \initState ->
        let (num, str) = span isDigit (string initState)
            newState = initState { string = str}
        in putState newState  ==> \_ ->
               if null num
               then nothing undefined
               else identity (read num :: Int)

parseInts :: Int -> Parse [Int]
parseInts n =
    getState ==> \initState ->
        case iter n (' ':string initState) [] of
             Nothing -> nothing undefined
             Just (ns, _) ->
                 identity ns

iter :: Int -> String -> [Int] -> Maybe ([Int], ParseState)
iter n s ns
    | n == 0 && (null s || null (dropWhile isSpace s))
        = Just (ns, ParseState s)
    | n /= 0 && null s = Nothing
    | n /= 0 && (isSpace (head s)) =
        let (num, str) = span isDigit (tail s)
        in if null num
        then Nothing
        else iter (n - 1) str (ns ++ [read num :: Int])
    | otherwise = Nothing

入出力結果(Terminal, runghc)

$ runghc ParseP2.hs test.pgm 
Just GreymapP2 24x7 15
データ
Just [0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,3,3,3,3,0,0,7,7,7,7,0,0,11,11,11,11,0,0,15,15,15,15,0,0,3,0,0,0,0,0,7,0,0,0,0,0,11,0,0,0,0,0,15,0,0,15,0,0,3,3,3,0,0,0,7,7,7,0,0,0,11,11,11,0,0,0,15,15,15,15,0,0,3,0,0,0,0,0,7,0,0,0,0,0,11,0,0,0,0,0,15,0,0,0,0,0,3,0,0,0,0,0,7,7,7,7,0,0,11,11,11,11,0,0,15,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]
kamimuras-MacBook-Pro:ch10 kamimura$ runghc ParseP2.hs ParseP2.hs 
Nothing
データ
Nothing
$ cat test.pgm 
P2
24 7
15
0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
0 3 3 3 3 0 0 7 7 7 7 0 0 11 11 11 11 0 0 15 15 15 15 0
0 3 0 0 0 0 0 7 0 0 0 0 0 11 0 0 0 0 0 15 0 0 15 0
0 3 3 3 0 0 0 7 7 7 0 0 0 11 11 11 0 0 0 15 15 15 15 0
0 3 0 0 0 0 0 7 0 0 0 0 0 11 0 0 0 0 0 15 0 0 0 0
0 3 0 0 0 0 0 7 7 7 7 0 0 11 11 11 11 0 0 15 0 0 0 0
0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
$

0 コメント:

コメントを投稿