module Data.Yaml.YamlLight
(
YamlLight(..)
, parseYaml, parseYamlFile, parseYamlBytes
, fromYamlNode, lookupYL, lookupYLWith
, combineSequencedMaps, combineMappedSequences, getTerminalsKeys
, unSeq, unMap, unStr
) where
import Control.Applicative
import Data.List
import Data.Maybe
import Control.Arrow
import qualified Data.Yaml.Syck as Syck
import qualified Data.Map as Map
import qualified Data.ByteString as ByteString
data YamlLight = YMap (Map.Map YamlLight YamlLight)
| YSeq [YamlLight]
| YStr ByteString.ByteString
| YNil
deriving (Show, Ord, Eq)
convert :: (a -> Syck.YamlNode) -> (a -> YamlLight)
convert f = fromYamlNode . f
convertIO :: (a -> IO Syck.YamlNode) -> (a -> IO YamlLight)
convertIO f yn = fromYamlNode <$> f yn
parseYaml :: String -> IO YamlLight
parseYaml = convertIO Syck.parseYaml
parseYamlFile :: String -> IO YamlLight
parseYamlFile = convertIO Syck.parseYamlFile
parseYamlBytes :: ByteString.ByteString -> IO YamlLight
parseYamlBytes = convertIO Syck.parseYamlBytes
fromYamlNode :: Syck.YamlNode -> YamlLight
fromYamlNode = yamlElemToLight . Syck.n_elem
yamlElemToLight :: Syck.YamlElem -> YamlLight
yamlElemToLight (Syck.EMap ms) = YMap . Map.fromList . map (\(a,b) -> (fromYamlNode a, fromYamlNode b)) $ ms
yamlElemToLight (Syck.ESeq s) = YSeq $ map fromYamlNode s
yamlElemToLight (Syck.EStr buf) = YStr buf
yamlElemToLight (Syck.ENil) = YNil
lookupYL :: YamlLight -> YamlLight -> Maybe YamlLight
lookupYL key (YMap m) = Map.lookup key m
lookupYL _ _ = Nothing
lookupYLWith :: (YamlLight -> Bool) -> YamlLight -> Maybe YamlLight
lookupYLWith p (YMap m) = snd <$> (find (p . fst) $ Map.toList m)
lookupYLWith _ _ = Nothing
combineSequencedMaps :: YamlLight -> Maybe [(YamlLight, YamlLight)]
combineSequencedMaps (YSeq ys) = Just . concatMap Map.assocs . catMaybes $ map unMap ys
combineSequencedMaps _ = Nothing
combineMappedSequences :: YamlLight -> Maybe [(YamlLight, YamlLight)]
combineMappedSequences (YMap m) = Just . concatMap flattenTags . removeSndMaybes $ mapThenList unSeq m
combineMappedSequences _ = Nothing
mapThenList :: (b -> Maybe [c]) -> Map.Map a b -> [(a, Maybe [c])]
mapThenList f m = Map.toList $ Map.map f m
removeSndMaybes :: [(a,Maybe [b])] -> [(a,[b])]
removeSndMaybes = map (second fromJust) . filter (isJust . snd)
flattenTags :: (a,[b]) -> [(a,b)]
flattenTags (a,bs) = map ((,) a) bs
getTerminalsKeys :: YamlLight -> [(ByteString.ByteString,[YamlLight])]
getTerminalsKeys = getTerminalsKeys' []
getTerminalsKeys' :: [YamlLight] -> YamlLight -> [(ByteString.ByteString,[YamlLight])]
getTerminalsKeys' hist (YStr s) = [(s,hist)]
getTerminalsKeys' hist (YSeq s) = concatMap (getTerminalsKeys' hist) s
getTerminalsKeys' hist (YMap m) = concat . Map.elems $ Map.mapWithKey (\k -> getTerminalsKeys' (k : hist)) m
getTerminalsKeys' _ _ = []
unSeq :: YamlLight -> Maybe [YamlLight]
unSeq (YSeq s) = Just s
unSeq _ = Nothing
unMap :: YamlLight -> Maybe (Map.Map YamlLight YamlLight)
unMap (YMap m) = Just m
unMap _ = Nothing
unStr :: YamlLight -> Maybe ByteString.ByteString
unStr (YStr s) = Just s
unStr _ = Nothing
performTest :: Show a => (YamlLight -> a) -> String -> IO ()
performTest f s = parseYaml s >>= print . f
cSeqMap1 = "[{key1: val1, key2: val2}, {key3: val3}]"
cMapSeq1 = "{key1: [val1, val2, val3], key2: [val4, val5]}"
gtKeys1 = " [{key1: \
\ { key1_1: [str1, str2] \
\ , key1_2: [str2, str3] }} \
\ , {key2: [str4]} \
\ , str5 \
\ ] "
gtKeys2 = "[a, b, c]"
gtKeys3 = "a: {b: [c, {d: [e, f]}]}"
gtKeys4 = "[{a: {b: [c1, c2], d: [e1, e2]}, f: [g]}, h]"
testCombineSequencedMaps1 = performTest combineSequencedMaps cSeqMap1
testCombineMappedSequences1 = performTest combineMappedSequences cMapSeq1
testGetTerminalsKeys1 = performTest getTerminalsKeys gtKeys1
testGetTerminalsKeys2 = performTest getTerminalsKeys gtKeys2
testGetTerminalsKeys3 = performTest getTerminalsKeys gtKeys3
testGetTerminalsKeys4 = performTest getTerminalsKeys gtKeys4