{-# LANGUAGE OverloadedStrings #-} module Main where import Data.Aeson import Data.Monoid import qualified Data.Map.Strict as M import Data.Text (Text) import qualified Data.Text.Encoding as T (decodeUtf8) import Data.List (intersperse) import qualified Data.Text as T import qualified Data.Text.Lazy.IO as TL import Data.Maybe (catMaybes) import Control.Applicative import Data.ByteString.Lazy as BL hiding (map, intersperse) import qualified Data.ByteString.Lazy.Char8 as BS import Data.Attoparsec.Lazy as Atto hiding (Result) import Data.Attoparsec.ByteString.Char8 (endOfLine, sepBy) import qualified Data.Attoparsec.Text as AT import qualified Data.HashMap.Lazy as HM import qualified Data.Vector as V import Data.Scientific import System.Environment (getArgs) import qualified Data.Text.Lazy.Builder as B import qualified Data.Text.Lazy.Builder.Int as B import qualified Data.Text.Lazy.Builder.RealFloat as B import qualified Options.Applicative as O import qualified Text.CSV as CSV data Options = Options { jsonExpr :: String, arrayDelim :: String, outputMode :: OutputMode } deriving Show data OutputMode = TSVOutput { delimiter :: String } | CSVOutput deriving (Show) parseOpts :: O.Parser Options parseOpts = Options <$> O.argument O.str (O.metavar "FIELDS") <*> O.strOption (O.metavar "STRING" <> O.value "," <> O.short 'a' <> O.help "concatentated array elem delimiter. Default to comma") <*> ((O.flag' CSVOutput (O.short 'c' <> O.long "csv" <> O.help "output CSV")) <|> (TSVOutput <$> (O.strOption (O.metavar "STRING" <> O.value "\t" <> O.short 'd' <> O.help "output field delimiter. Defaults to tab")))) opts = O.info (O.helper <*> parseOpts) (O.fullDesc <> O.progDesc "Transform JSON objects to TSV" <> O.header "jsontsv") main = do Options expr arrayDelim mode <- O.execParser opts x <- BL.getContents let xs :: [Value] xs = decodeStream x ks' = parseKeyPath $ T.pack expr arrayDelim' = T.pack arrayDelim -- Prelude.putStrLn $ "key Paths " ++ show ks' case mode of TSVOutput delim -> mapM_ (TL.putStrLn . B.toLazyText . evalToLineBuilder arrayDelim' delim ks') xs CSVOutput -> Prelude.putStrLn . CSV.printCSV $ map (map T.unpack . evalToList arrayDelim' ks') $ xs decodeStream :: (FromJSON a) => BL.ByteString -> [a] decodeStream bs = case decodeWith json bs of (Just x, xs) | xs == mempty -> [x] (Just x, xs) -> x:(decodeStream xs) (Nothing, _) -> [] decodeWith :: (FromJSON a) => Parser Value -> BL.ByteString -> (Maybe a, BL.ByteString) decodeWith p s = case Atto.parse p s of Atto.Done r v -> f v r Atto.Fail _ _ _ -> (Nothing, mempty) where f v' r = (\x -> case x of Success a -> (Just a, r) _ -> (Nothing, r)) $ fromJSON v' parseKeyPath :: Text -> [KeyPath] parseKeyPath s = case AT.parseOnly pKeyPaths s of Left err -> error $ "Parse error " ++ err Right res -> res spaces = many1 AT.space pKeyPaths :: AT.Parser [KeyPath] pKeyPaths = pKeyPath `AT.sepBy` spaces pKeyPath :: AT.Parser KeyPath pKeyPath = AT.sepBy1 pKeyOrIndex (AT.takeWhile1 $ AT.inClass ".[") pKeyOrIndex = pIndex <|> pKey pKey = Key <$> AT.takeWhile1 (AT.notInClass " .[") pIndex = Index <$> AT.decimal <* AT.char ']' type KeyPath = [Key] data Key = Key Text | Index Int deriving (Eq, Show) evalToLineBuilder :: Text -> String -> [KeyPath] -> Value -> B.Builder evalToLineBuilder arrayDelim delim ks v = mconcat $ intersperse (B.fromText . T.pack $ delim) $ map (flip (evalToBuilder arrayDelim) v) ks type ArrayDelimiter = Text evalToList :: Text -> [KeyPath] -> Value -> [Text] evalToList arrayDelim ks v = map (flip (evalToText arrayDelim) v) ks evalToBuilder :: ArrayDelimiter -> KeyPath -> Value -> B.Builder evalToBuilder d k v = valToBuilder $ evalKeyPath d k v evalToText :: ArrayDelimiter -> KeyPath -> Value -> Text evalToText d k v = valToText $ evalKeyPath d k v -- evaluates the a JS key path against a Value context to a leaf Value evalKeyPath :: ArrayDelimiter -> KeyPath -> Value -> Value evalKeyPath d [] x@(String _) = x evalKeyPath d [] x@Null = x evalKeyPath d [] x@(Number _) = x evalKeyPath d [] x@(Bool _) = x evalKeyPath d [] x@(Object _) = x evalKeyPath d [] x@(Array v) = let vs = V.toList v xs = intersperse d $ map (evalToText d []) vs in String . mconcat $ xs evalKeyPath d (Key key:ks) (Object s) = case (HM.lookup key s) of Just x -> evalKeyPath d ks x Nothing -> Null evalKeyPath d (Index idx:ks) (Array v) = let e = (V.!?) v idx in case e of Just e' -> evalKeyPath d ks e' Nothing -> Null -- traverse array elements with additional keys evalKeyPath d ks@(Key key:_) (Array v) = let vs = V.toList v in String . mconcat . intersperse d $ map (evalToText d ks) vs evalKeyPath _ ((Index _):_) _ = Null evalKeyPath _ _ _ = Null valToBuilder :: Value -> B.Builder valToBuilder (String x) = B.fromText x valToBuilder Null = B.fromText "null" valToBuilder (Bool True) = B.fromText "t" valToBuilder (Bool False) = B.fromText "f" valToBuilder (Number x) = case floatingOrInteger x of Left float -> B.realFloat float Right int -> B.decimal int valToBuilder (Object _) = B.fromText "[Object]" valToText :: Value -> Text valToText (String x) = x valToText Null = "null" valToText (Bool True) = "t" valToText (Bool False) = "f" valToText (Number x) = case floatingOrInteger x of Left float -> T.pack . show $ float Right int -> T.pack . show $ int valToText (Object _) = "[Object]"