1
Fork 0
This repository has been archived on 2025-04-09. You can view files and clone it, but cannot push or open issues or pull requests.
automata-reader/AutomataReader.hs

73 lines
2.6 KiB
Haskell

import Control.Applicative hiding (many, (<|>), optional)
import Data.ByteString (getContents)
import Data.Char (isAlphaNum, ord)
import Data.List
import Data.Maybe (catMaybes)
import Data.Monoid
import Prelude hiding (getContents)
import System.Environment (getArgs)
import Text.Parsec
import Text.Parsec.ByteString
import Text.Parsec.Char
import Text.Parsec.Combinator
import qualified Data.Attoparsec.ByteString as A
data Transition s i o = Transition s i s o
deriving (Show, Read, Eq, Ord)
parseInt :: Parser Int
parseInt = read <$> many1 digit
decimal :: A.Parser Int
decimal = foldl' step 0 `fmap` A.takeWhile1 isDecimal
where
step a c = a * 10 + fromIntegral (ord c - 48)
isDecimal c = c >= '0' && c <= '9'
parseString :: Parser String
parseString = many1 $ satisfy (liftA2 (||) isAlphaNum isAllowed)
where isAllowed = flip elem "._"
parseEndoSimao :: Parser [Transition Int Int Int]
parseEndoSimao = trans `endBy` newline
where
toTransition s i o t = Transition s i t o
trans = (toTransition <$> parseInt <* string " -- " <*> parseInt <* string " / " <*> parseInt <* string " -> " <*> parseInt)
aparseEndoSimao :: A.Parser [Transition Int Int Int]
aparseEndoSimao = trans `A.sepBy` (char '\n')
where
toTransition s i o t = Transition s i t o
trans = (toTransition <$> decimal <* string " -- " <*> decimal <* string " / " <*> decimal <* string " -> " <*> decimal)
parseYevtushenko :: Parser [Transition Int Int Int]
parseYevtushenko = header `endBy` newline *> (trans `endBy` newline)
where
header = choice
[ () <$ char 'F' <* space <* parseInt
, () <$ char 's' <* space <* parseInt
, () <$ char 'i' <* space <* parseInt
, () <$ char 'o' <* space <* parseInt
, () <$ string "n0" <* space <* parseInt
, () <$ char 'p' <* spaces <* parseInt
]
trans = Transition <$> parseInt <* space <*> parseInt <* space <*> parseInt <* space <*> parseInt
parseDot :: Parser [Transition String String String]
parseDot = header *> (catMaybes <$> many1 transOrNothing) <* footer
where
header = manyTill anyChar (char '{') *> manyTill anyChar newline
footer = spaces *> char '}'
transOrNothing = optionMaybe trans <* manyTill anyChar newline
trans = toTransition <$> trimmedString <* string "->" <*> trimmedString <*> io
io = between (char '[') (char ']') ((string "label=" *> (between (char '"') (char '"') ((,) <$> trimmedString <* char '/' <*> trimmedString))))
toTransition s t (i, o) = Transition s i t o
trimmedString = spaces *> parseString <* spaces
main = do
input <- getContents
let m = parse parseEndoSimao "" input
case m of
Right ts -> print $ length ts
Left e -> print e