{- Schema -} module Schema where --import Char import Control.Monad import qualified Data.Map as M import qualified Text.ParserCombinators.Parsec as P --import Data.Either import Data.Maybe import Data.Monoid import qualified Utils as U type Column = String type Delimiter = Char data Table = Table {getName :: String, getPath :: FilePath, getDlmt :: Delimiter, getCols :: [Column]} deriving (Show) {- delimiterMap :: Map Char Char delimiterMap = fromList [('c',','), ('t','\t'), ('s',' '), ('l','~')] -} prettyPrintTables :: [Maybe Table] -> IO () prettyPrintTables [] = return () prettyPrintTables (Nothing :ts) = putStrLn "Not a table." prettyPrintTables ((Just t):ts) = do putStrLn $ (getName t) ++ " : " ++ (show.getCols$t) prettyPrintTables ts type Schema = M.Map String Table prettyPrintSchema :: Schema -> IO () prettyPrintSchema schema = prettyPrintTables $ map Just (M.elems schema) {- Schema file format: ;;;,,..., tablename can be alphanumeric, but can't start with a digit aboslutefilepath is self-explanitory delimitercharacter is coded, t for tab, c for comma, s for space, l for tilde finally, comma separated columns, with same rules as tablename -} tablename :: P.Parser String tablename = U.object abspath :: P.Parser FilePath abspath = do root <- P.char '/' rest <- P.many (P.letter P.<|> P.digit P.<|> P.char '/' P.<|> P.char '-' P.<|> P.char '_' P.<|> P.char '.') return (root:rest) P. "absoulute file path" delimiter :: P.Parser Delimiter delimiter = P.anyChar comment :: P.Parser () comment = do P.char '#' P.skipMany (P.noneOf "\n") P. "comment" eol :: P.Parser () eol = do P.oneOf "\n" return () P. "end of line" item :: P.Parser (String,Table) item = do tn <- tablename P.char ';' path <- abspath P.char ';' dlmt <- delimiter P.char ';' cols <- U.csv P.manyTill P.anyChar ( P.try eol P.<|> P.try comment P.<|> P.eof) return (tn,Table tn path dlmt cols) P. "item" line :: P.Parser (Maybe (String,Table)) line = do P.skipMany P.space P.try (comment >> return Nothing) P.<|> (item >>= return . Just) fileParser :: P.Parser [(String,Table)] fileParser = do lines <- P.many line return (catMaybes lines) {- readSchema1 :: FilePath -> IO (Either P.ParseError Schema) readSchema1 schemaPath = P.parseFromFile fileParser schemaPath >>= return . fmap (foldr (uncurry M.insert) M.empty) -} readSchema :: FilePath -> IO Schema readSchema schemaPath = do result <- P.parseFromFile fileParser schemaPath return $ case result of Left err -> M.empty Right ts -> foldr (uncurry M.insert) M.empty ts {- test instances -} sampleSchema = readSchema "/DBlimited/sampleschema.txt" sampleTable = Table "person" "/DBlimited/sample/person.csv" ',' ["id","name","address","telephone","dob"]