Advertisement
Not a member of Pastebin yet?
Sign Up,
it unlocks many cool features!
- {-# LANGUAGE DeriveDataTypeable#-}
- {- Extract stuff from Crusader King 3's 00_landed_titles.txt.
- You'll need parsec, syb (and containers). And of course GHC.
- Super dirty code intended to put Perl to shame.
- Boost licensed in lieu of public domain.
- Permission is hereby granted, free of charge, to any person or organization
- obtaining a copy of the software and accompanying documentation covered by
- this license (the "Software") to use, reproduce, display, distribute,
- execute, and transmit the Software, and to prepare derivative works of the
- Software, and to permit third-parties to whom the Software is furnished to
- do so, all subject to the following:
- The copyright notices in the Software and this entire statement, including
- the above license grant, this restriction and the following disclaimer,
- must be included in all copies of the Software, in whole or in part, and
- all derivative works of the Software, unless such copies or derivative
- works are solely in the form of machine-executable object code generated by
- a source language processor.
- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
- IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
- FITNESS FOR A PARTICULAR PURPOSE, TITLE AND NON-INFRINGEMENT. IN NO EVENT
- SHALL THE COPYRIGHT HOLDERS OR ANYONE DISTRIBUTING THE SOFTWARE BE LIABLE
- FOR ANY DAMAGES OR OTHER LIABILITY, WHETHER IN CONTRACT, TORT OR OTHERWISE,
- ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER
- DEALINGS IN THE SOFTWARE.
- -}
- module Main where
- import Text.Parsec.String
- import Text.Parsec.Combinator
- import Text.Parsec.Char
- import Text.Parsec.Prim
- import Text.Parsec.Language (javaStyle)
- import qualified Text.Parsec.Token as Tok
- import Data.Generics
- import Data.Set as Set
- import Data.Map as Map
- import Data.List (isPrefixOf)
- import Control.Monad
- main :: IO ()
- main = do{ result <- parseFromFile (optional bom *> titles <* eof) "00_landed_titles.txt"
- ; case result of
- Left err -> print err
- Right ast -> do
- let x = everything (Map.unionWith Set.union) (mkQ Map.empty foo) ast
- forM_ (Map.toDescList x) $ \(n, xs) -> do
- putStr "##### " >> putStr (show $ Set.size xs)
- putStr " counties with " >> putStr (show n) >> putStrLn " baronies: "
- putStrLn . unwords $ Set.toAscList xs
- putStrLn ""
- }
- foo (Def (Ident n) x) | "c_" `isPrefixOf` n = Map.singleton (everything (+) (mkQ 0 bar) x) (Set.singleton n)
- foo _ = Map.empty
- bar (Def (Ident n) x) | "b_" `isPrefixOf` n = 1
- bar _ = 0
- lexer = Tok.makeTokenParser javaStyle { Tok.commentLine = "#"
- , Tok.identStart = letter <|> char '@'
- , Tok.identLetter = alphaNum <|> oneOf ":_-'"
- }
- natural = Tok.natural lexer
- white = Tok.whiteSpace lexer
- bom :: Parser ()
- bom = void $ char '\65279'
- data Item
- = Number Integer
- | Def Ident Rhs
- | Bare Ident
- deriving (Show, Typeable,Data, Eq, Ord)
- newtype Ident = Ident String
- deriving (Show, Typeable,Data, Eq, Ord)
- data Rhs = Single Item | Multi [Item] | Hsv ()
- deriving (Show, Typeable,Data, Eq, Ord)
- symbol = Tok.symbol lexer
- braces = between (symbol "{") (symbol "}")
- titles :: Parser [Item]
- titles = many1 item
- item = Number <$> natural <|> foo
- where
- foo = do
- i <- ident
- o <- optionMaybe $ Tok.reservedOp lexer "="
- case o of
- Nothing -> return $ Bare i
- Just _ -> Def <$> pure i <*> rhs
- ident = Ident <$> Tok.identifier lexer
- rhs =
- ( (try $ Hsv <$> (void $ symbol "hsv" *> braces (many1 $ Tok.naturalOrFloat lexer))) <?> "hsv") -- Don't tell me that wasn't hacked in after the fact
- <|> (try (Multi <$> braces titles) <?> "multi")
- <|> ( (Single <$> item) <?> "bare")
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement