Real World Haskell
実戦で学ぶ関数型言語プログラミング
(オライリージャパン)
Bryan O'Sullivan (著) John Goerzen (著)
Don Stewart (著)
山下 伸夫 (翻訳) 伊東 勝利 (翻訳)
株式会社タイムインターメディア (翻訳)
開発環境
- OS X Mavericks - Apple(OS)
- BBEdit - Bare Bones Software, Inc., Emacs (Text Editor)
- Haskell (純粋関数型プログラミング言語)
- GHC (The Glasgow Haskell Compiler) (処理系)
- The Haskell Platform (インストール方法、モジュール等)
Real World Haskell―実戦で学ぶ関数型言語プログラミング(Bryan O'Sullivan (著)、 John Goerzen (著)、 Don Stewart (著)、山下 伸夫 (翻訳)、伊東 勝利 (翻訳)、株式会社タイムインターメディア (翻訳)、オライリージャパン)の10章(コード事例研究: バイナリデータフォーマットの構文解析)、10.4(暗黙の状態)、10.4.1(恒等構文解析器)、10.4.4(解析状態の取得と変更)、10.4.5(構文解析エラーの報告)、10.9(今後の方向性)の練習問題 1.を解いてみる。
その他参考書籍
- すごいHaskellたのしく学ぼう!(オーム社) Miran Lipovača(著)、田中 英行、村主 崇行(翻訳)
- プログラミングHaskell (オーム社) Graham Hutton(著) 山本 和彦(翻訳)
練習問題 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
(filename:_) <- getArgs
contents <- readFile filename
putStrLn "グレースケールファイル内容----------------------"
putStr contents
putStrLn "幅、高さ、最大グレー値--------------------------"
let g = runParse parseP2 $ ParseState contents 0
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,
offset :: Int} deriving (Show)
newtype Parse a = Parse {
runParse :: ParseState -> Either String (a, ParseState)}
identity :: a -> Parse a
identity a = Parse $ \s -> Right (a, s)
getState :: Parse ParseState
getState = Parse $ \s -> Right (s, s)
putState :: ParseState -> Parse ()
putState s = Parse $ \_ -> Right ((), s)
bail :: String -> Parse a
bail err = Parse $ \s -> Left $ "offset " ++ show (offset s) ++ ' ':err
parseP2 :: Parse GreymapP2
parseP2 =
parseHeader ==> \header -> skipSpaces ==>&
assert (header == "P2")
"invalid header(not P2)" ==>&
parseNat ==> \width -> skipSpaces ==>&
parseNat ==> \height -> skipSpaces ==>&
parseNat ==> \maxGrey -> skipSpaces ==>&
assert (maxGrey <= 255)
"over 255 error" ==>&
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
Left errMessage -> Left errMessage
Right (firstResult, newState) ->
runParse (secondParser firstResult) newState
(==>&) :: Parse a -> Parse b -> Parse b
p ==>& f = p ==> \_ -> f
assert :: Bool -> String -> Parse ()
assert True _ = identity ()
assert False err = bail err
-- 構文解析器
skipSpaces :: Parse ()
skipSpaces =
getState ==> \initState ->
let (spaces, newString) = span isSpace (string initState)
newOffset = offset initState + length spaces
in putState $
initState {string = newString,
offset = newOffset}
parseHeader :: Parse String
parseHeader =
getState ==> \initState ->
let (header, newString) =
span (not . isSpace) (string initState)
newOffset = (offset initState) + (length header)
newState = initState {
string = newString,
offset = newOffset}
in putState newState ==> \_ ->
identity header
parseNat :: Parse Int
parseNat =
getState ==> \initState ->
let (num, str) = span isDigit (string initState)
newOffset = (offset initState) + (length num)
newState = initState {string = str,
offset = newOffset}
in putState newState ==> \_ ->
if null num
then bail "parseNat error"
else identity (read num :: Int)
parseInts :: Int -> Parse [Int]
parseInts m =
getState ==> \initState ->
iter m [] (initState { string = ' ':string initState,
offset = (offset initState) - 1})
iter :: Int -> [Int] -> ParseState -> Parse [Int]
iter m ns st
| m == 0 && null (dropWhile isSpace str) = identity ns
| m /= 0 && null str = bail "parseInts error"
| m /= 0 && (isSpace (head str)) =
let (num, newString) = span isDigit (tail str)
newOffset = offset st + 1 + length num
in if null num
then bail "parseInts error"
else iter (m - 1) (ns ++ [read num :: Int]) $
st { string = newString,
offset = newOffset}
| otherwise = bail "parseInts error"
where str = string st
入出力結果(Terminal, runghc)
$ runghc ParseP2 test_p2.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 幅、高さ、最大グレー値-------------------------- Right GreymapP2 24x7 15 データ Right [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] $ runghc ParseP2 test_p5.pgm グレースケールファイル内容---------------------- P5 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 幅、高さ、最大グレー値-------------------------- Left "offset 3 invalid header(not P2)" データ Left "offset 3 invalid header(not P2)" $ runghc ParseP2 temp1.pgm グレースケールファイル内容---------------------- P2 24 7 256 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 幅、高さ、最大グレー値-------------------------- Left "offset 12 over 255 error" データ Left "offset 12 over 255 error" $ runghc ParseP2 temp2.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 幅、高さ、最大グレー値-------------------------- Left "offset 11 parseInts error" データ Left "offset 11 parseInts error" $ runghc ParseP2 temp3.pgm グレースケールファイル内容---------------------- P2 haskell 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 幅、高さ、最大グレー値-------------------------- Left "offset 3 parseNat error" データ Left "offset 3 parseNat error" $ runghc ParseP2 temp4.pgm グレースケールファイル内容---------------------- P2 24 7 a 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 幅、高さ、最大グレー値-------------------------- Left "offset 8 parseNat error" データ Left "offset 8 parseNat error" $ runghc ParseP2 temp5.pgm グレースケールファイル内容---------------------- P2 24 7 15 0 a 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 幅、高さ、最大グレー値-------------------------- Left "offset 11 parseInts error" データ Left "offset 11 parseInts error" $
0 コメント:
コメントを投稿