-- Read stdin, which has lines of form "key=value". -- Lookup the command line args as keys, and print their values. -- -- $ ghc --make lmap.hs && (echo alpha=male; echo beta=max; echo 0=1; echo = ) | ./lmap alpha beta gamma 0 -- "alpha"="male","beta"="max","0"="1",""="",Nil -- male,max,NotFound,1,. -- $ module Main where import Prelude import IO import Control.Monad.Error import System.Environment import Text.ParserCombinators.Parsec main :: IO () main = do args <- getArgs --putStrLn $ joinOnCommas args --putStrLn $ joinOnCommas ["one","two","three"] lines <- getContents let emap = parseEmap "stdin" lines putStrLn $ elmShow emap putStrLn $ joinOnCommas $ map (elmLookupAsStr emap) args parseEmap :: String -> String -> Either ParseError LMap parseEmap name input = parse parseFile name input joinOnCommas :: [String] -> String joinOnCommas ss = foldr (\ x y -> x ++ "," ++ y) "." ss ---------------------------------------------------------- data LMap = LMapNode String String LMap | LMapNil instance Show LMap where show (LMapNode k v ms) = show k ++ "=" ++ show v ++ "," ++ show ms show (LMapNil) = "Nil" type EMap = Either ParseError LMap elmShow :: EMap -> String elmShow (Left s) = "\nfail ******\n" ++ show s ++ "\n******\n" elmShow (Right lmap) = show lmap elmLookupAsStr :: EMap -> String -> String elmLookupAsStr (Left _) key = "FAIL" elmLookupAsStr (Right lmap) key = lmLookupAsStr lmap key lmLookup :: LMap -> String -> Maybe String lmLookup (LMapNil) _ = Nothing lmLookup (LMapNode k v ms) key | k == key = Just v | otherwise = lmLookup ms key lmLookupAsStr :: LMap -> String -> String lmLookupAsStr ms key = case lmLookup ms key of Just s -> s Nothing -> "NotFound" ---------------------------------------------------------- parseFile :: Parser LMap parseFile = parseEof <|> parseLine parseLine :: Parser LMap parseLine = do skipWhite k <- many $ noneOf ("=" ++ white) skipWhite char '=' v <- many $ noneOf white char '\n' lmap <- parseFile return (LMapNode k v lmap) parseEof :: Parser LMap parseEof = do eof return (LMapNil) white :: String white = " \t\r\n" skipWhite :: Parser () skipWhite = skip $ many $ oneOf white skip :: Parser a -> Parser () skip p = p >> return () ----------------------------------------------------------