{-# LANGUAGE OverloadedStrings, CPP #-}
module Network.MPD.Util (
parseDate, parseIso8601, formatIso8601, parseNum, parseFrac,
parseBool, showBool, breakChar, parseTriple,
toAssoc, toAssocList, splitGroups, read
) where
import Control.Arrow
import Data.Time.Format (ParseTime, parseTime, FormatTime, formatTime)
#if MIN_VERSION_time(1,5,0)
import Data.Time.Format (defaultTimeLocale)
#else
import System.Locale (defaultTimeLocale)
#endif
import qualified Prelude
import Prelude hiding (break, take, drop, dropWhile, read)
import Data.ByteString.Char8 (break, drop, dropWhile, ByteString)
import qualified Data.ByteString.UTF8 as UTF8
import Data.String
import Control.Applicative
import qualified Data.Attoparsec.ByteString.Char8 as A
read :: Read a => ByteString -> a
read = Prelude.read . UTF8.toString
breakChar :: Char -> ByteString -> (ByteString, ByteString)
breakChar c = second (drop 1) . break (== c)
parseDate :: ByteString -> Maybe Int
parseDate = parseMaybe p
where
p = A.decimal <* A.skipMany (A.char '-' <|> A.digit)
parseIso8601 :: (ParseTime t) => ByteString -> Maybe t
parseIso8601 = parseTime defaultTimeLocale iso8601Format . UTF8.toString
formatIso8601 :: FormatTime t => t -> String
formatIso8601 = formatTime defaultTimeLocale iso8601Format
iso8601Format :: String
iso8601Format = "%FT%TZ"
parseNum :: (Read a, Integral a) => ByteString -> Maybe a
parseNum = parseMaybe (A.signed A.decimal)
parseFrac :: (Fractional a, Read a) => ByteString -> Maybe a
parseFrac = parseMaybe p
where
p = A.string "nan" *> pure (Prelude.read "NaN")
<|> A.string "inf" *> pure (Prelude.read "Infinity")
<|> A.string "-inf" *> pure (Prelude.read "-Infinity")
<|> A.rational
showBool :: IsString a => Bool -> a
showBool x = if x then "1" else "0"
parseBool :: ByteString -> Maybe Bool
parseBool = parseMaybe p
where
p = A.char '1' *> pure True <|> A.char '0' *> pure False
parseTriple :: Char -> (ByteString -> Maybe a) -> ByteString -> Maybe (a, a, a)
parseTriple c f s = let (u, u') = breakChar c s
(v, w) = breakChar c u' in
case (f u, f v, f w) of
(Just a, Just b, Just c') -> Just (a, b, c')
_ -> Nothing
toAssoc :: ByteString -> (ByteString, ByteString)
toAssoc = second (dropWhile (== ' ') . drop 1) . break (== ':')
toAssocList :: [ByteString] -> [(ByteString, ByteString)]
toAssocList = map toAssoc
splitGroups :: [ByteString] -> [(ByteString, ByteString)] -> [[(ByteString, ByteString)]]
splitGroups groupHeads = go
where
go [] = []
go (x:xs) =
let
(ys, zs) = Prelude.break isGroupHead xs
in
(x:ys) : go zs
isGroupHead = (`elem` groupHeads) . fst
parseMaybe :: A.Parser a -> ByteString -> Maybe a
parseMaybe p s = either (const Nothing) Just $ A.parseOnly (p <* A.endOfInput) s