aeson-1.4.2.0/0000755000000000000000000000000000000000000011110 5ustar0000000000000000aeson-1.4.2.0/Data/0000755000000000000000000000000000000000000011761 5ustar0000000000000000aeson-1.4.2.0/Data/Aeson.hs0000644000000000000000000004027200000000000013367 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} -- | -- Module: Data.Aeson -- Copyright: (c) 2011-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Types and functions for working efficiently with JSON data. -- -- (A note on naming: in Greek mythology, Aeson was the father of Jason.) module Data.Aeson ( -- * How to use this library -- $use -- ** Writing instances by hand -- $manual -- ** Working with the AST -- $ast -- ** Decoding to a Haskell value -- $haskell -- ** Decoding a mixed-type object -- $mixed -- * Encoding and decoding -- $encoding_and_decoding -- ** Direct encoding -- $encoding decode , decode' , eitherDecode , eitherDecode' , encode , encodeFile -- ** Variants for strict bytestrings , decodeStrict , decodeFileStrict , decodeStrict' , decodeFileStrict' , eitherDecodeStrict , eitherDecodeFileStrict , eitherDecodeStrict' , eitherDecodeFileStrict' -- * Core JSON types , Value(..) , Encoding , fromEncoding , Array , Object -- * Convenience types , DotNetTime(..) -- * Type conversion , FromJSON(..) , Result(..) , fromJSON , ToJSON(..) , KeyValue(..) -- ** Keys for maps , ToJSONKey(..) , ToJSONKeyFunction(..) , FromJSONKey(..) , FromJSONKeyFunction(..) -- ** Liftings to unary and binary type constructors , FromJSON1(..) , parseJSON1 , FromJSON2(..) , parseJSON2 , ToJSON1(..) , toJSON1 , toEncoding1 , ToJSON2(..) , toJSON2 , toEncoding2 -- ** Generic JSON classes and options , GFromJSON(..) , FromArgs(..) , GToJSON , GToEncoding , ToArgs(..) , Zero , One , genericToJSON , genericLiftToJSON , genericToEncoding , genericLiftToEncoding , genericParseJSON , genericLiftParseJSON -- ** Generic and TH encoding configuration , Options , defaultOptions -- *** Options fields -- $optionsFields , fieldLabelModifier , constructorTagModifier , allNullaryToStringTag , omitNothingFields , sumEncoding , unwrapUnaryRecords , tagSingleConstructors -- *** Options utilities , SumEncoding(..) , camelTo2 , defaultTaggedObject -- * Inspecting @'Value's@ , withObject , withText , withArray , withScientific , withBool , withEmbeddedJSON -- * Constructors and accessors , Series , pairs , foldable , (.:) , (.:?) , (.:!) , (.!=) , object -- * Parsing , json , json' ) where import Prelude.Compat import Data.Aeson.Types.FromJSON (ifromJSON) import Data.Aeson.Encoding (encodingToLazyByteString) import Data.Aeson.Parser.Internal (decodeWith, decodeStrictWith, eitherDecodeWith, eitherDecodeStrictWith, jsonEOF, json, jsonEOF', json') import Data.Aeson.Types import Data.Aeson.Types.Internal (JSONPath, formatError) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L -- | Efficiently serialize a JSON value as a lazy 'L.ByteString'. -- -- This is implemented in terms of the 'ToJSON' class's 'toEncoding' method. encode :: (ToJSON a) => a -> L.ByteString encode = encodingToLazyByteString . toEncoding -- | Efficiently serialize a JSON value as a lazy 'L.ByteString' and write it to a file. encodeFile :: (ToJSON a) => FilePath -> a -> IO () encodeFile fp = L.writeFile fp . encode -- | Efficiently deserialize a JSON value from a lazy 'L.ByteString'. -- If this fails due to incomplete or invalid input, 'Nothing' is -- returned. -- -- The input must consist solely of a JSON document, with no trailing -- data except for whitespace. -- -- This function parses immediately, but defers conversion. See -- 'json' for details. decode :: (FromJSON a) => L.ByteString -> Maybe a decode = decodeWith jsonEOF fromJSON {-# INLINE decode #-} -- | Efficiently deserialize a JSON value from a strict 'B.ByteString'. -- If this fails due to incomplete or invalid input, 'Nothing' is -- returned. -- -- The input must consist solely of a JSON document, with no trailing -- data except for whitespace. -- -- This function parses immediately, but defers conversion. See -- 'json' for details. decodeStrict :: (FromJSON a) => B.ByteString -> Maybe a decodeStrict = decodeStrictWith jsonEOF fromJSON {-# INLINE decodeStrict #-} -- | Efficiently deserialize a JSON value from a file. -- If this fails due to incomplete or invalid input, 'Nothing' is -- returned. -- -- The input file's content must consist solely of a JSON document, -- with no trailing data except for whitespace. -- -- This function parses immediately, but defers conversion. See -- 'json' for details. decodeFileStrict :: (FromJSON a) => FilePath -> IO (Maybe a) decodeFileStrict = fmap decodeStrict . B.readFile -- | Efficiently deserialize a JSON value from a lazy 'L.ByteString'. -- If this fails due to incomplete or invalid input, 'Nothing' is -- returned. -- -- The input must consist solely of a JSON document, with no trailing -- data except for whitespace. -- -- This function parses and performs conversion immediately. See -- 'json'' for details. decode' :: (FromJSON a) => L.ByteString -> Maybe a decode' = decodeWith jsonEOF' fromJSON {-# INLINE decode' #-} -- | Efficiently deserialize a JSON value from a strict 'B.ByteString'. -- If this fails due to incomplete or invalid input, 'Nothing' is -- returned. -- -- The input must consist solely of a JSON document, with no trailing -- data except for whitespace. -- -- This function parses and performs conversion immediately. See -- 'json'' for details. decodeStrict' :: (FromJSON a) => B.ByteString -> Maybe a decodeStrict' = decodeStrictWith jsonEOF' fromJSON {-# INLINE decodeStrict' #-} -- | Efficiently deserialize a JSON value from a file. -- If this fails due to incomplete or invalid input, 'Nothing' is -- returned. -- -- The input file's content must consist solely of a JSON document, -- with no trailing data except for whitespace. -- -- This function parses and performs conversion immediately. See -- 'json'' for details. decodeFileStrict' :: (FromJSON a) => FilePath -> IO (Maybe a) decodeFileStrict' = fmap decodeStrict' . B.readFile eitherFormatError :: Either (JSONPath, String) a -> Either String a eitherFormatError = either (Left . uncurry formatError) Right {-# INLINE eitherFormatError #-} -- | Like 'decode' but returns an error message when decoding fails. eitherDecode :: (FromJSON a) => L.ByteString -> Either String a eitherDecode = eitherFormatError . eitherDecodeWith jsonEOF ifromJSON {-# INLINE eitherDecode #-} -- | Like 'decodeStrict' but returns an error message when decoding fails. eitherDecodeStrict :: (FromJSON a) => B.ByteString -> Either String a eitherDecodeStrict = eitherFormatError . eitherDecodeStrictWith jsonEOF ifromJSON {-# INLINE eitherDecodeStrict #-} -- | Like 'decodeFileStrict' but returns an error message when decoding fails. eitherDecodeFileStrict :: (FromJSON a) => FilePath -> IO (Either String a) eitherDecodeFileStrict = fmap (eitherFormatError . eitherDecodeStrictWith jsonEOF ifromJSON) . B.readFile {-# INLINE eitherDecodeFileStrict #-} -- | Like 'decode'' but returns an error message when decoding fails. eitherDecode' :: (FromJSON a) => L.ByteString -> Either String a eitherDecode' = eitherFormatError . eitherDecodeWith jsonEOF' ifromJSON {-# INLINE eitherDecode' #-} -- | Like 'decodeStrict'' but returns an error message when decoding fails. eitherDecodeStrict' :: (FromJSON a) => B.ByteString -> Either String a eitherDecodeStrict' = eitherFormatError . eitherDecodeStrictWith jsonEOF' ifromJSON {-# INLINE eitherDecodeStrict' #-} -- | Like 'decodeFileStrict'' but returns an error message when decoding fails. eitherDecodeFileStrict' :: (FromJSON a) => FilePath -> IO (Either String a) eitherDecodeFileStrict' = fmap (eitherFormatError . eitherDecodeStrictWith jsonEOF' ifromJSON) . B.readFile {-# INLINE eitherDecodeFileStrict' #-} -- $use -- -- This section contains basic information on the different ways to -- work with data using this library. These range from simple but -- inflexible, to complex but flexible. -- -- The most common way to use the library is to define a data type, -- corresponding to some JSON data you want to work with, and then -- write either a 'FromJSON' instance, a to 'ToJSON' instance, or both -- for that type. -- -- For example, given this JSON data: -- -- > { "name": "Joe", "age": 12 } -- -- we create a matching data type: -- -- > {-# LANGUAGE DeriveGeneric #-} -- > -- > import GHC.Generics -- > -- > data Person = Person { -- > name :: Text -- > , age :: Int -- > } deriving (Generic, Show) -- -- The @LANGUAGE@ pragma and 'Generic' instance let us write empty -- 'FromJSON' and 'ToJSON' instances for which the compiler will -- generate sensible default implementations. -- -- @ -- instance 'ToJSON' Person where -- \-- No need to provide a 'toJSON' implementation. -- -- \-- For efficiency, we write a simple 'toEncoding' implementation, as -- \-- the default version uses 'toJSON'. -- 'toEncoding' = 'genericToEncoding' 'defaultOptions' -- -- instance 'FromJSON' Person -- \-- No need to provide a 'parseJSON' implementation. -- @ -- -- We can now encode a value like so: -- -- > >>> encode (Person {name = "Joe", age = 12}) -- > "{\"name\":\"Joe\",\"age\":12}" -- $manual -- -- When necessary, we can write 'ToJSON' and 'FromJSON' instances by -- hand. This is valuable when the JSON-on-the-wire and Haskell data -- are different or otherwise need some more carefully managed -- translation. Let's revisit our JSON data: -- -- > { "name": "Joe", "age": 12 } -- -- We once again create a matching data type, without bothering to add -- a 'Generic' instance this time: -- -- > data Person = Person { -- > name :: Text -- > , age :: Int -- > } deriving Show -- -- To decode data, we need to define a 'FromJSON' instance: -- -- > {-# LANGUAGE OverloadedStrings #-} -- > -- > instance FromJSON Person where -- > parseJSON = withObject "Person" $ \v -> Person -- > <$> v .: "name" -- > <*> v .: "age" -- -- We can now parse the JSON data like so: -- -- > >>> decode "{\"name\":\"Joe\",\"age\":12}" :: Maybe Person -- > Just (Person {name = "Joe", age = 12}) -- -- To encode data, we need to define a 'ToJSON' instance. Let's begin -- with an instance written entirely by hand. -- -- @ -- instance ToJSON Person where -- \-- this generates a 'Value' -- 'toJSON' (Person name age) = -- 'object' [\"name\" '.=' name, \"age\" '.=' age] -- -- \-- this encodes directly to a bytestring Builder -- 'toEncoding' (Person name age) = -- 'pairs' (\"name\" '.=' 'name' '<>' \"age\" '.=' age) -- @ -- -- We can now encode a value like so: -- -- > >>> encode (Person {name = "Joe", age = 12}) -- > "{\"name\":\"Joe\",\"age\":12}" -- -- There are predefined 'FromJSON' and 'ToJSON' instances for many -- types. Here's an example using lists and 'Int's: -- -- > >>> decode "[1,2,3]" :: Maybe [Int] -- > Just [1,2,3] -- -- And here's an example using the 'Data.Map.Map' type to get a map of -- 'Int's. -- -- > >>> decode "{\"foo\":1,\"bar\":2}" :: Maybe (Map String Int) -- > Just (fromList [("bar",2),("foo",1)]) -- While the notes below focus on decoding, you can apply almost the -- same techniques to /encoding/ data. (The main difference is that -- encoding always succeeds, but decoding has to handle the -- possibility of failure, where an input doesn't match our -- expectations.) -- -- See the documentation of 'FromJSON' and 'ToJSON' for some examples -- of how you can automatically derive instances in many common -- circumstances. -- $ast -- -- Sometimes you want to work with JSON data directly, without first -- converting it to a custom data type. This can be useful if you want -- to e.g. convert JSON data to YAML data, without knowing what the -- contents of the original JSON data was. The 'Value' type, which is -- an instance of 'FromJSON', is used to represent an arbitrary JSON -- AST (abstract syntax tree). Example usage: -- -- > >>> decode "{\"foo\": 123}" :: Maybe Value -- > Just (Object (fromList [("foo",Number 123)])) -- -- > >>> decode "{\"foo\": [\"abc\",\"def\"]}" :: Maybe Value -- > Just (Object (fromList [("foo",Array (fromList [String "abc",String "def"]))])) -- -- Once you have a 'Value' you can write functions to traverse it and -- make arbitrary transformations. -- $haskell -- -- We can decode to any instance of 'FromJSON': -- -- > λ> decode "[1,2,3]" :: Maybe [Int] -- > Just [1,2,3] -- -- Alternatively, there are instances for standard data types, so you -- can use them directly. For example, use the 'Data.Map.Map' type to -- get a map of 'Int's. -- -- > λ> import Data.Map -- > λ> decode "{\"foo\":1,\"bar\":2}" :: Maybe (Map String Int) -- > Just (fromList [("bar",2),("foo",1)]) -- $mixed -- -- The above approach with maps of course will not work for mixed-type -- objects that don't follow a strict schema, but there are a couple -- of approaches available for these. -- -- The 'Object' type contains JSON objects: -- -- > λ> decode "{\"name\":\"Dave\",\"age\":2}" :: Maybe Object -- > Just (fromList [("name",String "Dave"),("age",Number 2)]) -- -- You can extract values from it with a parser using 'parse', -- 'parseEither' or, in this example, 'parseMaybe': -- -- > λ> do result <- decode "{\"name\":\"Dave\",\"age\":2}" -- > flip parseMaybe result $ \obj -> do -- > age <- obj .: "age" -- > name <- obj .: "name" -- > return (name ++ ": " ++ show (age*2)) -- > -- > Just "Dave: 4" -- -- Considering that any type that implements 'FromJSON' can be used -- here, this is quite a powerful way to parse JSON. See the -- documentation in 'FromJSON' for how to implement this class for -- your own data types. -- -- The downside is that you have to write the parser yourself; the -- upside is that you have complete control over the way the JSON is -- parsed. -- $encoding_and_decoding -- -- Decoding is a two-step process. -- -- * When decoding a value, the process is reversed: the bytes are -- converted to a 'Value', then the 'FromJSON' class is used to -- convert to the desired type. -- -- There are two ways to encode a value. -- -- * Convert to a 'Value' using 'toJSON', then possibly further -- encode. This was the only method available in aeson 0.9 and -- earlier. -- -- * Directly encode (to what will become a 'L.ByteString') using -- 'toEncoding'. This is much more efficient (about 3x faster, and -- less memory intensive besides), but is only available in aeson -- 0.10 and newer. -- -- For convenience, the 'encode' and 'decode' functions combine both -- steps. -- $encoding -- -- In older versions of this library, encoding a Haskell value -- involved converting to an intermediate 'Value', then encoding that. -- -- A \"direct\" encoder converts straight from a source Haskell value -- to a 'BL.ByteString' without constructing an intermediate 'Value'. -- This approach is faster than 'toJSON', and allocates less memory. -- The 'toEncoding' method makes it possible to implement direct -- encoding with low memory overhead. -- -- To complicate matters, the default implementation of 'toEncoding' -- uses 'toJSON'. Why? The 'toEncoding' method was added to this -- library much more recently than 'toJSON'. Using 'toJSON' ensures -- that packages written against older versions of this library will -- compile and produce correct output, but they will not see any -- speedup from direct encoding. -- -- To write a minimal implementation of direct encoding, your type -- must implement GHC's 'Generic' class, and your code should look -- like this: -- -- @ -- 'toEncoding' = 'genericToEncoding' 'defaultOptions' -- @ -- -- What if you have more elaborate encoding needs? For example, -- perhaps you need to change the names of object keys, omit parts of -- a value. -- -- To encode to a JSON \"object\", use the 'pairs' function. -- -- @ -- 'toEncoding' (Person name age) = -- 'pairs' (\"name\" '.=' 'name' '<>' \"age\" '.=' age) -- @ -- -- Any container type that implements 'Foldable' can be encoded to a -- JSON \"array\" using 'foldable'. -- -- > > import Data.Sequence as Seq -- > > encode (Seq.fromList [1,2,3]) -- > "[1,2,3]" aeson-1.4.2.0/Data/Aeson/0000755000000000000000000000000000000000000013026 5ustar0000000000000000aeson-1.4.2.0/Data/Aeson/Compat.hs0000644000000000000000000000047400000000000014612 0ustar0000000000000000{-# LANGUAGE CPP #-} module Data.Aeson.Compat ( fromStrict ) where import qualified Data.ByteString as S import qualified Data.ByteString.Lazy as L fromStrict :: S.ByteString -> L.ByteString #if MIN_VERSION_bytestring(0, 9, 2) fromStrict = L.fromChunks . (:[]) #else fromStrict = L.fromStrict #endif aeson-1.4.2.0/Data/Aeson/Encode.hs0000644000000000000000000000166200000000000014564 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} -- | -- Module: Data.Aeson.Encode -- Copyright: (c) 2012-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- This module is left to supply limited backwards-compatibility. module Data.Aeson.Encode {-# DEPRECATED "Use Data.Aeson or Data.Aeson.Text instead" #-} ( encode , encodeToTextBuilder ) where import Data.ByteString.Lazy (ByteString) import Data.Text.Lazy.Builder (Builder) import qualified Data.Aeson as A import qualified Data.Aeson.Text as A encode :: A.ToJSON a => a -> ByteString encode = A.encode {-# DEPRECATED encode "Use encode from Data.Aeson" #-} encodeToTextBuilder :: A.Value -> Builder encodeToTextBuilder = A.encodeToTextBuilder {-# DEPRECATED encodeToTextBuilder "Use encodeTotextBuilder from Data.Aeson.Text" #-} aeson-1.4.2.0/Data/Aeson/Encoding.hs0000644000000000000000000000227100000000000015112 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} -- | -- -- Functions in this module return well-formed 'Encoding''. -- Polymorphic variants, which return @'Encoding' a@, return a textual JSON -- value, so it can be used as both @'Encoding'' 'Text'@ and @'Encoding' = 'Encoding'' 'Value'@. module Data.Aeson.Encoding ( -- * Encoding Encoding , Encoding' , encodingToLazyByteString , fromEncoding , unsafeToEncoding , Series , pairs , pair , pairStr , pair' -- * Predicates , nullEncoding -- * Encoding constructors , emptyArray_ , emptyObject_ , text , lazyText , string , list , dict , null_ , bool -- ** Decimal numbers , int8, int16, int32, int64, int , word8, word16, word32, word64, word , integer, float, double, scientific -- ** Decimal numbers as Text , int8Text, int16Text, int32Text, int64Text, intText , word8Text, word16Text, word32Text, word64Text, wordText , integerText, floatText, doubleText, scientificText -- ** Time , day , localTime , utcTime , timeOfDay , zonedTime -- ** value , value ) where import Data.Aeson.Encoding.Internal aeson-1.4.2.0/Data/Aeson/Encoding/0000755000000000000000000000000000000000000014554 5ustar0000000000000000aeson-1.4.2.0/Data/Aeson/Encoding/Builder.hs0000644000000000000000000002061300000000000016500 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TupleSections #-} -- | -- Module: Data.Aeson.Encoding.Builder -- Copyright: (c) 2011 MailRank, Inc. -- (c) 2013 Simon Meier -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Efficiently serialize a JSON value using the UTF-8 encoding. module Data.Aeson.Encoding.Builder ( encodeToBuilder , null_ , bool , array , emptyArray_ , emptyObject_ , object , text , string , unquoted , quote , scientific , day , localTime , utcTime , timeOfDay , zonedTime , ascii2 , ascii4 , ascii5 ) where import Prelude.Compat import Data.Aeson.Internal.Time import Data.Aeson.Types.Internal (Value (..)) import Data.ByteString.Builder as B import Data.ByteString.Builder.Prim as BP import Data.ByteString.Builder.Scientific (scientificBuilder) import Data.Char (chr, ord) import Data.Semigroup ((<>)) import Data.Scientific (Scientific, base10Exponent, coefficient) import Data.Text.Encoding (encodeUtf8BuilderEscaped) import Data.Time (UTCTime(..)) import Data.Time.Calendar (Day(..), toGregorian) import Data.Time.LocalTime import Data.Word (Word8) import qualified Data.HashMap.Strict as HMS import qualified Data.Text as T import qualified Data.Vector as V -- | Encode a JSON value to a "Data.ByteString" 'B.Builder'. -- -- Use this function if you are encoding over the wire, or need to -- prepend or append further bytes to the encoded JSON value. encodeToBuilder :: Value -> Builder encodeToBuilder Null = null_ encodeToBuilder (Bool b) = bool b encodeToBuilder (Number n) = scientific n encodeToBuilder (String s) = text s encodeToBuilder (Array v) = array v encodeToBuilder (Object m) = object m -- | Encode a JSON null. null_ :: Builder null_ = BP.primBounded (ascii4 ('n',('u',('l','l')))) () -- | Encode a JSON boolean. bool :: Bool -> Builder bool = BP.primBounded (BP.condB id (ascii4 ('t',('r',('u','e')))) (ascii5 ('f',('a',('l',('s','e')))))) -- | Encode a JSON array. array :: V.Vector Value -> Builder array v | V.null v = emptyArray_ | otherwise = B.char8 '[' <> encodeToBuilder (V.unsafeHead v) <> V.foldr withComma (B.char8 ']') (V.unsafeTail v) where withComma a z = B.char8 ',' <> encodeToBuilder a <> z -- Encode a JSON object. object :: HMS.HashMap T.Text Value -> Builder object m = case HMS.toList m of (x:xs) -> B.char8 '{' <> one x <> foldr withComma (B.char8 '}') xs _ -> emptyObject_ where withComma a z = B.char8 ',' <> one a <> z one (k,v) = text k <> B.char8 ':' <> encodeToBuilder v -- | Encode a JSON string. text :: T.Text -> Builder text t = B.char8 '"' <> unquoted t <> B.char8 '"' -- | Encode a JSON string, without enclosing quotes. unquoted :: T.Text -> Builder unquoted = encodeUtf8BuilderEscaped escapeAscii -- | Add quotes surrounding a builder quote :: Builder -> Builder quote b = B.char8 '"' <> b <> B.char8 '"' -- | Encode a JSON string. string :: String -> Builder string t = B.char8 '"' <> BP.primMapListBounded go t <> B.char8 '"' where go = BP.condB (> '\x7f') BP.charUtf8 (c2w >$< escapeAscii) escapeAscii :: BP.BoundedPrim Word8 escapeAscii = BP.condB (== c2w '\\' ) (ascii2 ('\\','\\')) $ BP.condB (== c2w '\"' ) (ascii2 ('\\','"' )) $ BP.condB (>= c2w '\x20') (BP.liftFixedToBounded BP.word8) $ BP.condB (== c2w '\n' ) (ascii2 ('\\','n' )) $ BP.condB (== c2w '\r' ) (ascii2 ('\\','r' )) $ BP.condB (== c2w '\t' ) (ascii2 ('\\','t' )) $ BP.liftFixedToBounded hexEscape -- fallback for chars < 0x20 where hexEscape :: BP.FixedPrim Word8 hexEscape = (\c -> ('\\', ('u', fromIntegral c))) BP.>$< BP.char8 >*< BP.char8 >*< BP.word16HexFixed {-# INLINE escapeAscii #-} c2w :: Char -> Word8 c2w c = fromIntegral (ord c) -- | Encode a JSON number. scientific :: Scientific -> Builder scientific s | e < 0 || e > 1024 = scientificBuilder s | otherwise = B.integerDec (coefficient s * 10 ^ e) where e = base10Exponent s emptyArray_ :: Builder emptyArray_ = BP.primBounded (ascii2 ('[',']')) () emptyObject_ :: Builder emptyObject_ = BP.primBounded (ascii2 ('{','}')) () ascii2 :: (Char, Char) -> BP.BoundedPrim a ascii2 cs = BP.liftFixedToBounded $ const cs BP.>$< BP.char7 >*< BP.char7 {-# INLINE ascii2 #-} ascii4 :: (Char, (Char, (Char, Char))) -> BP.BoundedPrim a ascii4 cs = BP.liftFixedToBounded $ const cs >$< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 {-# INLINE ascii4 #-} ascii5 :: (Char, (Char, (Char, (Char, Char)))) -> BP.BoundedPrim a ascii5 cs = BP.liftFixedToBounded $ const cs >$< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 {-# INLINE ascii5 #-} ascii6 :: (Char, (Char, (Char, (Char, (Char, Char))))) -> BP.BoundedPrim a ascii6 cs = BP.liftFixedToBounded $ const cs >$< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 {-# INLINE ascii6 #-} ascii8 :: (Char, (Char, (Char, (Char, (Char, (Char, (Char, Char))))))) -> BP.BoundedPrim a ascii8 cs = BP.liftFixedToBounded $ const cs >$< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 >*< BP.char7 {-# INLINE ascii8 #-} day :: Day -> Builder day dd = encodeYear yr <> BP.primBounded (ascii6 ('-',(mh,(ml,('-',(dh,dl)))))) () where (yr,m,d) = toGregorian dd !(T mh ml) = twoDigits m !(T dh dl) = twoDigits d encodeYear y | y >= 1000 = B.integerDec y | y >= 0 = BP.primBounded (ascii4 (padYear y)) () | y >= -999 = BP.primBounded (ascii5 ('-',padYear (- y))) () | otherwise = B.integerDec y padYear y = let (ab,c) = fromIntegral y `quotRem` 10 (a,b) = ab `quotRem` 10 in ('0',(digit a,(digit b,digit c))) {-# INLINE day #-} timeOfDay :: TimeOfDay -> Builder timeOfDay t = timeOfDay64 (toTimeOfDay64 t) {-# INLINE timeOfDay #-} timeOfDay64 :: TimeOfDay64 -> Builder timeOfDay64 (TOD h m s) | frac == 0 = hhmmss -- omit subseconds if 0 | otherwise = hhmmss <> BP.primBounded showFrac frac where hhmmss = BP.primBounded (ascii8 (hh,(hl,(':',(mh,(ml,(':',(sh,sl)))))))) () !(T hh hl) = twoDigits h !(T mh ml) = twoDigits m !(T sh sl) = twoDigits (fromIntegral real) (real,frac) = s `quotRem` pico showFrac = ('.',) >$< (BP.liftFixedToBounded BP.char7 >*< trunc12) trunc12 = (`quotRem` micro) >$< BP.condB (\(_,y) -> y == 0) (fst >$< trunc6) (digits6 >*< trunc6) digits6 = ((`quotRem` milli) . fromIntegral) >$< (digits3 >*< digits3) trunc6 = ((`quotRem` milli) . fromIntegral) >$< BP.condB (\(_,y) -> y == 0) (fst >$< trunc3) (digits3 >*< trunc3) digits3 = (`quotRem` 10) >$< (digits2 >*< digits1) digits2 = (`quotRem` 10) >$< (digits1 >*< digits1) digits1 = BP.liftFixedToBounded (digit >$< BP.char7) trunc3 = BP.condB (== 0) BP.emptyB $ (`quotRem` 100) >$< (digits1 >*< trunc2) trunc2 = BP.condB (== 0) BP.emptyB $ (`quotRem` 10) >$< (digits1 >*< trunc1) trunc1 = BP.condB (== 0) BP.emptyB digits1 pico = 1000000000000 -- number of picoseconds in 1 second micro = 1000000 -- number of microseconds in 1 second milli = 1000 -- number of milliseconds in 1 second timeZone :: TimeZone -> Builder timeZone (TimeZone off _ _) | off == 0 = B.char7 'Z' | otherwise = BP.primBounded (ascii6 (s,(hh,(hl,(':',(mh,ml)))))) () where !s = if off < 0 then '-' else '+' !(T hh hl) = twoDigits h !(T mh ml) = twoDigits m (h,m) = abs off `quotRem` 60 {-# INLINE timeZone #-} dayTime :: Day -> TimeOfDay64 -> Builder dayTime d t = day d <> B.char7 'T' <> timeOfDay64 t {-# INLINE dayTime #-} utcTime :: UTCTime -> B.Builder utcTime (UTCTime d s) = dayTime d (diffTimeOfDay64 s) <> B.char7 'Z' {-# INLINE utcTime #-} localTime :: LocalTime -> Builder localTime (LocalTime d t) = dayTime d (toTimeOfDay64 t) {-# INLINE localTime #-} zonedTime :: ZonedTime -> Builder zonedTime (ZonedTime t z) = localTime t <> timeZone z {-# INLINE zonedTime #-} data T = T {-# UNPACK #-} !Char {-# UNPACK #-} !Char twoDigits :: Int -> T twoDigits a = T (digit hi) (digit lo) where (hi,lo) = a `quotRem` 10 digit :: Int -> Char digit x = chr (x + 48) aeson-1.4.2.0/Data/Aeson/Encoding/Internal.hs0000644000000000000000000002443300000000000016672 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} module Data.Aeson.Encoding.Internal ( -- * Encoding Encoding' (..) , Encoding , encodingToLazyByteString , unsafeToEncoding , retagEncoding , Series (..) , pairs , pair , pairStr , pair' -- * Predicates , nullEncoding -- * Encoding constructors , emptyArray_ , emptyObject_ , wrapObject , wrapArray , null_ , bool , text , lazyText , string , list , dict , tuple , (>*<) , InArray , empty , (><) , econcat -- ** Decimal numbers , int8, int16, int32, int64, int , word8, word16, word32, word64, word , integer, float, double, scientific -- ** Decimal numbers as Text , int8Text, int16Text, int32Text, int64Text, intText , word8Text, word16Text, word32Text, word64Text, wordText , integerText, floatText, doubleText, scientificText -- ** Time , day , localTime , utcTime , timeOfDay , zonedTime -- ** value , value -- ** JSON tokens , comma, colon, openBracket, closeBracket, openCurly, closeCurly ) where import Prelude.Compat import Data.Aeson.Types.Internal (Value) import Data.ByteString.Builder (Builder, char7, toLazyByteString) import Data.Int import Data.Scientific (Scientific) import Data.Semigroup (Semigroup ((<>))) import Data.Text (Text) import Data.Time (Day, LocalTime, TimeOfDay, UTCTime, ZonedTime) import Data.Typeable (Typeable) import Data.Word import qualified Data.Aeson.Encoding.Builder as EB import qualified Data.ByteString.Builder as B import qualified Data.ByteString.Lazy as BSL import qualified Data.Text.Lazy as LT -- | An encoding of a JSON value. -- -- @tag@ represents which kind of JSON the Encoding is encoding to, -- we reuse 'Text' and 'Value' as tags here. newtype Encoding' tag = Encoding { fromEncoding :: Builder -- ^ Acquire the underlying bytestring builder. } deriving (Typeable) -- | Often used synonym for 'Encoding''. type Encoding = Encoding' Value -- | Make Encoding from Builder. -- -- Use with care! You have to make sure that the passed Builder -- is a valid JSON Encoding! unsafeToEncoding :: Builder -> Encoding' a unsafeToEncoding = Encoding encodingToLazyByteString :: Encoding' a -> BSL.ByteString encodingToLazyByteString = toLazyByteString . fromEncoding {-# INLINE encodingToLazyByteString #-} retagEncoding :: Encoding' a -> Encoding' b retagEncoding = Encoding . fromEncoding ------------------------------------------------------------------------------- -- Encoding instances ------------------------------------------------------------------------------- instance Show (Encoding' a) where show (Encoding e) = show (toLazyByteString e) instance Eq (Encoding' a) where Encoding a == Encoding b = toLazyByteString a == toLazyByteString b instance Ord (Encoding' a) where compare (Encoding a) (Encoding b) = compare (toLazyByteString a) (toLazyByteString b) -- | A series of values that, when encoded, should be separated by -- commas. Since 0.11.0.0, the '.=' operator is overloaded to create -- either @(Text, Value)@ or 'Series'. You can use Series when -- encoding directly to a bytestring builder as in the following -- example: -- -- > toEncoding (Person name age) = pairs ("name" .= name <> "age" .= age) data Series = Empty | Value (Encoding' Series) deriving (Typeable) pair :: Text -> Encoding -> Series pair name val = pair' (text name) val {-# INLINE pair #-} pairStr :: String -> Encoding -> Series pairStr name val = pair' (string name) val {-# INLINE pairStr #-} pair' :: Encoding' Text -> Encoding -> Series pair' name val = Value $ retagEncoding $ retagEncoding name >< colon >< val instance Semigroup Series where Empty <> a = a a <> Empty = a Value a <> Value b = Value (a >< comma >< b) instance Monoid Series where mempty = Empty mappend = (<>) nullEncoding :: Encoding' a -> Bool nullEncoding = BSL.null . toLazyByteString . fromEncoding emptyArray_ :: Encoding emptyArray_ = Encoding EB.emptyArray_ emptyObject_ :: Encoding emptyObject_ = Encoding EB.emptyObject_ wrapArray :: Encoding' a -> Encoding wrapArray e = retagEncoding $ openBracket >< e >< closeBracket wrapObject :: Encoding' a -> Encoding wrapObject e = retagEncoding $ openCurly >< e >< closeCurly null_ :: Encoding null_ = Encoding EB.null_ bool :: Bool -> Encoding bool True = Encoding "true" bool False = Encoding "false" -- | Encode a series of key/value pairs, separated by commas. pairs :: Series -> Encoding pairs (Value v) = openCurly >< retagEncoding v >< closeCurly pairs Empty = emptyObject_ {-# INLINE pairs #-} list :: (a -> Encoding) -> [a] -> Encoding list _ [] = emptyArray_ list to' (x:xs) = openBracket >< to' x >< commas xs >< closeBracket where commas = foldr (\v vs -> comma >< to' v >< vs) empty {-# INLINE list #-} -- | Encode as JSON object dict :: (k -> Encoding' Text) -- ^ key encoding -> (v -> Encoding) -- ^ value encoding -> (forall a. (k -> v -> a -> a) -> a -> m -> a) -- ^ @foldrWithKey@ - indexed fold -> m -- ^ container -> Encoding dict encodeKey encodeVal foldrWithKey = pairs . foldrWithKey go mempty where go k v c = Value (encodeKV k v) <> c encodeKV k v = retagEncoding (encodeKey k) >< colon >< retagEncoding (encodeVal v) {-# INLINE dict #-} -- | Type tag for tuples contents, see 'tuple'. data InArray infixr 6 >*< -- | See 'tuple'. (>*<) :: Encoding' a -> Encoding' b -> Encoding' InArray a >*< b = retagEncoding a >< comma >< retagEncoding b {-# INLINE (>*<) #-} empty :: Encoding' a empty = Encoding mempty econcat :: [Encoding' a] -> Encoding' a econcat = foldr (><) empty infixr 6 >< (><) :: Encoding' a -> Encoding' a -> Encoding' a Encoding a >< Encoding b = Encoding (a <> b) {-# INLINE (><) #-} -- | Encode as a tuple. -- -- @ -- toEncoding (X a b c) = tuple $ -- toEncoding a >*< -- toEncoding b >*< -- toEncoding c tuple :: Encoding' InArray -> Encoding tuple b = retagEncoding $ openBracket >< b >< closeBracket {-# INLINE tuple #-} text :: Text -> Encoding' a text = Encoding . EB.text lazyText :: LT.Text -> Encoding' a lazyText t = Encoding $ B.char7 '"' <> LT.foldrChunks (\x xs -> EB.unquoted x <> xs) (B.char7 '"') t string :: String -> Encoding' a string = Encoding . EB.string ------------------------------------------------------------------------------- -- chars ------------------------------------------------------------------------------- comma, colon, openBracket, closeBracket, openCurly, closeCurly :: Encoding' a comma = Encoding $ char7 ',' colon = Encoding $ char7 ':' openBracket = Encoding $ char7 '[' closeBracket = Encoding $ char7 ']' openCurly = Encoding $ char7 '{' closeCurly = Encoding $ char7 '}' ------------------------------------------------------------------------------- -- Decimal numbers ------------------------------------------------------------------------------- int8 :: Int8 -> Encoding int8 = Encoding . B.int8Dec int16 :: Int16 -> Encoding int16 = Encoding . B.int16Dec int32 :: Int32 -> Encoding int32 = Encoding . B.int32Dec int64 :: Int64 -> Encoding int64 = Encoding . B.int64Dec int :: Int -> Encoding int = Encoding . B.intDec word8 :: Word8 -> Encoding word8 = Encoding . B.word8Dec word16 :: Word16 -> Encoding word16 = Encoding . B.word16Dec word32 :: Word32 -> Encoding word32 = Encoding . B.word32Dec word64 :: Word64 -> Encoding word64 = Encoding . B.word64Dec word :: Word -> Encoding word = Encoding . B.wordDec integer :: Integer -> Encoding integer = Encoding . B.integerDec float :: Float -> Encoding float = realFloatToEncoding $ Encoding . B.floatDec double :: Double -> Encoding double = realFloatToEncoding $ Encoding . B.doubleDec scientific :: Scientific -> Encoding scientific = Encoding . EB.scientific realFloatToEncoding :: RealFloat a => (a -> Encoding) -> a -> Encoding realFloatToEncoding e d | isNaN d || isInfinite d = null_ | otherwise = e d {-# INLINE realFloatToEncoding #-} ------------------------------------------------------------------------------- -- Decimal numbers as Text ------------------------------------------------------------------------------- int8Text :: Int8 -> Encoding' a int8Text = Encoding . EB.quote . B.int8Dec int16Text :: Int16 -> Encoding' a int16Text = Encoding . EB.quote . B.int16Dec int32Text :: Int32 -> Encoding' a int32Text = Encoding . EB.quote . B.int32Dec int64Text :: Int64 -> Encoding' a int64Text = Encoding . EB.quote . B.int64Dec intText :: Int -> Encoding' a intText = Encoding . EB.quote . B.intDec word8Text :: Word8 -> Encoding' a word8Text = Encoding . EB.quote . B.word8Dec word16Text :: Word16 -> Encoding' a word16Text = Encoding . EB.quote . B.word16Dec word32Text :: Word32 -> Encoding' a word32Text = Encoding . EB.quote . B.word32Dec word64Text :: Word64 -> Encoding' a word64Text = Encoding . EB.quote . B.word64Dec wordText :: Word -> Encoding' a wordText = Encoding . EB.quote . B.wordDec integerText :: Integer -> Encoding' a integerText = Encoding . EB.quote . B.integerDec floatText :: Float -> Encoding' a floatText = Encoding . EB.quote . B.floatDec doubleText :: Double -> Encoding' a doubleText = Encoding . EB.quote . B.doubleDec scientificText :: Scientific -> Encoding' a scientificText = Encoding . EB.quote . EB.scientific ------------------------------------------------------------------------------- -- time ------------------------------------------------------------------------------- day :: Day -> Encoding' a day = Encoding . EB.quote . EB.day localTime :: LocalTime -> Encoding' a localTime = Encoding . EB.quote . EB.localTime utcTime :: UTCTime -> Encoding' a utcTime = Encoding . EB.quote . EB.utcTime timeOfDay :: TimeOfDay -> Encoding' a timeOfDay = Encoding . EB.quote . EB.timeOfDay zonedTime :: ZonedTime -> Encoding' a zonedTime = Encoding . EB.quote . EB.zonedTime ------------------------------------------------------------------------------- -- Value ------------------------------------------------------------------------------- value :: Value -> Encoding value = Encoding . EB.encodeToBuilder aeson-1.4.2.0/Data/Aeson/Internal.hs0000644000000000000000000000117500000000000015142 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} -- | -- Module: Data.Aeson.Internal -- Copyright: (c) 2015-2016 Bryan O'Sullivan -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Internal types and functions. -- -- __Note__: all declarations in this module are unstable, and prone -- to being changed at any time. module Data.Aeson.Internal ( IResult(..) , JSONPathElement(..) , JSONPath , () , formatError , ifromJSON , iparse ) where import Data.Aeson.Types.Internal import Data.Aeson.Types.FromJSON (ifromJSON) aeson-1.4.2.0/Data/Aeson/Internal/0000755000000000000000000000000000000000000014602 5ustar0000000000000000aeson-1.4.2.0/Data/Aeson/Internal/Functions.hs0000644000000000000000000000235300000000000017111 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} -- | -- Module: Data.Aeson.Functions -- Copyright: (c) 2011-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable module Data.Aeson.Internal.Functions ( mapHashKeyVal , mapKeyVal , mapKey ) where import Prelude.Compat import Data.Hashable (Hashable) import qualified Data.HashMap.Strict as H import qualified Data.Map as M -- | Transform a 'M.Map' into a 'H.HashMap' while transforming the keys. mapHashKeyVal :: (Eq k2, Hashable k2) => (k1 -> k2) -> (v1 -> v2) -> M.Map k1 v1 -> H.HashMap k2 v2 mapHashKeyVal fk kv = M.foldrWithKey (\k v -> H.insert (fk k) (kv v)) H.empty {-# INLINE mapHashKeyVal #-} -- | Transform the keys and values of a 'H.HashMap'. mapKeyVal :: (Eq k2, Hashable k2) => (k1 -> k2) -> (v1 -> v2) -> H.HashMap k1 v1 -> H.HashMap k2 v2 mapKeyVal fk kv = H.foldrWithKey (\k v -> H.insert (fk k) (kv v)) H.empty {-# INLINE mapKeyVal #-} -- | Transform the keys of a 'H.HashMap'. mapKey :: (Eq k2, Hashable k2) => (k1 -> k2) -> H.HashMap k1 v -> H.HashMap k2 v mapKey fk = mapKeyVal fk id {-# INLINE mapKey #-} aeson-1.4.2.0/Data/Aeson/Internal/Time.hs0000644000000000000000000000065100000000000016036 0ustar0000000000000000{-# LANGUAGE CPP #-} -- | -- Module: Data.Aeson.Internal.Time -- Copyright: (c) 2015-2016 Bryan O'Sullivan -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable module Data.Aeson.Internal.Time ( TimeOfDay64(..) , fromPico , toPico , diffTimeOfDay64 , toTimeOfDay64 ) where import Data.Attoparsec.Time.Internal aeson-1.4.2.0/Data/Aeson/Parser.hs0000644000000000000000000000441700000000000014624 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} -- | -- Module: Data.Aeson.Parser -- Copyright: (c) 2012-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Efficiently and correctly parse a JSON string. The string must be -- encoded as UTF-8. -- -- It can be useful to think of parsing as occurring in two phases: -- -- * Identification of the textual boundaries of a JSON value. This -- is always strict, so that an invalid JSON document can be -- rejected as soon as possible. -- -- * Conversion of a JSON value to a Haskell value. This may be -- either immediate (strict) or deferred (lazy); see below for -- details. -- -- The question of whether to choose a lazy or strict parser is -- subtle, but it can have significant performance implications, -- resulting in changes in CPU use and memory footprint of 30% to 50%, -- or occasionally more. Measure the performance of your application -- with each! module Data.Aeson.Parser ( -- * Lazy parsers -- $lazy json , value , jstring , scientific -- * Strict parsers -- $strict , json' , value' -- * Decoding without FromJSON instances , decodeWith , decodeStrictWith , eitherDecodeWith , eitherDecodeStrictWith ) where import Data.Aeson.Parser.Internal (decodeStrictWith, decodeWith, eitherDecodeStrictWith, eitherDecodeWith, json, json', jstring, scientific, value, value') -- $lazy -- -- The 'json' and 'value' parsers decouple identification from -- conversion. Identification occurs immediately (so that an invalid -- JSON document can be rejected as early as possible), but conversion -- to a Haskell value is deferred until that value is needed. -- -- This decoupling can be time-efficient if only a smallish subset of -- elements in a JSON value need to be inspected, since the cost of -- conversion is zero for uninspected elements. The trade off is an -- increase in memory usage, due to allocation of thunks for values -- that have not yet been converted. -- $strict -- -- The 'json'' and 'value'' parsers combine identification with -- conversion. They consume more CPU cycles up front, but have a -- smaller memory footprint. aeson-1.4.2.0/Data/Aeson/Parser/0000755000000000000000000000000000000000000014262 5ustar0000000000000000aeson-1.4.2.0/Data/Aeson/Parser/Internal.hs0000644000000000000000000003225000000000000016374 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} #if MIN_VERSION_ghc_prim(0,3,1) {-# LANGUAGE MagicHash #-} #endif -- | -- Module: Data.Aeson.Parser.Internal -- Copyright: (c) 2011-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Efficiently and correctly parse a JSON string. The string must be -- encoded as UTF-8. module Data.Aeson.Parser.Internal ( -- * Lazy parsers json, jsonEOF , value , jstring , jstring_ , scientific -- * Strict parsers , json', jsonEOF' , value' -- * Helpers , decodeWith , decodeStrictWith , eitherDecodeWith , eitherDecodeStrictWith ) where import Prelude.Compat import Control.Applicative ((<|>)) import Control.Monad (void, when) import Data.Aeson.Types.Internal (IResult(..), JSONPath, Result(..), Value(..)) import Data.Attoparsec.ByteString.Char8 (Parser, char, decimal, endOfInput, isDigit_w8, signed, string) import Data.Scientific (Scientific) import Data.Text (Text) import Data.Vector as Vector (Vector, empty, fromListN, reverse) import qualified Data.Attoparsec.ByteString as A import qualified Data.Attoparsec.Lazy as L import qualified Data.ByteString as B import qualified Data.ByteString.Unsafe as B import qualified Data.ByteString.Lazy as L import qualified Data.HashMap.Strict as H import qualified Data.Scientific as Sci import Data.Aeson.Parser.Unescape (unescapeText) #if MIN_VERSION_ghc_prim(0,3,1) import GHC.Base (Int#, (==#), isTrue#, word2Int#, orI#, andI#) import GHC.Word (Word8(W8#)) import qualified Data.Text.Encoding as TE #endif #define BACKSLASH 92 #define CLOSE_CURLY 125 #define CLOSE_SQUARE 93 #define COMMA 44 #define DOUBLE_QUOTE 34 #define OPEN_CURLY 123 #define OPEN_SQUARE 91 #define C_0 48 #define C_9 57 #define C_A 65 #define C_F 70 #define C_a 97 #define C_f 102 #define C_n 110 #define C_t 116 -- | Parse a top-level JSON value. -- -- The conversion of a parsed value to a Haskell value is deferred -- until the Haskell value is needed. This may improve performance if -- only a subset of the results of conversions are needed, but at a -- cost in thunk allocation. -- -- This function is an alias for 'value'. In aeson 0.8 and earlier, it -- parsed only object or array types, in conformance with the -- now-obsolete RFC 4627. json :: Parser Value json = value -- | Parse a top-level JSON value. -- -- This is a strict version of 'json' which avoids building up thunks -- during parsing; it performs all conversions immediately. Prefer -- this version if most of the JSON data needs to be accessed. -- -- This function is an alias for 'value''. In aeson 0.8 and earlier, it -- parsed only object or array types, in conformance with the -- now-obsolete RFC 4627. json' :: Parser Value json' = value' object_ :: Parser Value object_ = {-# SCC "object_" #-} Object <$> objectValues jstring value object_' :: Parser Value object_' = {-# SCC "object_'" #-} do !vals <- objectValues jstring' value' return (Object vals) where jstring' = do !s <- jstring return s objectValues :: Parser Text -> Parser Value -> Parser (H.HashMap Text Value) objectValues str val = do skipSpace w <- A.peekWord8' if w == CLOSE_CURLY then A.anyWord8 >> return H.empty else loop [] where -- Why use acc pattern here, you may ask? because 'H.fromList' use 'unsafeInsert' -- and it's much faster because it's doing in place update to the 'HashMap'! loop acc = do k <- str <* skipSpace <* char ':' v <- val <* skipSpace ch <- A.satisfy $ \w -> w == COMMA || w == CLOSE_CURLY let acc' = (k, v) : acc if ch == COMMA then skipSpace >> loop acc' else return (H.fromList acc') {-# INLINE objectValues #-} array_ :: Parser Value array_ = {-# SCC "array_" #-} Array <$> arrayValues value array_' :: Parser Value array_' = {-# SCC "array_'" #-} do !vals <- arrayValues value' return (Array vals) arrayValues :: Parser Value -> Parser (Vector Value) arrayValues val = do skipSpace w <- A.peekWord8' if w == CLOSE_SQUARE then A.anyWord8 >> return Vector.empty else loop [] 1 where loop acc !len = do v <- val <* skipSpace ch <- A.satisfy $ \w -> w == COMMA || w == CLOSE_SQUARE if ch == COMMA then skipSpace >> loop (v:acc) (len+1) else return (Vector.reverse (Vector.fromListN len (v:acc))) {-# INLINE arrayValues #-} -- | Parse any JSON value. You should usually 'json' in preference to -- this function, as this function relaxes the object-or-array -- requirement of RFC 4627. -- -- In particular, be careful in using this function if you think your -- code might interoperate with Javascript. A naïve Javascript -- library that parses JSON data using @eval@ is vulnerable to attack -- unless the encoded data represents an object or an array. JSON -- implementations in other languages conform to that same restriction -- to preserve interoperability and security. value :: Parser Value value = do skipSpace w <- A.peekWord8' case w of DOUBLE_QUOTE -> A.anyWord8 *> (String <$> jstring_) OPEN_CURLY -> A.anyWord8 *> object_ OPEN_SQUARE -> A.anyWord8 *> array_ C_f -> string "false" *> pure (Bool False) C_t -> string "true" *> pure (Bool True) C_n -> string "null" *> pure Null _ | w >= 48 && w <= 57 || w == 45 -> Number <$> scientific | otherwise -> fail "not a valid json value" -- | Strict version of 'value'. See also 'json''. value' :: Parser Value value' = do skipSpace w <- A.peekWord8' case w of DOUBLE_QUOTE -> do !s <- A.anyWord8 *> jstring_ return (String s) OPEN_CURLY -> A.anyWord8 *> object_' OPEN_SQUARE -> A.anyWord8 *> array_' C_f -> string "false" *> pure (Bool False) C_t -> string "true" *> pure (Bool True) C_n -> string "null" *> pure Null _ | w >= 48 && w <= 57 || w == 45 -> do !n <- scientific return (Number n) | otherwise -> fail "not a valid json value" -- | Parse a quoted JSON string. jstring :: Parser Text jstring = A.word8 DOUBLE_QUOTE *> jstring_ -- | Parse a string without a leading quote. jstring_ :: Parser Text {-# INLINE jstring_ #-} jstring_ = {-# SCC "jstring_" #-} do #if MIN_VERSION_ghc_prim(0,3,1) (s, S _ escaped) <- A.runScanner startState go <* A.anyWord8 -- We escape only if there are -- non-ascii (over 7bit) characters or backslash present. -- -- Note: if/when text will have fast ascii -> text conversion -- (e.g. uses utf8 encoding) we can have further speedup. if isTrue# escaped then case unescapeText s of Right r -> return r Left err -> fail $ show err else return (TE.decodeUtf8 s) where startState = S 0# 0# go (S skip escaped) (W8# c) | isTrue# skip = Just (S 0# escaped') | isTrue# (w ==# 34#) = Nothing -- double quote | otherwise = Just (S skip' escaped') where w = word2Int# c skip' = w ==# 92# -- backslash escaped' = escaped `orI#` (w `andI#` 0x80# ==# 0x80#) -- c >= 0x80 `orI#` skip' `orI#` (w `andI#` 0x1f# ==# w) -- c < 0x20 data S = S Int# Int# #else s <- A.scan startState go <* A.anyWord8 case unescapeText s of Right r -> return r Left err -> fail $ show err where startState = False go a c | a = Just False | c == DOUBLE_QUOTE = Nothing | otherwise = let a' = c == backslash in Just a' where backslash = BACKSLASH #endif decodeWith :: Parser Value -> (Value -> Result a) -> L.ByteString -> Maybe a decodeWith p to s = case L.parse p s of L.Done _ v -> case to v of Success a -> Just a _ -> Nothing _ -> Nothing {-# INLINE decodeWith #-} decodeStrictWith :: Parser Value -> (Value -> Result a) -> B.ByteString -> Maybe a decodeStrictWith p to s = case either Error to (A.parseOnly p s) of Success a -> Just a _ -> Nothing {-# INLINE decodeStrictWith #-} eitherDecodeWith :: Parser Value -> (Value -> IResult a) -> L.ByteString -> Either (JSONPath, String) a eitherDecodeWith p to s = case L.parse p s of L.Done _ v -> case to v of ISuccess a -> Right a IError path msg -> Left (path, msg) L.Fail _ _ msg -> Left ([], msg) {-# INLINE eitherDecodeWith #-} eitherDecodeStrictWith :: Parser Value -> (Value -> IResult a) -> B.ByteString -> Either (JSONPath, String) a eitherDecodeStrictWith p to s = case either (IError []) to (A.parseOnly p s) of ISuccess a -> Right a IError path msg -> Left (path, msg) {-# INLINE eitherDecodeStrictWith #-} -- $lazy -- -- The 'json' and 'value' parsers decouple identification from -- conversion. Identification occurs immediately (so that an invalid -- JSON document can be rejected as early as possible), but conversion -- to a Haskell value is deferred until that value is needed. -- -- This decoupling can be time-efficient if only a smallish subset of -- elements in a JSON value need to be inspected, since the cost of -- conversion is zero for uninspected elements. The trade off is an -- increase in memory usage, due to allocation of thunks for values -- that have not yet been converted. -- $strict -- -- The 'json'' and 'value'' parsers combine identification with -- conversion. They consume more CPU cycles up front, but have a -- smaller memory footprint. -- | Parse a top-level JSON value followed by optional whitespace and -- end-of-input. See also: 'json'. jsonEOF :: Parser Value jsonEOF = json <* skipSpace <* endOfInput -- | Parse a top-level JSON value followed by optional whitespace and -- end-of-input. See also: 'json''. jsonEOF' :: Parser Value jsonEOF' = json' <* skipSpace <* endOfInput -- | The only valid whitespace in a JSON document is space, newline, -- carriage return, and tab. skipSpace :: Parser () skipSpace = A.skipWhile $ \w -> w == 0x20 || w == 0x0a || w == 0x0d || w == 0x09 {-# INLINE skipSpace #-} ------------------ Copy-pasted and adapted from attoparsec ------------------ -- A strict pair data SP = SP !Integer {-# UNPACK #-}!Int decimal0 :: Parser Integer decimal0 = do let zero = 48 digits <- A.takeWhile1 isDigit_w8 if B.length digits > 1 && B.unsafeHead digits == zero then fail "leading zero" else return (bsToInteger digits) -- | Parse a JSON number. scientific :: Parser Scientific scientific = do let minus = 45 plus = 43 sign <- A.peekWord8' let !positive = sign == plus || sign /= minus when (sign == plus || sign == minus) $ void A.anyWord8 n <- decimal0 let f fracDigits = SP (B.foldl' step n fracDigits) (negate $ B.length fracDigits) step a w = a * 10 + fromIntegral (w - 48) dotty <- A.peekWord8 -- '.' -> ascii 46 SP c e <- case dotty of Just 46 -> A.anyWord8 *> (f <$> A.takeWhile1 isDigit_w8) _ -> pure (SP n 0) let !signedCoeff | positive = c | otherwise = -c let littleE = 101 bigE = 69 (A.satisfy (\ex -> ex == littleE || ex == bigE) *> fmap (Sci.scientific signedCoeff . (e +)) (signed decimal)) <|> return (Sci.scientific signedCoeff e) {-# INLINE scientific #-} ------------------ Copy-pasted and adapted from base ------------------------ bsToInteger :: B.ByteString -> Integer bsToInteger bs | l > 40 = valInteger 10 l [ fromIntegral (w - 48) | w <- B.unpack bs ] | otherwise = bsToIntegerSimple bs where l = B.length bs bsToIntegerSimple :: B.ByteString -> Integer bsToIntegerSimple = B.foldl' step 0 where step a b = a * 10 + fromIntegral (b - 48) -- 48 = '0' -- A sub-quadratic algorithm for Integer. Pairs of adjacent radix b -- digits are combined into a single radix b^2 digit. This process is -- repeated until we are left with a single digit. This algorithm -- performs well only on large inputs, so we use the simple algorithm -- for smaller inputs. valInteger :: Integer -> Int -> [Integer] -> Integer valInteger = go where go :: Integer -> Int -> [Integer] -> Integer go _ _ [] = 0 go _ _ [d] = d go b l ds | l > 40 = b' `seq` go b' l' (combine b ds') | otherwise = valSimple b ds where -- ensure that we have an even number of digits -- before we call combine: ds' = if even l then ds else 0 : ds b' = b * b l' = (l + 1) `quot` 2 combine b (d1 : d2 : ds) = d `seq` (d : combine b ds) where d = d1 * b + d2 combine _ [] = [] combine _ [_] = errorWithoutStackTrace "this should not happen" -- The following algorithm is only linear for types whose Num operations -- are in constant time. valSimple :: Integer -> [Integer] -> Integer valSimple base = go 0 where go r [] = r go r (d : ds) = r' `seq` go r' ds where r' = r * base + fromIntegral d aeson-1.4.2.0/Data/Aeson/Parser/Time.hs0000644000000000000000000000420100000000000015511 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Data.Aeson.Parser.Time ( run , day , localTime , timeOfDay , timeZone , utcTime , zonedTime ) where import Prelude.Compat import Data.Attoparsec.Text (Parser) import Data.Text (Text) import Data.Time.Calendar (Day) import Data.Time.Clock (UTCTime(..)) import qualified Data.Aeson.Types.Internal as Aeson import qualified Data.Attoparsec.Text as A import qualified Data.Attoparsec.Time as T import qualified Data.Time.LocalTime as Local -- | Run an attoparsec parser as an aeson parser. run :: Parser a -> Text -> Aeson.Parser a run p t = case A.parseOnly (p <* A.endOfInput) t of Left err -> fail $ "could not parse date: " ++ err Right r -> return r -- | Parse a date of the form @[+,-]YYYY-MM-DD@. day :: Parser Day day = T.day {-# INLINE day #-} -- | Parse a time of the form @HH:MM[:SS[.SSS]]@. timeOfDay :: Parser Local.TimeOfDay timeOfDay = T.timeOfDay {-# INLINE timeOfDay #-} -- | Parse a time zone, and return 'Nothing' if the offset from UTC is -- zero. (This makes some speedups possible.) timeZone :: Parser (Maybe Local.TimeZone) timeZone = T.timeZone {-# INLINE timeZone #-} -- | Parse a date and time, of the form @YYYY-MM-DD HH:MM[:SS[.SSS]]@. -- The space may be replaced with a @T@. The number of seconds is optional -- and may be followed by a fractional component. localTime :: Parser Local.LocalTime localTime = T.localTime {-# INLINE localTime #-} -- | Behaves as 'zonedTime', but converts any time zone offset into a -- UTC time. utcTime :: Parser UTCTime utcTime = T.utcTime {-# INLINE utcTime #-} -- | Parse a date with time zone info. Acceptable formats: -- -- @YYYY-MM-DD HH:MM Z@ -- @YYYY-MM-DD HH:MM:SS Z@ -- @YYYY-MM-DD HH:MM:SS.SSS Z@ -- -- The first space may instead be a @T@, and the second space is -- optional. The @Z@ represents UTC. The @Z@ may be replaced with a -- time zone offset of the form @+0000@ or @-08:00@, where the first -- two digits are hours, the @:@ is optional and the second two digits -- (also optional) are minutes. zonedTime :: Parser Local.ZonedTime zonedTime = T.zonedTime {-# INLINE zonedTime #-} aeson-1.4.2.0/Data/Aeson/Parser/Unescape.hs0000644000000000000000000000033100000000000016356 0ustar0000000000000000{-# LANGUAGE CPP #-} module Data.Aeson.Parser.Unescape ( unescapeText ) where #ifdef CFFI import Data.Aeson.Parser.UnescapeFFI (unescapeText) #else import Data.Aeson.Parser.UnescapePure (unescapeText) #endif aeson-1.4.2.0/Data/Aeson/QQ/0000755000000000000000000000000000000000000013347 5ustar0000000000000000aeson-1.4.2.0/Data/Aeson/QQ/Simple.hs0000644000000000000000000000162000000000000015133 0ustar0000000000000000-- | Like "Data.Aeson.QQ" but without interpolation. module Data.Aeson.QQ.Simple (aesonQQ) where import Data.Aeson import qualified Data.Text as T import qualified Data.Text.Encoding as TE import Language.Haskell.TH import Language.Haskell.TH.Quote import Language.Haskell.TH.Syntax (Lift (..)) import Prelude () import Prelude.Compat aesonQQ :: QuasiQuoter aesonQQ = QuasiQuoter { quoteExp = aesonExp , quotePat = const $ error "No quotePat defined for jsonQQ" , quoteType = const $ error "No quoteType defined for jsonQQ" , quoteDec = const $ error "No quoteDec defined for jsonQQ" } aesonExp :: String -> ExpQ aesonExp txt = case eitherDecodeStrict $ TE.encodeUtf8 $ T.pack txt of Left err -> error $ "Error in aesonExp: " ++ show err Right val -> lift (val :: Value) aeson-1.4.2.0/Data/Aeson/TH.hs0000644000000000000000000023052200000000000013701 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE UndecidableInstances #-} #if __GLASGOW_HASKELL__ >= 800 -- a) THQ works on cross-compilers and unregisterised GHCs -- b) may make compilation faster as no dynamic loading is ever needed (not sure about this) -- c) removes one hindrance to have code inferred as SafeHaskell safe {-# LANGUAGE TemplateHaskellQuotes #-} #else {-# LANGUAGE TemplateHaskell #-} #endif #include "incoherent-compat.h" #include "overlapping-compat.h" {-| Module: Data.Aeson.TH Copyright: (c) 2011-2016 Bryan O'Sullivan (c) 2011 MailRank, Inc. License: BSD3 Stability: experimental Portability: portable Functions to mechanically derive 'ToJSON' and 'FromJSON' instances. Note that you need to enable the @TemplateHaskell@ language extension in order to use this module. An example shows how instances are generated for arbitrary data types. First we define a data type: @ data D a = Nullary | Unary Int | Product String Char a | Record { testOne :: Double , testTwo :: Bool , testThree :: D a } deriving Eq @ Next we derive the necessary instances. Note that we make use of the feature to change record field names. In this case we drop the first 4 characters of every field name. We also modify constructor names by lower-casing them: @ $('deriveJSON' 'defaultOptions'{'fieldLabelModifier' = 'drop' 4, 'constructorTagModifier' = map toLower} ''D) @ Now we can use the newly created instances. @ d :: D 'Int' d = Record { testOne = 3.14159 , testTwo = 'True' , testThree = Product \"test\" \'A\' 123 } @ >>> fromJSON (toJSON d) == Success d > True This also works for data family instances, but instead of passing in the data family name (with double quotes), we pass in a data family instance constructor (with a single quote): @ data family DF a data instance DF Int = DF1 Int | DF2 Int Int deriving Eq $('deriveJSON' 'defaultOptions' 'DF1) -- Alternatively, one could pass 'DF2 instead @ Please note that you can derive instances for tuples using the following syntax: @ -- FromJSON and ToJSON instances for 4-tuples. $('deriveJSON' 'defaultOptions' ''(,,,)) @ -} module Data.Aeson.TH ( -- * Encoding configuration Options(..) , SumEncoding(..) , defaultOptions , defaultTaggedObject -- * FromJSON and ToJSON derivation , deriveJSON , deriveJSON1 , deriveJSON2 , deriveToJSON , deriveToJSON1 , deriveToJSON2 , deriveFromJSON , deriveFromJSON1 , deriveFromJSON2 , mkToJSON , mkLiftToJSON , mkLiftToJSON2 , mkToEncoding , mkLiftToEncoding , mkLiftToEncoding2 , mkParseJSON , mkLiftParseJSON , mkLiftParseJSON2 ) where import Prelude.Compat import Control.Applicative ((<|>)) import Data.Aeson (Object, (.:), FromJSON(..), FromJSON1(..), FromJSON2(..), ToJSON(..), ToJSON1(..), ToJSON2(..)) import Data.Aeson.Types (Options(..), Parser, SumEncoding(..), Value(..), defaultOptions, defaultTaggedObject) import Data.Aeson.Types.Internal ((), JSONPathElement(Key)) import Data.Aeson.Types.FromJSON (parseOptionalFieldWith) import Data.Aeson.Types.ToJSON (fromPairs, pair) import Control.Monad (liftM2, unless, when) import Data.Foldable (foldr') #if MIN_VERSION_template_haskell(2,8,0) && !MIN_VERSION_template_haskell(2,10,0) import Data.List (nub) #endif import Data.List (foldl', genericLength, intercalate, partition, union) import Data.List.NonEmpty ((<|), NonEmpty((:|))) import Data.Map (Map) import Data.Maybe (catMaybes, fromMaybe, mapMaybe) import qualified Data.Monoid as Monoid import Data.Set (Set) #if MIN_VERSION_template_haskell(2,8,0) import Language.Haskell.TH hiding (Arity) #else import Language.Haskell.TH #endif import Language.Haskell.TH.Datatype #if MIN_VERSION_template_haskell(2,7,0) && !(MIN_VERSION_template_haskell(2,8,0)) import Language.Haskell.TH.Lib (starK) #endif #if MIN_VERSION_template_haskell(2,8,0) && !(MIN_VERSION_template_haskell(2,10,0)) import Language.Haskell.TH.Syntax (mkNameG_tc) #endif import Text.Printf (printf) import qualified Data.Aeson.Encoding.Internal as E import qualified Data.Foldable as F (all) import qualified Data.HashMap.Strict as H (lookup, toList) import qualified Data.List.NonEmpty as NE (length, reverse) import qualified Data.Map as M (fromList, keys, lookup , singleton, size) import qualified Data.Semigroup as Semigroup (Option(..)) import qualified Data.Set as Set (empty, insert, member) import qualified Data.Text as T (Text, pack, unpack) import qualified Data.Vector as V (unsafeIndex, null, length, create, empty) import qualified Data.Vector.Mutable as VM (unsafeNew, unsafeWrite) {-# ANN module "Hlint: ignore Reduce duplication" #-} -------------------------------------------------------------------------------- -- Convenience -------------------------------------------------------------------------------- -- | Generates both 'ToJSON' and 'FromJSON' instance declarations for the given -- data type or data family instance constructor. -- -- This is a convienience function which is equivalent to calling both -- 'deriveToJSON' and 'deriveFromJSON'. deriveJSON :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate 'ToJSON' and 'FromJSON' -- instances. -> Q [Dec] deriveJSON = deriveJSONBoth deriveToJSON deriveFromJSON -- | Generates both 'ToJSON1' and 'FromJSON1' instance declarations for the given -- data type or data family instance constructor. -- -- This is a convienience function which is equivalent to calling both -- 'deriveToJSON1' and 'deriveFromJSON1'. deriveJSON1 :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate 'ToJSON1' and 'FromJSON1' -- instances. -> Q [Dec] deriveJSON1 = deriveJSONBoth deriveToJSON1 deriveFromJSON1 -- | Generates both 'ToJSON2' and 'FromJSON2' instance declarations for the given -- data type or data family instance constructor. -- -- This is a convienience function which is equivalent to calling both -- 'deriveToJSON2' and 'deriveFromJSON2'. deriveJSON2 :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate 'ToJSON2' and 'FromJSON2' -- instances. -> Q [Dec] deriveJSON2 = deriveJSONBoth deriveToJSON2 deriveFromJSON2 -------------------------------------------------------------------------------- -- ToJSON -------------------------------------------------------------------------------- {- TODO: Don't constrain phantom type variables. data Foo a = Foo Int instance (ToJSON a) ⇒ ToJSON Foo where ... The above (ToJSON a) constraint is not necessary and perhaps undesirable. -} -- | Generates a 'ToJSON' instance declaration for the given data type or -- data family instance constructor. deriveToJSON :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate a 'ToJSON' instance -- declaration. -> Q [Dec] deriveToJSON = deriveToJSONCommon toJSONClass -- | Generates a 'ToJSON1' instance declaration for the given data type or -- data family instance constructor. deriveToJSON1 :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate a 'ToJSON1' instance -- declaration. -> Q [Dec] deriveToJSON1 = deriveToJSONCommon toJSON1Class -- | Generates a 'ToJSON2' instance declaration for the given data type or -- data family instance constructor. deriveToJSON2 :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate a 'ToJSON2' instance -- declaration. -> Q [Dec] deriveToJSON2 = deriveToJSONCommon toJSON2Class deriveToJSONCommon :: JSONClass -- ^ The ToJSON variant being derived. -> Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate an instance. -> Q [Dec] deriveToJSONCommon = deriveJSONClass [ (ToJSON, \jc _ -> consToValue Value jc) , (ToEncoding, \jc _ -> consToValue Encoding jc) ] -- | Generates a lambda expression which encodes the given data type or -- data family instance constructor as a 'Value'. mkToJSON :: Options -- ^ Encoding options. -> Name -- ^ Name of the type to encode. -> Q Exp mkToJSON = mkToJSONCommon toJSONClass -- | Generates a lambda expression which encodes the given data type or -- data family instance constructor as a 'Value' by using the given encoding -- function on occurrences of the last type parameter. mkLiftToJSON :: Options -- ^ Encoding options. -> Name -- ^ Name of the type to encode. -> Q Exp mkLiftToJSON = mkToJSONCommon toJSON1Class -- | Generates a lambda expression which encodes the given data type or -- data family instance constructor as a 'Value' by using the given encoding -- functions on occurrences of the last two type parameters. mkLiftToJSON2 :: Options -- ^ Encoding options. -> Name -- ^ Name of the type to encode. -> Q Exp mkLiftToJSON2 = mkToJSONCommon toJSON2Class mkToJSONCommon :: JSONClass -- ^ Which class's method is being derived. -> Options -- ^ Encoding options. -> Name -- ^ Name of the encoded type. -> Q Exp mkToJSONCommon = mkFunCommon (\jc _ -> consToValue Value jc) -- | Generates a lambda expression which encodes the given data type or -- data family instance constructor as a JSON string. mkToEncoding :: Options -- ^ Encoding options. -> Name -- ^ Name of the type to encode. -> Q Exp mkToEncoding = mkToEncodingCommon toJSONClass -- | Generates a lambda expression which encodes the given data type or -- data family instance constructor as a JSON string by using the given encoding -- function on occurrences of the last type parameter. mkLiftToEncoding :: Options -- ^ Encoding options. -> Name -- ^ Name of the type to encode. -> Q Exp mkLiftToEncoding = mkToEncodingCommon toJSON1Class -- | Generates a lambda expression which encodes the given data type or -- data family instance constructor as a JSON string by using the given encoding -- functions on occurrences of the last two type parameters. mkLiftToEncoding2 :: Options -- ^ Encoding options. -> Name -- ^ Name of the type to encode. -> Q Exp mkLiftToEncoding2 = mkToEncodingCommon toJSON2Class mkToEncodingCommon :: JSONClass -- ^ Which class's method is being derived. -> Options -- ^ Encoding options. -> Name -- ^ Name of the encoded type. -> Q Exp mkToEncodingCommon = mkFunCommon (\jc _ -> consToValue Encoding jc) -- | Helper function used by both 'deriveToJSON' and 'mkToJSON'. Generates -- code to generate a 'Value' or 'Encoding' of a number of constructors. All -- constructors must be from the same type. consToValue :: ToJSONFun -- ^ The method ('toJSON' or 'toEncoding') being derived. -> JSONClass -- ^ The ToJSON variant being derived. -> Options -- ^ Encoding options. -> [Type] -- ^ The types from the data type/data family instance declaration -> [ConstructorInfo] -- ^ Constructors for which to generate JSON generating code. -> Q Exp consToValue _ _ _ _ [] = error $ "Data.Aeson.TH.consToValue: " ++ "Not a single constructor given!" consToValue target jc opts vars cons = do value <- newName "value" tjs <- newNameList "_tj" $ arityInt jc tjls <- newNameList "_tjl" $ arityInt jc let zippedTJs = zip tjs tjls interleavedTJs = interleave tjs tjls lastTyVars = map varTToName $ drop (length vars - arityInt jc) vars tvMap = M.fromList $ zip lastTyVars zippedTJs lamE (map varP $ interleavedTJs ++ [value]) $ caseE (varE value) (matches tvMap) where matches tvMap = case cons of -- A single constructor is directly encoded. The constructor itself may be -- forgotten. [con] | not (tagSingleConstructors opts) -> [argsToValue target jc tvMap opts False con] _ | allNullaryToStringTag opts && all isNullary cons -> [ match (conP conName []) (normalB $ conStr target opts conName) [] | con <- cons , let conName = constructorName con ] | otherwise -> [argsToValue target jc tvMap opts True con | con <- cons] -- | Name of the constructor as a quoted 'Value' or 'Encoding'. conStr :: ToJSONFun -> Options -> Name -> Q Exp conStr Value opts = appE [|String|] . conTxt opts conStr Encoding opts = appE [|E.text|] . conTxt opts -- | Name of the constructor as a quoted 'Text'. conTxt :: Options -> Name -> Q Exp conTxt opts = appE [|T.pack|] . stringE . conString opts -- | Name of the constructor. conString :: Options -> Name -> String conString opts = constructorTagModifier opts . nameBase -- | If constructor is nullary. isNullary :: ConstructorInfo -> Bool isNullary ConstructorInfo { constructorVariant = NormalConstructor , constructorFields = tys } = null tys isNullary _ = False -- | Wrap fields of a non-record constructor. See 'sumToValue'. opaqueSumToValue :: ToJSONFun -> Options -> Bool -> Bool -> Name -> ExpQ -> ExpQ opaqueSumToValue target opts multiCons nullary conName value = sumToValue target opts multiCons nullary conName value pairs where pairs contentsFieldName = pairE contentsFieldName value -- | Wrap fields of a record constructor. See 'sumToValue'. recordSumToValue :: ToJSONFun -> Options -> Bool -> Bool -> Name -> ExpQ -> ExpQ recordSumToValue target opts multiCons nullary conName pairs = sumToValue target opts multiCons nullary conName (fromPairsE pairs) (const pairs) -- | Wrap fields of a constructor. sumToValue :: ToJSONFun -- ^ The method being derived. -> Options -- ^ Deriving options. -> Bool -- ^ Does this type have multiple constructors. -> Bool -- ^ Is this constructor nullary. -> Name -- ^ Constructor name. -> ExpQ -- ^ Fields of the constructor as a 'Value' or 'Encoding'. -> (String -> ExpQ) -- ^ Representation of an 'Object' fragment used for the 'TaggedObject' -- variant; of type @[(Text,Value)]@ or @[Encoding]@, depending on the method -- being derived. -- -- - For non-records, produces a pair @"contentsFieldName":value@, -- given a @contentsFieldName@ as an argument. See 'opaqueSumToValue'. -- - For records, produces the list of pairs corresponding to fields of the -- encoded value (ignores the argument). See 'recordSumToValue'. -> ExpQ sumToValue target opts multiCons nullary conName value pairs | multiCons = case sumEncoding opts of TwoElemArray -> array target [conStr target opts conName, value] TaggedObject{tagFieldName, contentsFieldName} -> -- TODO: Maybe throw an error in case -- tagFieldName overwrites a field in pairs. let tag = pairE tagFieldName (conStr target opts conName) content = pairs contentsFieldName in fromPairsE $ if nullary then tag else infixApp tag [|(Monoid.<>)|] content ObjectWithSingleField -> objectE [(conString opts conName, value)] UntaggedValue | nullary -> conStr target opts conName UntaggedValue -> value | otherwise = value -- | Generates code to generate the JSON encoding of a single constructor. argsToValue :: ToJSONFun -> JSONClass -> TyVarMap -> Options -> Bool -> ConstructorInfo -> Q Match -- Polyadic constructors with special case for unary constructors. argsToValue target jc tvMap opts multiCons ConstructorInfo { constructorName = conName , constructorVariant = NormalConstructor , constructorFields = argTys } = do argTys' <- mapM resolveTypeSynonyms argTys let len = length argTys' args <- newNameList "arg" len let js = case [ dispatchToJSON target jc conName tvMap argTy `appE` varE arg | (arg, argTy) <- zip args argTys' ] of -- Single argument is directly converted. [e] -> e -- Zero and multiple arguments are converted to a JSON array. es -> array target es match (conP conName $ map varP args) (normalB $ opaqueSumToValue target opts multiCons (null argTys') conName js) [] -- Records. argsToValue target jc tvMap opts multiCons info@ConstructorInfo { constructorName = conName , constructorVariant = RecordConstructor fields , constructorFields = argTys } = case (unwrapUnaryRecords opts, not multiCons, argTys) of (True,True,[_]) -> argsToValue target jc tvMap opts multiCons (info{constructorVariant = NormalConstructor}) _ -> do argTys' <- mapM resolveTypeSynonyms argTys args <- newNameList "arg" $ length argTys' let pairs | omitNothingFields opts = infixApp maybeFields [|(Monoid.<>)|] restFields | otherwise = mconcatE (map pureToPair argCons) argCons = zip3 (map varE args) argTys' fields maybeFields = mconcatE (map maybeToPair maybes) restFields = mconcatE (map pureToPair rest) (maybes0, rest0) = partition isMaybe argCons (options, rest) = partition isOption rest0 maybes = maybes0 ++ map optionToMaybe options maybeToPair = toPairLifted True pureToPair = toPairLifted False toPairLifted lifted (arg, argTy, field) = let toValue = dispatchToJSON target jc conName tvMap argTy fieldName = fieldLabel opts field e arg' = pairE fieldName (toValue `appE` arg') in if lifted then do x <- newName "x" [|maybe mempty|] `appE` lam1E (varP x) (e (varE x)) `appE` arg else e arg match (conP conName $ map varP args) (normalB $ recordSumToValue target opts multiCons (null argTys) conName pairs) [] -- Infix constructors. argsToValue target jc tvMap opts multiCons ConstructorInfo { constructorName = conName , constructorVariant = InfixConstructor , constructorFields = argTys } = do [alTy, arTy] <- mapM resolveTypeSynonyms argTys al <- newName "argL" ar <- newName "argR" match (infixP (varP al) conName (varP ar)) ( normalB $ opaqueSumToValue target opts multiCons False conName $ array target [ dispatchToJSON target jc conName tvMap aTy `appE` varE a | (a, aTy) <- [(al,alTy), (ar,arTy)] ] ) [] isMaybe :: (a, Type, b) -> Bool isMaybe (_, AppT (ConT t) _, _) = t == ''Maybe isMaybe _ = False isOption :: (a, Type, b) -> Bool isOption (_, AppT (ConT t) _, _) = t == ''Semigroup.Option isOption _ = False optionToMaybe :: (ExpQ, b, c) -> (ExpQ, b, c) optionToMaybe (a, b, c) = ([|Semigroup.getOption|] `appE` a, b, c) (<^>) :: ExpQ -> ExpQ -> ExpQ (<^>) a b = infixApp a [|(E.><)|] b infixr 6 <^> (<%>) :: ExpQ -> ExpQ -> ExpQ (<%>) a b = a <^> [|E.comma|] <^> b infixr 4 <%> -- | Wrap a list of quoted 'Value's in a quoted 'Array' (of type 'Value'). array :: ToJSONFun -> [ExpQ] -> ExpQ array Encoding [] = [|E.emptyArray_|] array Value [] = [|Array V.empty|] array Encoding es = [|E.wrapArray|] `appE` foldr1 (<%>) es array Value es = do mv <- newName "mv" let newMV = bindS (varP mv) ([|VM.unsafeNew|] `appE` litE (integerL $ fromIntegral (length es))) stmts = [ noBindS $ [|VM.unsafeWrite|] `appE` varE mv `appE` litE (integerL ix) `appE` e | (ix, e) <- zip [(0::Integer)..] es ] ret = noBindS $ [|return|] `appE` varE mv [|Array|] `appE` (varE 'V.create `appE` doE (newMV:stmts++[ret])) -- | Wrap an associative list of keys and quoted values in a quoted 'Object'. objectE :: [(String, ExpQ)] -> ExpQ objectE = fromPairsE . mconcatE . fmap (uncurry pairE) -- | 'mconcat' a list of fixed length. -- -- > mconcatE [ [|x|], [|y|], [|z|] ] = [| x <> (y <> z) |] mconcatE :: [ExpQ] -> ExpQ mconcatE [] = [|Monoid.mempty|] mconcatE [x] = x mconcatE (x : xs) = infixApp x [|(Monoid.<>)|] (mconcatE xs) fromPairsE :: ExpQ -> ExpQ fromPairsE = ([|fromPairs|] `appE`) -- | Create (an encoding of) a key-value pair. -- -- > pairE "k" [|v|] = [|pair "k" v|] pairE :: String -> ExpQ -> ExpQ pairE k v = [|pair k|] `appE` v -------------------------------------------------------------------------------- -- FromJSON -------------------------------------------------------------------------------- -- | Generates a 'FromJSON' instance declaration for the given data type or -- data family instance constructor. deriveFromJSON :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate a 'FromJSON' instance -- declaration. -> Q [Dec] deriveFromJSON = deriveFromJSONCommon fromJSONClass -- | Generates a 'FromJSON1' instance declaration for the given data type or -- data family instance constructor. deriveFromJSON1 :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate a 'FromJSON1' instance -- declaration. -> Q [Dec] deriveFromJSON1 = deriveFromJSONCommon fromJSON1Class -- | Generates a 'FromJSON2' instance declaration for the given data type or -- data family instance constructor. deriveFromJSON2 :: Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate a 'FromJSON3' instance -- declaration. -> Q [Dec] deriveFromJSON2 = deriveFromJSONCommon fromJSON2Class deriveFromJSONCommon :: JSONClass -- ^ The FromJSON variant being derived. -> Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate an instance. -- declaration. -> Q [Dec] deriveFromJSONCommon = deriveJSONClass [(ParseJSON, consFromJSON)] -- | Generates a lambda expression which parses the JSON encoding of the given -- data type or data family instance constructor. mkParseJSON :: Options -- ^ Encoding options. -> Name -- ^ Name of the encoded type. -> Q Exp mkParseJSON = mkParseJSONCommon fromJSONClass -- | Generates a lambda expression which parses the JSON encoding of the given -- data type or data family instance constructor by using the given parsing -- function on occurrences of the last type parameter. mkLiftParseJSON :: Options -- ^ Encoding options. -> Name -- ^ Name of the encoded type. -> Q Exp mkLiftParseJSON = mkParseJSONCommon fromJSON1Class -- | Generates a lambda expression which parses the JSON encoding of the given -- data type or data family instance constructor by using the given parsing -- functions on occurrences of the last two type parameters. mkLiftParseJSON2 :: Options -- ^ Encoding options. -> Name -- ^ Name of the encoded type. -> Q Exp mkLiftParseJSON2 = mkParseJSONCommon fromJSON2Class mkParseJSONCommon :: JSONClass -- ^ Which class's method is being derived. -> Options -- ^ Encoding options. -> Name -- ^ Name of the encoded type. -> Q Exp mkParseJSONCommon = mkFunCommon consFromJSON -- | Helper function used by both 'deriveFromJSON' and 'mkParseJSON'. Generates -- code to parse the JSON encoding of a number of constructors. All constructors -- must be from the same type. consFromJSON :: JSONClass -- ^ The FromJSON variant being derived. -> Name -- ^ Name of the type to which the constructors belong. -> Options -- ^ Encoding options -> [Type] -- ^ The types from the data type/data family instance declaration -> [ConstructorInfo] -- ^ Constructors for which to generate JSON parsing code. -> Q Exp consFromJSON _ _ _ _ [] = error $ "Data.Aeson.TH.consFromJSON: " ++ "Not a single constructor given!" consFromJSON jc tName opts vars cons = do value <- newName "value" pjs <- newNameList "_pj" $ arityInt jc pjls <- newNameList "_pjl" $ arityInt jc let zippedPJs = zip pjs pjls interleavedPJs = interleave pjs pjls lastTyVars = map varTToName $ drop (length vars - arityInt jc) vars tvMap = M.fromList $ zip lastTyVars zippedPJs lamE (map varP $ interleavedPJs ++ [value]) $ lamExpr value tvMap where checkExi tvMap con = checkExistentialContext jc tvMap (constructorContext con) (constructorName con) lamExpr value tvMap = case cons of [con] | not (tagSingleConstructors opts) -> checkExi tvMap con $ parseArgs jc tvMap tName opts con (Right value) _ | sumEncoding opts == UntaggedValue -> parseUntaggedValue tvMap cons value | otherwise -> caseE (varE value) $ if allNullaryToStringTag opts && all isNullary cons then allNullaryMatches else mixedMatches tvMap allNullaryMatches = [ do txt <- newName "txt" match (conP 'String [varP txt]) (guardedB $ [ liftM2 (,) (normalG $ infixApp (varE txt) [|(==)|] (conTxt opts conName) ) ([|pure|] `appE` conE conName) | con <- cons , let conName = constructorName con ] ++ [ liftM2 (,) (normalG [|otherwise|]) ( [|noMatchFail|] `appE` litE (stringL $ show tName) `appE` ([|T.unpack|] `appE` varE txt) ) ] ) [] , do other <- newName "other" match (varP other) (normalB $ [|noStringFail|] `appE` litE (stringL $ show tName) `appE` ([|valueConName|] `appE` varE other) ) [] ] mixedMatches tvMap = case sumEncoding opts of TaggedObject {tagFieldName, contentsFieldName} -> parseObject $ parseTaggedObject tvMap tagFieldName contentsFieldName UntaggedValue -> error "UntaggedValue: Should be handled already" ObjectWithSingleField -> parseObject $ parseObjectWithSingleField tvMap TwoElemArray -> [ do arr <- newName "array" match (conP 'Array [varP arr]) (guardedB [ liftM2 (,) (normalG $ infixApp ([|V.length|] `appE` varE arr) [|(==)|] (litE $ integerL 2)) (parse2ElemArray tvMap arr) , liftM2 (,) (normalG [|otherwise|]) ([|not2ElemArray|] `appE` litE (stringL $ show tName) `appE` ([|V.length|] `appE` varE arr)) ] ) [] , do other <- newName "other" match (varP other) ( normalB $ [|noArrayFail|] `appE` litE (stringL $ show tName) `appE` ([|valueConName|] `appE` varE other) ) [] ] parseObject f = [ do obj <- newName "obj" match (conP 'Object [varP obj]) (normalB $ f obj) [] , do other <- newName "other" match (varP other) ( normalB $ [|noObjectFail|] `appE` litE (stringL $ show tName) `appE` ([|valueConName|] `appE` varE other) ) [] ] parseTaggedObject tvMap typFieldName valFieldName obj = do conKey <- newName "conKey" doE [ bindS (varP conKey) (infixApp (varE obj) [|(.:)|] ([|T.pack|] `appE` stringE typFieldName)) , noBindS $ parseContents tvMap conKey (Left (valFieldName, obj)) 'conNotFoundFailTaggedObject ] parseUntaggedValue tvMap cons' conVal = foldr1 (\e e' -> infixApp e [|(<|>)|] e') (map (\x -> parseValue tvMap x conVal) cons') parseValue _tvMap ConstructorInfo { constructorName = conName , constructorVariant = NormalConstructor , constructorFields = [] } conVal = do str <- newName "str" caseE (varE conVal) [ match (conP 'String [varP str]) (guardedB [ liftM2 (,) (normalG $ infixApp (varE str) [|(==)|] (conTxt opts conName) ) ([|pure|] `appE` conE conName) ] ) [] , matchFailed tName conName "String" ] parseValue tvMap con conVal = checkExi tvMap con $ parseArgs jc tvMap tName opts con (Right conVal) parse2ElemArray tvMap arr = do conKey <- newName "conKey" conVal <- newName "conVal" let letIx n ix = valD (varP n) (normalB ([|V.unsafeIndex|] `appE` varE arr `appE` litE (integerL ix))) [] letE [ letIx conKey 0 , letIx conVal 1 ] (caseE (varE conKey) [ do txt <- newName "txt" match (conP 'String [varP txt]) (normalB $ parseContents tvMap txt (Right conVal) 'conNotFoundFail2ElemArray ) [] , do other <- newName "other" match (varP other) ( normalB $ [|firstElemNoStringFail|] `appE` litE (stringL $ show tName) `appE` ([|valueConName|] `appE` varE other) ) [] ] ) parseObjectWithSingleField tvMap obj = do conKey <- newName "conKey" conVal <- newName "conVal" caseE ([e|H.toList|] `appE` varE obj) [ match (listP [tupP [varP conKey, varP conVal]]) (normalB $ parseContents tvMap conKey (Right conVal) 'conNotFoundFailObjectSingleField) [] , do other <- newName "other" match (varP other) (normalB $ [|wrongPairCountFail|] `appE` litE (stringL $ show tName) `appE` ([|show . length|] `appE` varE other) ) [] ] parseContents tvMap conKey contents errorFun = caseE (varE conKey) [ match wildP ( guardedB $ [ do g <- normalG $ infixApp (varE conKey) [|(==)|] ([|T.pack|] `appE` conNameExp opts con) e <- checkExi tvMap con $ parseArgs jc tvMap tName opts con contents return (g, e) | con <- cons ] ++ [ liftM2 (,) (normalG [e|otherwise|]) ( varE errorFun `appE` litE (stringL $ show tName) `appE` listE (map ( litE . stringL . constructorTagModifier opts . nameBase . constructorName ) cons ) `appE` ([|T.unpack|] `appE` varE conKey) ) ] ) [] ] parseNullaryMatches :: Name -> Name -> [Q Match] parseNullaryMatches tName conName = [ do arr <- newName "arr" match (conP 'Array [varP arr]) (guardedB [ liftM2 (,) (normalG $ [|V.null|] `appE` varE arr) ([|pure|] `appE` conE conName) , liftM2 (,) (normalG [|otherwise|]) (parseTypeMismatch tName conName (litE $ stringL "an empty Array") (infixApp (litE $ stringL "Array of length ") [|(++)|] ([|show . V.length|] `appE` varE arr) ) ) ] ) [] , matchFailed tName conName "Array" ] parseUnaryMatches :: JSONClass -> TyVarMap -> Type -> Name -> [Q Match] parseUnaryMatches jc tvMap argTy conName = [ do arg <- newName "arg" match (varP arg) ( normalB $ infixApp (conE conName) [|(<$>)|] (dispatchParseJSON jc conName tvMap argTy `appE` varE arg) ) [] ] parseRecord :: JSONClass -> TyVarMap -> [Type] -> Options -> Name -> Name -> [Name] -> Name -> ExpQ parseRecord jc tvMap argTys opts tName conName fields obj = foldl' (\a b -> infixApp a [|(<*>)|] b) (infixApp (conE conName) [|(<$>)|] x) xs where x:xs = [ [|lookupField|] `appE` dispatchParseJSON jc conName tvMap argTy `appE` litE (stringL $ show tName) `appE` litE (stringL $ constructorTagModifier opts $ nameBase conName) `appE` varE obj `appE` ( [|T.pack|] `appE` stringE (fieldLabel opts field) ) | (field, argTy) <- zip fields argTys ] getValField :: Name -> String -> [MatchQ] -> Q Exp getValField obj valFieldName matches = do val <- newName "val" doE [ bindS (varP val) $ infixApp (varE obj) [|(.:)|] ([|T.pack|] `appE` litE (stringL valFieldName)) , noBindS $ caseE (varE val) matches ] matchCases :: Either (String, Name) Name -> [MatchQ] -> Q Exp matchCases (Left (valFieldName, obj)) = getValField obj valFieldName matchCases (Right valName) = caseE (varE valName) -- | Generates code to parse the JSON encoding of a single constructor. parseArgs :: JSONClass -- ^ The FromJSON variant being derived. -> TyVarMap -- ^ Maps the last type variables to their decoding -- function arguments. -> Name -- ^ Name of the type to which the constructor belongs. -> Options -- ^ Encoding options. -> ConstructorInfo -- ^ Constructor for which to generate JSON parsing code. -> Either (String, Name) Name -- ^ Left (valFieldName, objName) or -- Right valName -> Q Exp -- Nullary constructors. parseArgs _ _ _ _ ConstructorInfo { constructorName = conName , constructorVariant = NormalConstructor , constructorFields = [] } (Left _) = [|pure|] `appE` conE conName parseArgs _ _ tName _ ConstructorInfo { constructorName = conName , constructorVariant = NormalConstructor , constructorFields = [] } (Right valName) = caseE (varE valName) $ parseNullaryMatches tName conName -- Unary constructors. parseArgs jc tvMap _ _ ConstructorInfo { constructorName = conName , constructorVariant = NormalConstructor , constructorFields = [argTy] } contents = do argTy' <- resolveTypeSynonyms argTy matchCases contents $ parseUnaryMatches jc tvMap argTy' conName -- Polyadic constructors. parseArgs jc tvMap tName _ ConstructorInfo { constructorName = conName , constructorVariant = NormalConstructor , constructorFields = argTys } contents = do argTys' <- mapM resolveTypeSynonyms argTys let len = genericLength argTys' matchCases contents $ parseProduct jc tvMap argTys' tName conName len -- Records. parseArgs jc tvMap tName opts ConstructorInfo { constructorName = conName , constructorVariant = RecordConstructor fields , constructorFields = argTys } (Left (_, obj)) = do argTys' <- mapM resolveTypeSynonyms argTys parseRecord jc tvMap argTys' opts tName conName fields obj parseArgs jc tvMap tName opts info@ConstructorInfo { constructorName = conName , constructorVariant = RecordConstructor fields , constructorFields = argTys } (Right valName) = case (unwrapUnaryRecords opts,argTys) of (True,[_])-> parseArgs jc tvMap tName opts (info{constructorVariant = NormalConstructor}) (Right valName) _ -> do obj <- newName "recObj" argTys' <- mapM resolveTypeSynonyms argTys caseE (varE valName) [ match (conP 'Object [varP obj]) (normalB $ parseRecord jc tvMap argTys' opts tName conName fields obj) [] , matchFailed tName conName "Object" ] -- Infix constructors. Apart from syntax these are the same as -- polyadic constructors. parseArgs jc tvMap tName _ ConstructorInfo { constructorName = conName , constructorVariant = InfixConstructor , constructorFields = argTys } contents = do argTys' <- mapM resolveTypeSynonyms argTys matchCases contents $ parseProduct jc tvMap argTys' tName conName 2 -- | Generates code to parse the JSON encoding of an n-ary -- constructor. parseProduct :: JSONClass -- ^ The FromJSON variant being derived. -> TyVarMap -- ^ Maps the last type variables to their decoding -- function arguments. -> [Type] -- ^ The argument types of the constructor. -> Name -- ^ Name of the type to which the constructor belongs. -> Name -- ^ 'Con'structor name. -> Integer -- ^ 'Con'structor arity. -> [Q Match] parseProduct jc tvMap argTys tName conName numArgs = [ do arr <- newName "arr" -- List of: "parseJSON (arr `V.unsafeIndex` )" let x:xs = [ dispatchParseJSON jc conName tvMap argTy `appE` infixApp (varE arr) [|V.unsafeIndex|] (litE $ integerL ix) | (argTy, ix) <- zip argTys [0 .. numArgs - 1] ] match (conP 'Array [varP arr]) (normalB $ condE ( infixApp ([|V.length|] `appE` varE arr) [|(==)|] (litE $ integerL numArgs) ) ( foldl' (\a b -> infixApp a [|(<*>)|] b) (infixApp (conE conName) [|(<$>)|] x) xs ) ( parseTypeMismatch tName conName (litE $ stringL $ "Array of length " ++ show numArgs) ( infixApp (litE $ stringL "Array of length ") [|(++)|] ([|show . V.length|] `appE` varE arr) ) ) ) [] , matchFailed tName conName "Array" ] -------------------------------------------------------------------------------- -- Parsing errors -------------------------------------------------------------------------------- matchFailed :: Name -> Name -> String -> MatchQ matchFailed tName conName expected = do other <- newName "other" match (varP other) ( normalB $ parseTypeMismatch tName conName (litE $ stringL expected) ([|valueConName|] `appE` varE other) ) [] parseTypeMismatch :: Name -> Name -> ExpQ -> ExpQ -> ExpQ parseTypeMismatch tName conName expected actual = foldl appE [|parseTypeMismatch'|] [ litE $ stringL $ nameBase conName , litE $ stringL $ show tName , expected , actual ] class LookupField a where lookupField :: (Value -> Parser a) -> String -> String -> Object -> T.Text -> Parser a instance OVERLAPPABLE_ LookupField a where lookupField = lookupFieldWith instance INCOHERENT_ LookupField (Maybe a) where lookupField pj _ _ = parseOptionalFieldWith pj instance INCOHERENT_ LookupField (Semigroup.Option a) where lookupField pj tName rec obj key = fmap Semigroup.Option (lookupField (fmap Semigroup.getOption . pj) tName rec obj key) lookupFieldWith :: (Value -> Parser a) -> String -> String -> Object -> T.Text -> Parser a lookupFieldWith pj tName rec obj key = case H.lookup key obj of Nothing -> unknownFieldFail tName rec (T.unpack key) Just v -> pj v Key key unknownFieldFail :: String -> String -> String -> Parser fail unknownFieldFail tName rec key = fail $ printf "When parsing the record %s of type %s the key %s was not present." rec tName key noArrayFail :: String -> String -> Parser fail noArrayFail t o = fail $ printf "When parsing %s expected Array but got %s." t o noObjectFail :: String -> String -> Parser fail noObjectFail t o = fail $ printf "When parsing %s expected Object but got %s." t o firstElemNoStringFail :: String -> String -> Parser fail firstElemNoStringFail t o = fail $ printf "When parsing %s expected an Array of 2 elements where the first element is a String but got %s at the first element." t o wrongPairCountFail :: String -> String -> Parser fail wrongPairCountFail t n = fail $ printf "When parsing %s expected an Object with a single tag/contents pair but got %s pairs." t n noStringFail :: String -> String -> Parser fail noStringFail t o = fail $ printf "When parsing %s expected String but got %s." t o noMatchFail :: String -> String -> Parser fail noMatchFail t o = fail $ printf "When parsing %s expected a String with the tag of a constructor but got %s." t o not2ElemArray :: String -> Int -> Parser fail not2ElemArray t i = fail $ printf "When parsing %s expected an Array of 2 elements but got %i elements" t i conNotFoundFail2ElemArray :: String -> [String] -> String -> Parser fail conNotFoundFail2ElemArray t cs o = fail $ printf "When parsing %s expected a 2-element Array with a tag and contents element where the tag is one of [%s], but got %s." t (intercalate ", " cs) o conNotFoundFailObjectSingleField :: String -> [String] -> String -> Parser fail conNotFoundFailObjectSingleField t cs o = fail $ printf "When parsing %s expected an Object with a single tag/contents pair where the tag is one of [%s], but got %s." t (intercalate ", " cs) o conNotFoundFailTaggedObject :: String -> [String] -> String -> Parser fail conNotFoundFailTaggedObject t cs o = fail $ printf "When parsing %s expected an Object with a tag field where the value is one of [%s], but got %s." t (intercalate ", " cs) o parseTypeMismatch' :: String -> String -> String -> String -> Parser fail parseTypeMismatch' conName tName expected actual = fail $ printf "When parsing the constructor %s of type %s expected %s but got %s." conName tName expected actual -------------------------------------------------------------------------------- -- Shared ToJSON and FromJSON code -------------------------------------------------------------------------------- -- | Functionality common to 'deriveJSON', 'deriveJSON1', and 'deriveJSON2'. deriveJSONBoth :: (Options -> Name -> Q [Dec]) -- ^ Function which derives a flavor of 'ToJSON'. -> (Options -> Name -> Q [Dec]) -- ^ Function which derives a flavor of 'FromJSON'. -> Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate 'ToJSON' and 'FromJSON' -- instances. -> Q [Dec] deriveJSONBoth dtj dfj opts name = liftM2 (++) (dtj opts name) (dfj opts name) -- | Functionality common to @deriveToJSON(1)(2)@ and @deriveFromJSON(1)(2)@. deriveJSONClass :: [(JSONFun, JSONClass -> Name -> Options -> [Type] -> [ConstructorInfo] -> Q Exp)] -- ^ The class methods and the functions which derive them. -> JSONClass -- ^ The class for which to generate an instance. -> Options -- ^ Encoding options. -> Name -- ^ Name of the type for which to generate a class instance -- declaration. -> Q [Dec] deriveJSONClass consFuns jc opts name = do info <- reifyDatatype name case info of DatatypeInfo { datatypeContext = ctxt , datatypeName = parentName , datatypeVars = vars , datatypeVariant = variant , datatypeCons = cons } -> do (instanceCxt, instanceType) <- buildTypeInstance parentName jc ctxt vars variant (:[]) <$> instanceD (return instanceCxt) (return instanceType) (methodDecs parentName vars cons) where methodDecs :: Name -> [Type] -> [ConstructorInfo] -> [Q Dec] methodDecs parentName vars cons = flip map consFuns $ \(jf, jfMaker) -> funD (jsonFunValName jf (arity jc)) [ clause [] (normalB $ jfMaker jc parentName opts vars cons) [] ] mkFunCommon :: (JSONClass -> Name -> Options -> [Type] -> [ConstructorInfo] -> Q Exp) -- ^ The function which derives the expression. -> JSONClass -- ^ Which class's method is being derived. -> Options -- ^ Encoding options. -> Name -- ^ Name of the encoded type. -> Q Exp mkFunCommon consFun jc opts name = do info <- reifyDatatype name case info of DatatypeInfo { datatypeContext = ctxt , datatypeName = parentName , datatypeVars = vars , datatypeVariant = variant , datatypeCons = cons } -> do -- We force buildTypeInstance here since it performs some checks for whether -- or not the provided datatype's kind matches the derived method's -- typeclass, and produces errors if it can't. !_ <- buildTypeInstance parentName jc ctxt vars variant consFun jc parentName opts vars cons dispatchFunByType :: JSONClass -> JSONFun -> Name -> TyVarMap -> Bool -- True if we are using the function argument that works -- on lists (e.g., [a] -> Value). False is we are using -- the function argument that works on single values -- (e.g., a -> Value). -> Type -> Q Exp dispatchFunByType _ jf _ tvMap list (VarT tyName) = varE $ case M.lookup tyName tvMap of Just (tfjExp, tfjlExp) -> if list then tfjlExp else tfjExp Nothing -> jsonFunValOrListName list jf Arity0 dispatchFunByType jc jf conName tvMap list (SigT ty _) = dispatchFunByType jc jf conName tvMap list ty dispatchFunByType jc jf conName tvMap list (ForallT _ _ ty) = dispatchFunByType jc jf conName tvMap list ty dispatchFunByType jc jf conName tvMap list ty = do let tyCon :: Type tyArgs :: [Type] tyCon :| tyArgs = unapplyTy ty numLastArgs :: Int numLastArgs = min (arityInt jc) (length tyArgs) lhsArgs, rhsArgs :: [Type] (lhsArgs, rhsArgs) = splitAt (length tyArgs - numLastArgs) tyArgs tyVarNames :: [Name] tyVarNames = M.keys tvMap itf <- isTyFamily tyCon if any (`mentionsName` tyVarNames) lhsArgs || itf && any (`mentionsName` tyVarNames) tyArgs then outOfPlaceTyVarError jc conName else if any (`mentionsName` tyVarNames) rhsArgs then appsE $ varE (jsonFunValOrListName list jf $ toEnum numLastArgs) : zipWith (dispatchFunByType jc jf conName tvMap) (cycle [False,True]) (interleave rhsArgs rhsArgs) else varE $ jsonFunValOrListName list jf Arity0 dispatchToJSON :: ToJSONFun -> JSONClass -> Name -> TyVarMap -> Type -> Q Exp dispatchToJSON target jc n tvMap = dispatchFunByType jc (targetToJSONFun target) n tvMap False dispatchParseJSON :: JSONClass -> Name -> TyVarMap -> Type -> Q Exp dispatchParseJSON jc n tvMap = dispatchFunByType jc ParseJSON n tvMap False -------------------------------------------------------------------------------- -- Utility functions -------------------------------------------------------------------------------- -- For the given Types, generate an instance context and head. buildTypeInstance :: Name -- ^ The type constructor or data family name -> JSONClass -- ^ The typeclass to derive -> Cxt -- ^ The datatype context -> [Type] -- ^ The types to instantiate the instance with -> DatatypeVariant -- ^ Are we dealing with a data family instance or not -> Q (Cxt, Type) buildTypeInstance tyConName jc dataCxt varTysOrig variant = do -- Make sure to expand through type/kind synonyms! Otherwise, the -- eta-reduction check might get tripped up over type variables in a -- synonym that are actually dropped. -- (See GHC Trac #11416 for a scenario where this actually happened.) varTysExp <- mapM resolveTypeSynonyms varTysOrig let remainingLength :: Int remainingLength = length varTysOrig - arityInt jc droppedTysExp :: [Type] droppedTysExp = drop remainingLength varTysExp droppedStarKindStati :: [StarKindStatus] droppedStarKindStati = map canRealizeKindStar droppedTysExp -- Check there are enough types to drop and that all of them are either of -- kind * or kind k (for some kind variable k). If not, throw an error. when (remainingLength < 0 || elem NotKindStar droppedStarKindStati) $ derivingKindError jc tyConName let droppedKindVarNames :: [Name] droppedKindVarNames = catKindVarNames droppedStarKindStati -- Substitute kind * for any dropped kind variables varTysExpSubst :: [Type] varTysExpSubst = map (substNamesWithKindStar droppedKindVarNames) varTysExp remainingTysExpSubst, droppedTysExpSubst :: [Type] (remainingTysExpSubst, droppedTysExpSubst) = splitAt remainingLength varTysExpSubst -- All of the type variables mentioned in the dropped types -- (post-synonym expansion) droppedTyVarNames :: [Name] droppedTyVarNames = freeVariables droppedTysExpSubst -- If any of the dropped types were polykinded, ensure that they are of kind * -- after substituting * for the dropped kind variables. If not, throw an error. unless (all hasKindStar droppedTysExpSubst) $ derivingKindError jc tyConName let preds :: [Maybe Pred] kvNames :: [[Name]] kvNames' :: [Name] -- Derive instance constraints (and any kind variables which are specialized -- to * in those constraints) (preds, kvNames) = unzip $ map (deriveConstraint jc) remainingTysExpSubst kvNames' = concat kvNames -- Substitute the kind variables specialized in the constraints with * remainingTysExpSubst' :: [Type] remainingTysExpSubst' = map (substNamesWithKindStar kvNames') remainingTysExpSubst -- We now substitute all of the specialized-to-* kind variable names with -- *, but in the original types, not the synonym-expanded types. The reason -- we do this is a superficial one: we want the derived instance to resemble -- the datatype written in source code as closely as possible. For example, -- for the following data family instance: -- -- data family Fam a -- newtype instance Fam String = Fam String -- -- We'd want to generate the instance: -- -- instance C (Fam String) -- -- Not: -- -- instance C (Fam [Char]) remainingTysOrigSubst :: [Type] remainingTysOrigSubst = map (substNamesWithKindStar (droppedKindVarNames `union` kvNames')) $ take remainingLength varTysOrig isDataFamily :: Bool isDataFamily = case variant of Datatype -> False Newtype -> False DataInstance -> True NewtypeInstance -> True remainingTysOrigSubst' :: [Type] -- See Note [Kind signatures in derived instances] for an explanation -- of the isDataFamily check. remainingTysOrigSubst' = if isDataFamily then remainingTysOrigSubst else map unSigT remainingTysOrigSubst instanceCxt :: Cxt instanceCxt = catMaybes preds instanceType :: Type instanceType = AppT (ConT $ jsonClassName jc) $ applyTyCon tyConName remainingTysOrigSubst' -- If the datatype context mentions any of the dropped type variables, -- we can't derive an instance, so throw an error. when (any (`predMentionsName` droppedTyVarNames) dataCxt) $ datatypeContextError tyConName instanceType -- Also ensure the dropped types can be safely eta-reduced. Otherwise, -- throw an error. unless (canEtaReduce remainingTysExpSubst' droppedTysExpSubst) $ etaReductionError instanceType return (instanceCxt, instanceType) -- | Attempt to derive a constraint on a Type. If successful, return -- Just the constraint and any kind variable names constrained to *. -- Otherwise, return Nothing and the empty list. -- -- See Note [Type inference in derived instances] for the heuristics used to -- come up with constraints. deriveConstraint :: JSONClass -> Type -> (Maybe Pred, [Name]) deriveConstraint jc t | not (isTyVar t) = (Nothing, []) | hasKindStar t = (Just (applyCon (jcConstraint Arity0) tName), []) | otherwise = case hasKindVarChain 1 t of Just ns | jcArity >= Arity1 -> (Just (applyCon (jcConstraint Arity1) tName), ns) _ -> case hasKindVarChain 2 t of Just ns | jcArity == Arity2 -> (Just (applyCon (jcConstraint Arity2) tName), ns) _ -> (Nothing, []) where tName :: Name tName = varTToName t jcArity :: Arity jcArity = arity jc jcConstraint :: Arity -> Name jcConstraint = jsonClassName . JSONClass (direction jc) {- Note [Kind signatures in derived instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ It is possible to put explicit kind signatures into the derived instances, e.g., instance C a => C (Data (f :: * -> *)) where ... But it is preferable to avoid this if possible. If we come up with an incorrect kind signature (which is entirely possible, since Template Haskell doesn't always have the best track record with reifying kind signatures), then GHC will flat-out reject the instance, which is quite unfortunate. Plain old datatypes have the advantage that you can avoid using any kind signatures at all in their instances. This is because a datatype declaration uses all type variables, so the types that we use in a derived instance uniquely determine their kinds. As long as we plug in the right types, the kind inferencer can do the rest of the work. For this reason, we use unSigT to remove all kind signatures before splicing in the instance context and head. Data family instances are trickier, since a data family can have two instances that are distinguished by kind alone, e.g., data family Fam (a :: k) data instance Fam (a :: * -> *) data instance Fam (a :: *) If we dropped the kind signatures for C (Fam a), then GHC will have no way of knowing which instance we are talking about. To avoid this scenario, we always include explicit kind signatures in data family instances. There is a chance that the inferred kind signatures will be incorrect, but if so, we can always fall back on the mk- functions. Note [Type inference in derived instances] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Type inference is can be tricky to get right, and we want to avoid recreating the entirety of GHC's type inferencer in Template Haskell. For this reason, we will probably never come up with derived instance contexts that are as accurate as GHC's. But that doesn't mean we can't do anything! There are a couple of simple things we can do to make instance contexts that work for 80% of use cases: 1. If one of the last type parameters is polykinded, then its kind will be specialized to * in the derived instance. We note what kind variable the type parameter had and substitute it with * in the other types as well. For example, imagine you had data Data (a :: k) (b :: k) Then you'd want to derived instance to be: instance C (Data (a :: *)) Not: instance C (Data (a :: k)) 2. We naïvely come up with instance constraints using the following criteria: (i) If there's a type parameter n of kind *, generate a ToJSON n/FromJSON n constraint. (ii) If there's a type parameter n of kind k1 -> k2 (where k1/k2 are * or kind variables), then generate a ToJSON1 n/FromJSON1 n constraint, and if k1/k2 are kind variables, then substitute k1/k2 with * elsewhere in the types. We must consider the case where they are kind variables because you might have a scenario like this: newtype Compose (f :: k2 -> *) (g :: k1 -> k2) (a :: k1) = Compose (f (g a)) Which would have a derived ToJSON1 instance of: instance (ToJSON1 f, ToJSON1 g) => ToJSON1 (Compose f g) where ... (iii) If there's a type parameter n of kind k1 -> k2 -> k3 (where k1/k2/k3 are * or kind variables), then generate a ToJSON2 n/FromJSON2 n constraint and perform kind substitution as in the other cases. -} checkExistentialContext :: JSONClass -> TyVarMap -> Cxt -> Name -> Q a -> Q a checkExistentialContext jc tvMap ctxt conName q = if (any (`predMentionsName` M.keys tvMap) ctxt || M.size tvMap < arityInt jc) && not (allowExQuant jc) then existentialContextError conName else q {- Note [Matching functions with GADT type variables] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When deriving ToJSON2, there is a tricky corner case to consider: data Both a b where BothCon :: x -> x -> Both x x Which encoding functions should be applied to which arguments of BothCon? We have a choice, since both the function of type (a -> Value) and of type (b -> Value) can be applied to either argument. In such a scenario, the second encoding function takes precedence over the first encoding function, so the derived ToJSON2 instance would be something like: instance ToJSON2 Both where liftToJSON2 tj1 tj2 p (BothCon x1 x2) = Array $ create $ do mv <- unsafeNew 2 unsafeWrite mv 0 (tj1 x1) unsafeWrite mv 1 (tj2 x2) return mv This is not an arbitrary choice, as this definition ensures that liftToJSON2 toJSON = liftToJSON for a derived ToJSON1 instance for Both. -} -- A mapping of type variable Names to their encoding/decoding function Names. -- For example, in a ToJSON2 declaration, a TyVarMap might look like -- -- { a ~> (tj1, tjl1) -- , b ~> (tj2, tjl2) } -- -- where a and b are the last two type variables of the datatype, tj1 and tjl1 are -- the function arguments of types (a -> Value) and ([a] -> Value), and tj2 and tjl2 -- are the function arguments of types (b -> Value) and ([b] -> Value). type TyVarMap = Map Name (Name, Name) -- | Returns True if a Type has kind *. hasKindStar :: Type -> Bool hasKindStar VarT{} = True #if MIN_VERSION_template_haskell(2,8,0) hasKindStar (SigT _ StarT) = True #else hasKindStar (SigT _ StarK) = True #endif hasKindStar _ = False -- Returns True is a kind is equal to *, or if it is a kind variable. isStarOrVar :: Kind -> Bool #if MIN_VERSION_template_haskell(2,8,0) isStarOrVar StarT = True isStarOrVar VarT{} = True #else isStarOrVar StarK = True #endif isStarOrVar _ = False -- Generate a list of fresh names with a common prefix, and numbered suffixes. newNameList :: String -> Int -> Q [Name] newNameList prefix len = mapM newName [prefix ++ show n | n <- [1..len]] -- | @hasKindVarChain n kind@ Checks if @kind@ is of the form -- k_0 -> k_1 -> ... -> k_(n-1), where k0, k1, ..., and k_(n-1) can be * or -- kind variables. hasKindVarChain :: Int -> Type -> Maybe [Name] hasKindVarChain kindArrows t = let uk = uncurryKind (tyKind t) in if (NE.length uk - 1 == kindArrows) && F.all isStarOrVar uk then Just (concatMap freeVariables uk) else Nothing -- | If a Type is a SigT, returns its kind signature. Otherwise, return *. tyKind :: Type -> Kind tyKind (SigT _ k) = k tyKind _ = starK -- | Extract Just the Name from a type variable. If the argument Type is not a -- type variable, return Nothing. varTToNameMaybe :: Type -> Maybe Name varTToNameMaybe (VarT n) = Just n varTToNameMaybe (SigT t _) = varTToNameMaybe t varTToNameMaybe _ = Nothing -- | Extract the Name from a type variable. If the argument Type is not a -- type variable, throw an error. varTToName :: Type -> Name varTToName = fromMaybe (error "Not a type variable!") . varTToNameMaybe interleave :: [a] -> [a] -> [a] interleave (a1:a1s) (a2:a2s) = a1:a2:interleave a1s a2s interleave _ _ = [] -- | Fully applies a type constructor to its type variables. applyTyCon :: Name -> [Type] -> Type applyTyCon = foldl' AppT . ConT -- | Is the given type a variable? isTyVar :: Type -> Bool isTyVar (VarT _) = True isTyVar (SigT t _) = isTyVar t isTyVar _ = False -- | Is the given type a type family constructor (and not a data family constructor)? isTyFamily :: Type -> Q Bool isTyFamily (ConT n) = do info <- reify n return $ case info of #if MIN_VERSION_template_haskell(2,11,0) FamilyI OpenTypeFamilyD{} _ -> True #else FamilyI (FamilyD TypeFam _ _ _) _ -> True #endif #if MIN_VERSION_template_haskell(2,9,0) FamilyI ClosedTypeFamilyD{} _ -> True #endif _ -> False isTyFamily _ = return False -- | Peel off a kind signature from a Type (if it has one). unSigT :: Type -> Type unSigT (SigT t _) = t unSigT t = t -- | Are all of the items in a list (which have an ordering) distinct? -- -- This uses Set (as opposed to nub) for better asymptotic time complexity. allDistinct :: Ord a => [a] -> Bool allDistinct = allDistinct' Set.empty where allDistinct' :: Ord a => Set a -> [a] -> Bool allDistinct' uniqs (x:xs) | x `Set.member` uniqs = False | otherwise = allDistinct' (Set.insert x uniqs) xs allDistinct' _ _ = True -- | Does the given type mention any of the Names in the list? mentionsName :: Type -> [Name] -> Bool mentionsName = go where go :: Type -> [Name] -> Bool go (AppT t1 t2) names = go t1 names || go t2 names go (SigT t _k) names = go t names #if MIN_VERSION_template_haskell(2,8,0) || go _k names #endif go (VarT n) names = n `elem` names go _ _ = False -- | Does an instance predicate mention any of the Names in the list? predMentionsName :: Pred -> [Name] -> Bool #if MIN_VERSION_template_haskell(2,10,0) predMentionsName = mentionsName #else predMentionsName (ClassP n tys) names = n `elem` names || any (`mentionsName` names) tys predMentionsName (EqualP t1 t2) names = mentionsName t1 names || mentionsName t2 names #endif -- | Split an applied type into its individual components. For example, this: -- -- @ -- Either Int Char -- @ -- -- would split to this: -- -- @ -- [Either, Int, Char] -- @ unapplyTy :: Type -> NonEmpty Type unapplyTy = NE.reverse . go where go :: Type -> NonEmpty Type go (AppT t1 t2) = t2 <| go t1 go (SigT t _) = go t go (ForallT _ _ t) = go t go t = t :| [] -- | Split a type signature by the arrows on its spine. For example, this: -- -- @ -- forall a b. (a ~ b) => (a -> b) -> Char -> () -- @ -- -- would split to this: -- -- @ -- (a ~ b, [a -> b, Char, ()]) -- @ uncurryTy :: Type -> (Cxt, NonEmpty Type) uncurryTy (AppT (AppT ArrowT t1) t2) = let (ctxt, tys) = uncurryTy t2 in (ctxt, t1 <| tys) uncurryTy (SigT t _) = uncurryTy t uncurryTy (ForallT _ ctxt t) = let (ctxt', tys) = uncurryTy t in (ctxt ++ ctxt', tys) uncurryTy t = ([], t :| []) -- | Like uncurryType, except on a kind level. uncurryKind :: Kind -> NonEmpty Kind #if MIN_VERSION_template_haskell(2,8,0) uncurryKind = snd . uncurryTy #else uncurryKind (ArrowK k1 k2) = k1 <| uncurryKind k2 uncurryKind k = k :| [] #endif createKindChain :: Int -> Kind createKindChain = go starK where go :: Kind -> Int -> Kind go k 0 = k #if MIN_VERSION_template_haskell(2,8,0) go k !n = go (AppT (AppT ArrowT StarT) k) (n - 1) #else go k !n = go (ArrowK StarK k) (n - 1) #endif -- | Makes a string literal expression from a constructor's name. conNameExp :: Options -> ConstructorInfo -> Q Exp conNameExp opts = litE . stringL . constructorTagModifier opts . nameBase . constructorName -- | Extracts a record field label. fieldLabel :: Options -- ^ Encoding options -> Name -> String fieldLabel opts = fieldLabelModifier opts . nameBase -- | The name of the outermost 'Value' constructor. valueConName :: Value -> String valueConName (Object _) = "Object" valueConName (Array _) = "Array" valueConName (String _) = "String" valueConName (Number _) = "Number" valueConName (Bool _) = "Boolean" valueConName Null = "Null" applyCon :: Name -> Name -> Pred applyCon con t = #if MIN_VERSION_template_haskell(2,10,0) AppT (ConT con) (VarT t) #else ClassP con [VarT t] #endif -- | Checks to see if the last types in a data family instance can be safely eta- -- reduced (i.e., dropped), given the other types. This checks for three conditions: -- -- (1) All of the dropped types are type variables -- (2) All of the dropped types are distinct -- (3) None of the remaining types mention any of the dropped types canEtaReduce :: [Type] -> [Type] -> Bool canEtaReduce remaining dropped = all isTyVar dropped && allDistinct droppedNames -- Make sure not to pass something of type [Type], since Type -- didn't have an Ord instance until template-haskell-2.10.0.0 && not (any (`mentionsName` droppedNames) remaining) where droppedNames :: [Name] droppedNames = map varTToName dropped ------------------------------------------------------------------------------- -- Expanding type synonyms ------------------------------------------------------------------------------- applySubstitutionKind :: Map Name Kind -> Type -> Type #if MIN_VERSION_template_haskell(2,8,0) applySubstitutionKind = applySubstitution #else applySubstitutionKind _ t = t #endif substNameWithKind :: Name -> Kind -> Type -> Type substNameWithKind n k = applySubstitutionKind (M.singleton n k) substNamesWithKindStar :: [Name] -> Type -> Type substNamesWithKindStar ns t = foldr' (`substNameWithKind` starK) t ns ------------------------------------------------------------------------------- -- Error messages ------------------------------------------------------------------------------- -- | Either the given data type doesn't have enough type variables, or one of -- the type variables to be eta-reduced cannot realize kind *. derivingKindError :: JSONClass -> Name -> Q a derivingKindError jc tyConName = fail . showString "Cannot derive well-kinded instance of form ‘" . showString className . showChar ' ' . showParen True ( showString (nameBase tyConName) . showString " ..." ) . showString "‘\n\tClass " . showString className . showString " expects an argument of kind " . showString (pprint . createKindChain $ arityInt jc) $ "" where className :: String className = nameBase $ jsonClassName jc -- | One of the last type variables cannot be eta-reduced (see the canEtaReduce -- function for the criteria it would have to meet). etaReductionError :: Type -> Q a etaReductionError instanceType = fail $ "Cannot eta-reduce to an instance of form \n\tinstance (...) => " ++ pprint instanceType -- | The data type has a DatatypeContext which mentions one of the eta-reduced -- type variables. datatypeContextError :: Name -> Type -> Q a datatypeContextError dataName instanceType = fail . showString "Can't make a derived instance of ‘" . showString (pprint instanceType) . showString "‘:\n\tData type ‘" . showString (nameBase dataName) . showString "‘ must not have a class context involving the last type argument(s)" $ "" -- | The data type mentions one of the n eta-reduced type variables in a place other -- than the last nth positions of a data type in a constructor's field. outOfPlaceTyVarError :: JSONClass -> Name -> a outOfPlaceTyVarError jc conName = error . showString "Constructor ‘" . showString (nameBase conName) . showString "‘ must only use its last " . shows n . showString " type variable(s) within the last " . shows n . showString " argument(s) of a data type" $ "" where n :: Int n = arityInt jc -- | The data type has an existential constraint which mentions one of the -- eta-reduced type variables. existentialContextError :: Name -> a existentialContextError conName = error . showString "Constructor ‘" . showString (nameBase conName) . showString "‘ must be truly polymorphic in the last argument(s) of the data type" $ "" ------------------------------------------------------------------------------- -- Class-specific constants ------------------------------------------------------------------------------- -- | A representation of the arity of the ToJSON/FromJSON typeclass being derived. data Arity = Arity0 | Arity1 | Arity2 deriving (Enum, Eq, Ord) -- | Whether ToJSON(1)(2) or FromJSON(1)(2) is being derived. data Direction = To | From -- | A representation of which typeclass method is being spliced in. data JSONFun = ToJSON | ToEncoding | ParseJSON -- | A refinement of JSONFun to [ToJSON, ToEncoding]. data ToJSONFun = Value | Encoding targetToJSONFun :: ToJSONFun -> JSONFun targetToJSONFun Value = ToJSON targetToJSONFun Encoding = ToEncoding -- | A representation of which typeclass is being derived. data JSONClass = JSONClass { direction :: Direction, arity :: Arity } toJSONClass, toJSON1Class, toJSON2Class, fromJSONClass, fromJSON1Class, fromJSON2Class :: JSONClass toJSONClass = JSONClass To Arity0 toJSON1Class = JSONClass To Arity1 toJSON2Class = JSONClass To Arity2 fromJSONClass = JSONClass From Arity0 fromJSON1Class = JSONClass From Arity1 fromJSON2Class = JSONClass From Arity2 jsonClassName :: JSONClass -> Name jsonClassName (JSONClass To Arity0) = ''ToJSON jsonClassName (JSONClass To Arity1) = ''ToJSON1 jsonClassName (JSONClass To Arity2) = ''ToJSON2 jsonClassName (JSONClass From Arity0) = ''FromJSON jsonClassName (JSONClass From Arity1) = ''FromJSON1 jsonClassName (JSONClass From Arity2) = ''FromJSON2 jsonFunValName :: JSONFun -> Arity -> Name jsonFunValName ToJSON Arity0 = 'toJSON jsonFunValName ToJSON Arity1 = 'liftToJSON jsonFunValName ToJSON Arity2 = 'liftToJSON2 jsonFunValName ToEncoding Arity0 = 'toEncoding jsonFunValName ToEncoding Arity1 = 'liftToEncoding jsonFunValName ToEncoding Arity2 = 'liftToEncoding2 jsonFunValName ParseJSON Arity0 = 'parseJSON jsonFunValName ParseJSON Arity1 = 'liftParseJSON jsonFunValName ParseJSON Arity2 = 'liftParseJSON2 jsonFunListName :: JSONFun -> Arity -> Name jsonFunListName ToJSON Arity0 = 'toJSONList jsonFunListName ToJSON Arity1 = 'liftToJSONList jsonFunListName ToJSON Arity2 = 'liftToJSONList2 jsonFunListName ToEncoding Arity0 = 'toEncodingList jsonFunListName ToEncoding Arity1 = 'liftToEncodingList jsonFunListName ToEncoding Arity2 = 'liftToEncodingList2 jsonFunListName ParseJSON Arity0 = 'parseJSONList jsonFunListName ParseJSON Arity1 = 'liftParseJSONList jsonFunListName ParseJSON Arity2 = 'liftParseJSONList2 jsonFunValOrListName :: Bool -- e.g., toJSONList if True, toJSON if False -> JSONFun -> Arity -> Name jsonFunValOrListName False = jsonFunValName jsonFunValOrListName True = jsonFunListName arityInt :: JSONClass -> Int arityInt = fromEnum . arity allowExQuant :: JSONClass -> Bool allowExQuant (JSONClass To _) = True allowExQuant _ = False ------------------------------------------------------------------------------- -- StarKindStatus ------------------------------------------------------------------------------- -- | Whether a type is not of kind *, is of kind *, or is a kind variable. data StarKindStatus = NotKindStar | KindStar | IsKindVar Name deriving Eq -- | Does a Type have kind * or k (for some kind variable k)? canRealizeKindStar :: Type -> StarKindStatus canRealizeKindStar t = case t of _ | hasKindStar t -> KindStar #if MIN_VERSION_template_haskell(2,8,0) SigT _ (VarT k) -> IsKindVar k #endif _ -> NotKindStar -- | Returns 'Just' the kind variable 'Name' of a 'StarKindStatus' if it exists. -- Otherwise, returns 'Nothing'. starKindStatusToName :: StarKindStatus -> Maybe Name starKindStatusToName (IsKindVar n) = Just n starKindStatusToName _ = Nothing -- | Concat together all of the StarKindStatuses that are IsKindVar and extract -- the kind variables' Names out. catKindVarNames :: [StarKindStatus] -> [Name] catKindVarNames = mapMaybe starKindStatusToName aeson-1.4.2.0/Data/Aeson/Text.hs0000644000000000000000000000700200000000000014305 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} -- | -- Module: Data.Aeson.Text -- Copyright: (c) 2012-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Most frequently, you'll probably want to encode straight to UTF-8 -- (the standard JSON encoding) using 'encode'. -- -- You can use the conversions to 'Builder's when embedding JSON messages as -- parts of a protocol. module Data.Aeson.Text ( encodeToLazyText , encodeToTextBuilder ) where import Prelude.Compat import Data.Aeson.Types (Value(..), ToJSON(..)) import Data.Aeson.Encoding (encodingToLazyByteString) import Data.Semigroup ((<>)) import Data.Scientific (FPFormat(..), Scientific, base10Exponent) import Data.Text.Lazy.Builder import Data.Text.Lazy.Builder.Scientific (formatScientificBuilder) import Numeric (showHex) import qualified Data.HashMap.Strict as H import qualified Data.Text as T import qualified Data.Text.Lazy as LT import qualified Data.Text.Lazy.Encoding as LT import qualified Data.Vector as V -- | Encode a JSON 'Value' to a "Data.Text.Lazy" -- -- /Note:/ uses 'toEncoding' encodeToLazyText :: ToJSON a => a -> LT.Text encodeToLazyText = LT.decodeUtf8 . encodingToLazyByteString . toEncoding -- | Encode a JSON 'Value' to a "Data.Text" 'Builder', which can be -- embedded efficiently in a text-based protocol. -- -- If you are going to immediately encode straight to a -- 'L.ByteString', it is more efficient to use 'encode' (lazy ByteString) -- or @'fromEncoding' . 'toEncoding'@ (ByteString.Builder) instead. -- -- /Note:/ Uses 'toJSON' encodeToTextBuilder :: ToJSON a => a -> Builder encodeToTextBuilder = go . toJSON where go Null = {-# SCC "go/Null" #-} "null" go (Bool b) = {-# SCC "go/Bool" #-} if b then "true" else "false" go (Number s) = {-# SCC "go/Number" #-} fromScientific s go (String s) = {-# SCC "go/String" #-} string s go (Array v) | V.null v = {-# SCC "go/Array" #-} "[]" | otherwise = {-# SCC "go/Array" #-} singleton '[' <> go (V.unsafeHead v) <> V.foldr f (singleton ']') (V.unsafeTail v) where f a z = singleton ',' <> go a <> z go (Object m) = {-# SCC "go/Object" #-} case H.toList m of (x:xs) -> singleton '{' <> one x <> foldr f (singleton '}') xs _ -> "{}" where f a z = singleton ',' <> one a <> z one (k,v) = string k <> singleton ':' <> go v string :: T.Text -> Builder string s = {-# SCC "string" #-} singleton '"' <> quote s <> singleton '"' where quote q = case T.uncons t of Nothing -> fromText h Just (!c,t') -> fromText h <> escape c <> quote t' where (h,t) = {-# SCC "break" #-} T.break isEscape q isEscape c = c == '\"' || c == '\\' || c < '\x20' escape '\"' = "\\\"" escape '\\' = "\\\\" escape '\n' = "\\n" escape '\r' = "\\r" escape '\t' = "\\t" escape c | c < '\x20' = fromString $ "\\u" ++ replicate (4 - length h) '0' ++ h | otherwise = singleton c where h = showHex (fromEnum c) "" fromScientific :: Scientific -> Builder fromScientific s = formatScientificBuilder format prec s where (format, prec) | base10Exponent s < 0 = (Generic, Nothing) | otherwise = (Fixed, Just 0) aeson-1.4.2.0/Data/Aeson/Types.hs0000644000000000000000000000557500000000000014502 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} -- | -- Module: Data.Aeson.Types -- Copyright: (c) 2011-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Types for working with JSON data. module Data.Aeson.Types ( -- * Core JSON types Value(..) , Encoding , unsafeToEncoding , fromEncoding , Series , Array , emptyArray , Pair , Object , emptyObject -- * Convenience types and functions , DotNetTime(..) , typeMismatch -- * Type conversion , Parser , Result(..) , FromJSON(..) , fromJSON , parse , parseEither , parseMaybe , ToJSON(..) , KeyValue(..) , modifyFailure , parserThrowError , parserCatchError -- ** Keys for maps , ToJSONKey(..) , ToJSONKeyFunction(..) , toJSONKeyText , contramapToJSONKeyFunction , FromJSONKey(..) , FromJSONKeyFunction(..) , fromJSONKeyCoerce , coerceFromJSONKeyFunction , mapFromJSONKeyFunction -- ** Liftings to unary and binary type constructors , FromJSON1(..) , parseJSON1 , FromJSON2(..) , parseJSON2 , ToJSON1(..) , toJSON1 , toEncoding1 , ToJSON2(..) , toJSON2 , toEncoding2 -- ** Generic JSON classes , GFromJSON(..) , FromArgs(..) , GToJSON , GToEncoding , ToArgs(..) , Zero , One , genericToJSON , genericLiftToJSON , genericToEncoding , genericLiftToEncoding , genericParseJSON , genericLiftParseJSON -- * Inspecting @'Value's@ , withObject , withText , withArray , withScientific , withBool , withEmbeddedJSON , pairs , foldable , (.:) , (.:?) , (.:!) , (.!=) , object , parseField , parseFieldMaybe , parseFieldMaybe' , explicitParseField , explicitParseFieldMaybe , explicitParseFieldMaybe' , listEncoding , listValue , listParser -- * Generic and TH encoding configuration , Options -- ** Options fields -- $optionsFields , fieldLabelModifier , constructorTagModifier , allNullaryToStringTag , omitNothingFields , sumEncoding , unwrapUnaryRecords , tagSingleConstructors -- ** Options utilities , SumEncoding(..) , camelTo , camelTo2 , defaultOptions , defaultTaggedObject ) where import Prelude.Compat import Data.Aeson.Encoding (Encoding, unsafeToEncoding, fromEncoding, Series, pairs) import Data.Aeson.Types.Class import Data.Aeson.Types.Internal import Data.Foldable (toList) -- | Encode a 'Foldable' as a JSON array. foldable :: (Foldable t, ToJSON a) => t a -> Encoding foldable = toEncoding . toList {-# INLINE foldable #-} -- $optionsFields -- The functions here are in fact record fields of the 'Options' type. aeson-1.4.2.0/Data/Aeson/Types/0000755000000000000000000000000000000000000014132 5ustar0000000000000000aeson-1.4.2.0/Data/Aeson/Types/Class.hs0000644000000000000000000000453000000000000015535 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeSynonymInstances #-} -- | -- Module: Data.Aeson.Types.Class -- Copyright: (c) 2011-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Types for working with JSON data. module Data.Aeson.Types.Class ( -- * Core JSON classes FromJSON(..) , ToJSON(..) -- * Liftings to unary and binary type constructors , FromJSON1(..) , parseJSON1 , FromJSON2(..) , parseJSON2 , ToJSON1(..) , toJSON1 , toEncoding1 , ToJSON2(..) , toJSON2 , toEncoding2 -- * Generic JSON classes , GFromJSON(..) , FromArgs(..) , GToJSON , GToEncoding , ToArgs(..) , Zero , One , genericToJSON , genericLiftToJSON , genericToEncoding , genericLiftToEncoding , genericParseJSON , genericLiftParseJSON -- * Classes and types for map keys , ToJSONKey(..) , ToJSONKeyFunction(..) , toJSONKeyText , contramapToJSONKeyFunction , FromJSONKey(..) , FromJSONKeyFunction(..) , fromJSONKeyCoerce , coerceFromJSONKeyFunction , mapFromJSONKeyFunction -- * Object key-value pairs , KeyValue(..) -- * List functions , listEncoding , listValue , listParser -- * Inspecting @'Value's@ , withObject , withText , withArray , withScientific , withBool , withEmbeddedJSON -- * Functions , fromJSON , ifromJSON , typeMismatch , parseField , parseFieldMaybe , parseFieldMaybe' , explicitParseField , explicitParseFieldMaybe , explicitParseFieldMaybe' -- ** Operators , (.:) , (.:?) , (.:!) , (.!=) ) where import Data.Aeson.Types.FromJSON import Data.Aeson.Types.Generic (One, Zero) import Data.Aeson.Types.ToJSON hiding (GToJSON) import qualified Data.Aeson.Types.ToJSON as ToJSON import Data.Aeson.Types.Internal (Value) import Data.Aeson.Encoding (Encoding) type GToJSON = ToJSON.GToJSON Value type GToEncoding = ToJSON.GToJSON Encoding aeson-1.4.2.0/Data/Aeson/Types/FromJSON.hs0000644000000000000000000026225600000000000016100 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ViewPatterns #-} #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE PolyKinds #-} #endif #include "incoherent-compat.h" #include "overlapping-compat.h" -- TODO: Drop this when we remove support for Data.Attoparsec.Number {-# OPTIONS_GHC -fno-warn-deprecations #-} module Data.Aeson.Types.FromJSON ( -- * Core JSON classes FromJSON(..) -- * Liftings to unary and binary type constructors , FromJSON1(..) , parseJSON1 , FromJSON2(..) , parseJSON2 -- * Generic JSON classes , GFromJSON(..) , FromArgs(..) , genericParseJSON , genericLiftParseJSON -- * Classes and types for map keys , FromJSONKey(..) , FromJSONKeyFunction(..) , fromJSONKeyCoerce , coerceFromJSONKeyFunction , mapFromJSONKeyFunction -- * List functions , listParser -- * Inspecting @'Value's@ , withObject , withText , withArray , withScientific , withBool , withEmbeddedJSON -- * Functions , fromJSON , ifromJSON , typeMismatch , parseField , parseFieldMaybe , parseFieldMaybe' , explicitParseField , explicitParseFieldMaybe , explicitParseFieldMaybe' -- ** Operators , (.:) , (.:?) , (.:!) , (.!=) -- * Internal , parseOptionalFieldWith ) where import Prelude.Compat import Control.Applicative ((<|>), Const(..)) import Control.Monad ((<=<), zipWithM) import Data.Aeson.Internal.Functions (mapKey) import Data.Aeson.Parser.Internal (eitherDecodeWith, jsonEOF) import Data.Aeson.Types.Generic import Data.Aeson.Types.Internal import Data.Bits (unsafeShiftR) import Data.Fixed (Fixed, HasResolution) import Data.Functor.Compose (Compose(..)) import Data.Functor.Identity (Identity(..)) import Data.Functor.Product (Product(..)) import Data.Functor.Sum (Sum(..)) import Data.Hashable (Hashable(..)) import Data.Int (Int16, Int32, Int64, Int8) import Data.List.NonEmpty (NonEmpty(..)) import Data.Maybe (fromMaybe) import Data.Semigroup ((<>)) import Data.Proxy (Proxy(..)) import Data.Ratio ((%), Ratio) import Data.Scientific (Scientific, base10Exponent) import Data.Tagged (Tagged(..)) import Data.Text (Text, pack, unpack) import Data.Time (Day, DiffTime, LocalTime, NominalDiffTime, TimeOfDay, UTCTime, ZonedTime) import Data.Time.Format (parseTime) import Data.Time.Locale.Compat (defaultTimeLocale) import Data.Traversable as Tr (sequence) import Data.Vector (Vector) import Data.Version (Version, parseVersion) import Data.Void (Void) import Data.Word (Word16, Word32, Word64, Word8) import Foreign.Storable (Storable) import Foreign.C.Types (CTime (..)) import GHC.Generics import Numeric.Natural (Natural) import Text.ParserCombinators.ReadP (readP_to_S) import Unsafe.Coerce (unsafeCoerce) import qualified Data.Aeson.Compat as Compat import qualified Data.Aeson.Parser.Time as Time import qualified Data.Attoparsec.ByteString.Char8 as A (endOfInput, parseOnly, scientific) import qualified Data.DList as DList import qualified Data.HashMap.Strict as H import qualified Data.HashSet as HashSet import qualified Data.IntMap as IntMap import qualified Data.IntSet as IntSet import qualified Data.Map as M import qualified Data.Monoid as Monoid import qualified Data.Scientific as Scientific import qualified Data.Semigroup as Semigroup import qualified Data.Sequence as Seq import qualified Data.Set as Set import qualified Data.Text as T import qualified Data.Text.Encoding as T import qualified Data.Text.Lazy as LT import qualified Data.Tree as Tree import qualified Data.UUID.Types as UUID import qualified Data.Vector as V import qualified Data.Vector.Generic as VG import qualified Data.Vector.Primitive as VP import qualified Data.Vector.Storable as VS import qualified Data.Vector.Unboxed as VU import qualified GHC.Exts as Exts import qualified Data.Primitive.Array as PM import qualified Data.Primitive.SmallArray as PM import qualified Data.Primitive.Types as PM #if MIN_VERSION_primitive(0,6,4) import qualified Data.Primitive.UnliftedArray as PM import qualified Data.Primitive.PrimArray as PM #endif #ifndef HAS_COERCIBLE #define HAS_COERCIBLE (__GLASGOW_HASKELL__ >= 707) #endif #if HAS_COERCIBLE import Data.Coerce (Coercible, coerce) coerce' :: Coercible a b => a -> b coerce' = coerce #else coerce' :: a -> b coerce' = unsafeCoerce #endif parseIndexedJSON :: (Value -> Parser a) -> Int -> Value -> Parser a parseIndexedJSON p idx value = p value Index idx {-# INLINE parseIndexedJSON #-} parseIndexedJSONPair :: (Value -> Parser a) -> (Value -> Parser b) -> Int -> Value -> Parser (a, b) parseIndexedJSONPair keyParser valParser idx value = p value Index idx where p = withArray "(k,v)" $ \ab -> let n = V.length ab in if n == 2 then (,) <$> parseJSONElemAtIndex keyParser 0 ab <*> parseJSONElemAtIndex valParser 1 ab else fail $ "cannot unpack array of length " ++ show n ++ " into a pair" {-# INLINE parseIndexedJSONPair #-} parseJSONElemAtIndex :: (Value -> Parser a) -> Int -> V.Vector Value -> Parser a parseJSONElemAtIndex p idx ary = p (V.unsafeIndex ary idx) Index idx parseRealFloat :: RealFloat a => String -> Value -> Parser a parseRealFloat _ (Number s) = pure $ Scientific.toRealFloat s parseRealFloat _ Null = pure (0/0) parseRealFloat expected v = typeMismatch expected v {-# INLINE parseRealFloat #-} parseIntegralFromScientific :: forall a. Integral a => String -> Scientific -> Parser a parseIntegralFromScientific expected s = case Scientific.floatingOrInteger s :: Either Double a of Right x -> pure x Left _ -> fail $ "expected " ++ expected ++ ", encountered floating number " ++ show s {-# INLINE parseIntegralFromScientific #-} parseIntegral :: Integral a => String -> Value -> Parser a parseIntegral expected = withBoundedScientific expected $ parseIntegralFromScientific expected {-# INLINE parseIntegral #-} parseBoundedIntegralFromScientific :: (Bounded a, Integral a) => String -> Scientific -> Parser a parseBoundedIntegralFromScientific expected s = maybe (fail $ expected ++ " is either floating or will cause over or underflow: " ++ show s) pure (Scientific.toBoundedInteger s) {-# INLINE parseBoundedIntegralFromScientific #-} parseBoundedIntegral :: (Bounded a, Integral a) => String -> Value -> Parser a parseBoundedIntegral expected = withScientific expected $ parseBoundedIntegralFromScientific expected {-# INLINE parseBoundedIntegral #-} parseScientificText :: Text -> Parser Scientific parseScientificText = either fail pure . A.parseOnly (A.scientific <* A.endOfInput) . T.encodeUtf8 parseIntegralText :: Integral a => String -> Text -> Parser a parseIntegralText expected t = parseScientificText t >>= rejectLargeExponent >>= parseIntegralFromScientific expected where rejectLargeExponent :: Scientific -> Parser Scientific rejectLargeExponent s = withBoundedScientific expected pure (Number s) {-# INLINE parseIntegralText #-} parseBoundedIntegralText :: (Bounded a, Integral a) => String -> Text -> Parser a parseBoundedIntegralText expected t = parseScientificText t >>= parseBoundedIntegralFromScientific expected parseOptionalFieldWith :: (Value -> Parser (Maybe a)) -> Object -> Text -> Parser (Maybe a) parseOptionalFieldWith pj obj key = case H.lookup key obj of Nothing -> pure Nothing Just v -> pj v Key key {-# INLINE parseOptionalFieldWith #-} ------------------------------------------------------------------------------- -- Generics ------------------------------------------------------------------------------- -- | Class of generic representation types that can be converted from JSON. class GFromJSON arity f where -- | This method (applied to 'defaultOptions') is used as the -- default generic implementation of 'parseJSON' (if the @arity@ is 'Zero') -- or 'liftParseJSON' (if the @arity@ is 'One'). gParseJSON :: Options -> FromArgs arity a -> Value -> Parser (f a) -- | A 'FromArgs' value either stores nothing (for 'FromJSON') or it stores the -- two function arguments that decode occurrences of the type parameter (for -- 'FromJSON1'). data FromArgs arity a where NoFromArgs :: FromArgs Zero a From1Args :: (Value -> Parser a) -> (Value -> Parser [a]) -> FromArgs One a -- | A configurable generic JSON decoder. This function applied to -- 'defaultOptions' is used as the default for 'parseJSON' when the -- type is an instance of 'Generic'. genericParseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Options -> Value -> Parser a genericParseJSON opts = fmap to . gParseJSON opts NoFromArgs -- | A configurable generic JSON decoder. This function applied to -- 'defaultOptions' is used as the default for 'liftParseJSON' when the -- type is an instance of 'Generic1'. genericLiftParseJSON :: (Generic1 f, GFromJSON One (Rep1 f)) => Options -> (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) genericLiftParseJSON opts pj pjl = fmap to1 . gParseJSON opts (From1Args pj pjl) ------------------------------------------------------------------------------- -- Class ------------------------------------------------------------------------------- -- | A type that can be converted from JSON, with the possibility of -- failure. -- -- In many cases, you can get the compiler to generate parsing code -- for you (see below). To begin, let's cover writing an instance by -- hand. -- -- There are various reasons a conversion could fail. For example, an -- 'Object' could be missing a required key, an 'Array' could be of -- the wrong size, or a value could be of an incompatible type. -- -- The basic ways to signal a failed conversion are as follows: -- -- * 'empty' and 'mzero' work, but are terse and uninformative; -- -- * 'fail' yields a custom error message; -- -- * 'typeMismatch' produces an informative message for cases when the -- value encountered is not of the expected type. -- -- An example type and instance using 'typeMismatch': -- -- @ -- \-- Allow ourselves to write 'Text' literals. -- {-\# LANGUAGE OverloadedStrings #-} -- -- data Coord = Coord { x :: Double, y :: Double } -- -- instance 'FromJSON' Coord where -- 'parseJSON' ('Object' v) = Coord -- '<$>' v '.:' \"x\" -- '<*>' v '.:' \"y\" -- -- \-- We do not expect a non-'Object' value here. -- \-- We could use 'mzero' to fail, but 'typeMismatch' -- \-- gives a much more informative error message. -- 'parseJSON' invalid = 'typeMismatch' \"Coord\" invalid -- @ -- -- For this common case of only being concerned with a single -- type of JSON value, the functions 'withObject', 'withNumber', etc. -- are provided. Their use is to be preferred when possible, since -- they are more terse. Using 'withObject', we can rewrite the above instance -- (assuming the same language extension and data type) as: -- -- @ -- instance 'FromJSON' Coord where -- 'parseJSON' = 'withObject' \"Coord\" $ \\v -> Coord -- '<$>' v '.:' \"x\" -- '<*>' v '.:' \"y\" -- @ -- -- Instead of manually writing your 'FromJSON' instance, there are two options -- to do it automatically: -- -- * "Data.Aeson.TH" provides Template Haskell functions which will derive an -- instance at compile time. The generated instance is optimized for your type -- so it will probably be more efficient than the following option. -- -- * The compiler can provide a default generic implementation for -- 'parseJSON'. -- -- To use the second, simply add a @deriving 'Generic'@ clause to your -- datatype and declare a 'FromJSON' instance for your datatype without giving -- a definition for 'parseJSON'. -- -- For example, the previous example can be simplified to just: -- -- @ -- {-\# LANGUAGE DeriveGeneric \#-} -- -- import "GHC.Generics" -- -- data Coord = Coord { x :: Double, y :: Double } deriving 'Generic' -- -- instance 'FromJSON' Coord -- @ -- -- The default implementation will be equivalent to -- @parseJSON = 'genericParseJSON' 'defaultOptions'@; If you need different -- options, you can customize the generic decoding by defining: -- -- @ -- customOptions = 'defaultOptions' -- { 'fieldLabelModifier' = 'map' 'Data.Char.toUpper' -- } -- -- instance 'FromJSON' Coord where -- 'parseJSON' = 'genericParseJSON' customOptions -- @ class FromJSON a where parseJSON :: Value -> Parser a default parseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a parseJSON = genericParseJSON defaultOptions parseJSONList :: Value -> Parser [a] parseJSONList (Array a) = zipWithM (parseIndexedJSON parseJSON) [0..] . V.toList $ a parseJSONList v = typeMismatch "[a]" v ------------------------------------------------------------------------------- -- Classes and types for map keys ------------------------------------------------------------------------------- -- | Read the docs for 'ToJSONKey' first. This class is a conversion -- in the opposite direction. If you have a newtype wrapper around 'Text', -- the recommended way to define instances is with generalized newtype deriving: -- -- > newtype SomeId = SomeId { getSomeId :: Text } -- > deriving (Eq,Ord,Hashable,FromJSONKey) -- class FromJSONKey a where -- | Strategy for parsing the key of a map-like container. fromJSONKey :: FromJSONKeyFunction a default fromJSONKey :: FromJSON a => FromJSONKeyFunction a fromJSONKey = FromJSONKeyValue parseJSON -- | This is similar in spirit to the 'readList' method of 'Read'. -- It makes it possible to give 'String' keys special treatment -- without using @OverlappingInstances@. End users should always -- be able to use the default implementation of this method. fromJSONKeyList :: FromJSONKeyFunction [a] default fromJSONKeyList :: FromJSON a => FromJSONKeyFunction [a] fromJSONKeyList = FromJSONKeyValue parseJSON -- | With GHC 7.8+ we carry around @'Coercible' 'Text' a@ dictionary, -- to give us an assurance that the program will not segfault. -- Unfortunately we cannot enforce that the 'Eq' instances or the -- 'Hashable' instances for 'Text' and @a@ agree. -- -- At the moment this type is intentionally not exported. 'FromJSONKeyFunction' -- can be inspected, but cannot be constructed. data CoerceText a where #if HAS_COERCIBLE CoerceText :: Coercible Text a => CoerceText a #else CoerceText :: CoerceText a #endif -- | This type is related to 'ToJSONKeyFunction'. If 'FromJSONKeyValue' is used in the -- 'FromJSONKey' instance, then 'ToJSONKeyValue' should be used in the 'ToJSONKey' -- instance. The other three data constructors for this type all correspond to -- 'ToJSONKeyText'. Strictly speaking, 'FromJSONKeyTextParser' is more powerful than -- 'FromJSONKeyText', which is in turn more powerful than 'FromJSONKeyCoerce'. -- For performance reasons, these exist as three options instead of one. data FromJSONKeyFunction a = FromJSONKeyCoerce !(CoerceText a) -- ^ uses 'coerce' ('unsafeCoerce' in older GHCs) | FromJSONKeyText !(Text -> a) -- ^ conversion from 'Text' that always succeeds | FromJSONKeyTextParser !(Text -> Parser a) -- ^ conversion from 'Text' that may fail | FromJSONKeyValue !(Value -> Parser a) -- ^ conversion for non-textual keys -- | Only law abiding up to interpretation instance Functor FromJSONKeyFunction where fmap h (FromJSONKeyCoerce CoerceText) = FromJSONKeyText (h . coerce') fmap h (FromJSONKeyText f) = FromJSONKeyText (h . f) fmap h (FromJSONKeyTextParser f) = FromJSONKeyTextParser (fmap h . f) fmap h (FromJSONKeyValue f) = FromJSONKeyValue (fmap h . f) -- | Construct 'FromJSONKeyFunction' for types coercible from 'Text'. This -- conversion is still unsafe, as 'Hashable' and 'Eq' instances of @a@ should be -- compatible with 'Text' i.e. hash values should be equal for wrapped values as well. -- This property will always be maintained if the 'Hashable' and 'Eq' instances -- are derived with generalized newtype deriving. -- compatible with 'Text' i.e. hash values be equal for wrapped values as well. -- -- On pre GHC 7.8 this is unconstrainted function. fromJSONKeyCoerce :: #if HAS_COERCIBLE Coercible Text a => #endif FromJSONKeyFunction a fromJSONKeyCoerce = FromJSONKeyCoerce CoerceText -- | Semantically the same as @coerceFromJSONKeyFunction = fmap coerce = coerce@. -- -- See note on 'fromJSONKeyCoerce'. coerceFromJSONKeyFunction :: #if HAS_COERCIBLE Coercible a b => #endif FromJSONKeyFunction a -> FromJSONKeyFunction b #if HAS_COERCIBLE coerceFromJSONKeyFunction = coerce #else coerceFromJSONKeyFunction (FromJSONKeyCoerce CoerceText) = FromJSONKeyCoerce CoerceText coerceFromJSONKeyFunction (FromJSONKeyText f) = FromJSONKeyText (coerce' . f) coerceFromJSONKeyFunction (FromJSONKeyTextParser f) = FromJSONKeyTextParser (fmap coerce' . f) coerceFromJSONKeyFunction (FromJSONKeyValue f) = FromJSONKeyValue (fmap coerce' . f) #endif {-# RULES "FromJSONKeyCoerce: fmap id" forall (x :: FromJSONKeyFunction a). fmap id x = x #-} #if HAS_COERCIBLE {-# RULES "FromJSONKeyCoerce: fmap coerce" forall x . fmap coerce x = coerceFromJSONKeyFunction x #-} #endif -- | Same as 'fmap'. Provided for the consistency with 'ToJSONKeyFunction'. mapFromJSONKeyFunction :: (a -> b) -> FromJSONKeyFunction a -> FromJSONKeyFunction b mapFromJSONKeyFunction = fmap ------------------------------------------------------------------------------- -- Functions needed for documentation ------------------------------------------------------------------------------- -- | Fail parsing due to a type mismatch, with a descriptive message. -- -- Example usage: -- -- @ -- instance FromJSON Coord where -- parseJSON ('Object' v) = {- type matches, life is good -} -- parseJSON wat = 'typeMismatch' \"Coord\" wat -- @ typeMismatch :: String -- ^ The name of the type you are trying to parse. -> Value -- ^ The actual value encountered. -> Parser a typeMismatch expected actual = fail $ "expected " ++ expected ++ ", encountered " ++ name where name = case actual of Object _ -> "Object" Array _ -> "Array" String _ -> "String" Number _ -> "Number" Bool _ -> "Boolean" Null -> "Null" ------------------------------------------------------------------------------- -- Lifings of FromJSON and ToJSON to unary and binary type constructors ------------------------------------------------------------------------------- -- | Lifting of the 'FromJSON' class to unary type constructors. -- -- Instead of manually writing your 'FromJSON1' instance, there are two options -- to do it automatically: -- -- * "Data.Aeson.TH" provides Template Haskell functions which will derive an -- instance at compile time. The generated instance is optimized for your type -- so it will probably be more efficient than the following option. -- -- * The compiler can provide a default generic implementation for -- 'liftParseJSON'. -- -- To use the second, simply add a @deriving 'Generic1'@ clause to your -- datatype and declare a 'FromJSON1' instance for your datatype without giving -- a definition for 'liftParseJSON'. -- -- For example: -- -- @ -- {-\# LANGUAGE DeriveGeneric \#-} -- -- import "GHC.Generics" -- -- data Pair a b = Pair { pairFst :: a, pairSnd :: b } deriving 'Generic1' -- -- instance 'FromJSON' a => 'FromJSON1' (Pair a) -- @ -- -- If the default implementation doesn't give exactly the results you want, -- you can customize the generic decoding with only a tiny amount of -- effort, using 'genericLiftParseJSON' with your preferred 'Options': -- -- @ -- customOptions = 'defaultOptions' -- { 'fieldLabelModifier' = 'map' 'Data.Char.toUpper' -- } -- -- instance 'FromJSON' a => 'FromJSON1' (Pair a) where -- 'liftParseJSON' = 'genericLiftParseJSON' customOptions -- @ class FromJSON1 f where liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) default liftParseJSON :: (Generic1 f, GFromJSON One (Rep1 f)) => (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) liftParseJSON = genericLiftParseJSON defaultOptions liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [f a] liftParseJSONList f g v = listParser (liftParseJSON f g) v -- | Lift the standard 'parseJSON' function through the type constructor. parseJSON1 :: (FromJSON1 f, FromJSON a) => Value -> Parser (f a) parseJSON1 = liftParseJSON parseJSON parseJSONList {-# INLINE parseJSON1 #-} -- | Lifting of the 'FromJSON' class to binary type constructors. -- -- Instead of manually writing your 'FromJSON2' instance, "Data.Aeson.TH" -- provides Template Haskell functions which will derive an instance at compile time. -- The compiler cannot provide a default generic implementation for 'liftParseJSON2', -- unlike 'parseJSON' and 'liftParseJSON'. class FromJSON2 f where liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (f a b) liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [f a b] liftParseJSONList2 fa ga fb gb v = case v of Array vals -> fmap V.toList (V.mapM (liftParseJSON2 fa ga fb gb) vals) _ -> typeMismatch "[a]" v -- | Lift the standard 'parseJSON' function through the type constructor. parseJSON2 :: (FromJSON2 f, FromJSON a, FromJSON b) => Value -> Parser (f a b) parseJSON2 = liftParseJSON2 parseJSON parseJSONList parseJSON parseJSONList {-# INLINE parseJSON2 #-} ------------------------------------------------------------------------------- -- List functions ------------------------------------------------------------------------------- -- | Helper function to use with 'liftParseJSON'. See 'Data.Aeson.ToJSON.listEncoding'. listParser :: (Value -> Parser a) -> Value -> Parser [a] listParser f (Array xs) = fmap V.toList (V.mapM f xs) listParser _ v = typeMismatch "[a]" v {-# INLINE listParser #-} ------------------------------------------------------------------------------- -- [] instances ------------------------------------------------------------------------------- instance FromJSON1 [] where liftParseJSON _ p' = p' {-# INLINE liftParseJSON #-} instance (FromJSON a) => FromJSON [a] where parseJSON = parseJSON1 ------------------------------------------------------------------------------- -- Functions ------------------------------------------------------------------------------- -- | @'withObject' expected f value@ applies @f@ to the 'Object' when @value@ -- is an 'Object' and fails using @'typeMismatch' expected@ otherwise. withObject :: String -> (Object -> Parser a) -> Value -> Parser a withObject _ f (Object obj) = f obj withObject expected _ v = typeMismatch expected v {-# INLINE withObject #-} -- | @'withText' expected f value@ applies @f@ to the 'Text' when @value@ is a -- 'String' and fails using @'typeMismatch' expected@ otherwise. withText :: String -> (Text -> Parser a) -> Value -> Parser a withText _ f (String txt) = f txt withText expected _ v = typeMismatch expected v {-# INLINE withText #-} -- | @'withArray' expected f value@ applies @f@ to the 'Array' when @value@ is -- an 'Array' and fails using @'typeMismatch' expected@ otherwise. withArray :: String -> (Array -> Parser a) -> Value -> Parser a withArray _ f (Array arr) = f arr withArray expected _ v = typeMismatch expected v {-# INLINE withArray #-} -- | @'withScientific' expected f value@ applies @f@ to the 'Scientific' number -- when @value@ is a 'Number' and fails using @'typeMismatch' expected@ -- otherwise. -- . -- /Warning/: If you are converting from a scientific to an unbounded -- type such as 'Integer' you may want to add a restriction on the -- size of the exponent (see 'withBoundedScientific') to prevent -- malicious input from filling up the memory of the target system. withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a withScientific _ f (Number scientific) = f scientific withScientific expected _ v = typeMismatch expected v {-# INLINE withScientific #-} -- | @'withBoundedScientific' expected f value@ applies @f@ to the 'Scientific' number -- when @value@ is a 'Number' and fails using @'typeMismatch' expected@ -- otherwise. -- -- The conversion will also fail with a @'typeMismatch' if the -- 'Scientific' exponent is larger than 1024. withBoundedScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a withBoundedScientific _ f v@(Number scientific) = if base10Exponent scientific > 1024 then typeMismatch "a number with exponent <= 1024" v else f scientific withBoundedScientific expected _ v = typeMismatch expected v {-# INLINE withBoundedScientific #-} -- | @'withBool' expected f value@ applies @f@ to the 'Bool' when @value@ is a -- 'Bool' and fails using @'typeMismatch' expected@ otherwise. withBool :: String -> (Bool -> Parser a) -> Value -> Parser a withBool _ f (Bool arr) = f arr withBool expected _ v = typeMismatch expected v {-# INLINE withBool #-} -- | Decode a nested JSON-encoded string. withEmbeddedJSON :: String -> (Value -> Parser a) -> Value -> Parser a withEmbeddedJSON _ innerParser (String txt) = either fail innerParser $ eitherDecode (Compat.fromStrict $ T.encodeUtf8 txt) where eitherDecode = eitherFormatError . eitherDecodeWith jsonEOF ifromJSON eitherFormatError = either (Left . uncurry formatError) Right withEmbeddedJSON name _ v = typeMismatch name v {-# INLINE withEmbeddedJSON #-} -- | Convert a value from JSON, failing if the types do not match. fromJSON :: (FromJSON a) => Value -> Result a fromJSON = parse parseJSON {-# INLINE fromJSON #-} -- | Convert a value from JSON, failing if the types do not match. ifromJSON :: (FromJSON a) => Value -> IResult a ifromJSON = iparse parseJSON {-# INLINE ifromJSON #-} -- | Retrieve the value associated with the given key of an 'Object'. -- The result is 'empty' if the key is not present or the value cannot -- be converted to the desired type. -- -- This accessor is appropriate if the key and value /must/ be present -- in an object for it to be valid. If the key and value are -- optional, use '.:?' instead. (.:) :: (FromJSON a) => Object -> Text -> Parser a (.:) = explicitParseField parseJSON {-# INLINE (.:) #-} -- | Retrieve the value associated with the given key of an 'Object'. The -- result is 'Nothing' if the key is not present or if its value is 'Null', -- or 'empty' if the value cannot be converted to the desired type. -- -- This accessor is most useful if the key and value can be absent -- from an object without affecting its validity. If the key and -- value are mandatory, use '.:' instead. (.:?) :: (FromJSON a) => Object -> Text -> Parser (Maybe a) (.:?) = explicitParseFieldMaybe parseJSON {-# INLINE (.:?) #-} -- | Retrieve the value associated with the given key of an 'Object'. -- The result is 'Nothing' if the key is not present or 'empty' if the -- value cannot be converted to the desired type. -- -- This differs from '.:?' by attempting to parse 'Null' the same as any -- other JSON value, instead of interpreting it as 'Nothing'. (.:!) :: (FromJSON a) => Object -> Text -> Parser (Maybe a) (.:!) = explicitParseFieldMaybe' parseJSON {-# INLINE (.:!) #-} -- | Function variant of '.:'. parseField :: (FromJSON a) => Object -> Text -> Parser a parseField = (.:) {-# INLINE parseField #-} -- | Function variant of '.:?'. parseFieldMaybe :: (FromJSON a) => Object -> Text -> Parser (Maybe a) parseFieldMaybe = (.:?) {-# INLINE parseFieldMaybe #-} -- | Function variant of '.:!'. parseFieldMaybe' :: (FromJSON a) => Object -> Text -> Parser (Maybe a) parseFieldMaybe' = (.:!) {-# INLINE parseFieldMaybe' #-} -- | Variant of '.:' with explicit parser function. -- -- E.g. @'explicitParseField' 'parseJSON1' :: ('FromJSON1' f, 'FromJSON' a) -> 'Object' -> 'Text' -> 'Parser' (f a)@ explicitParseField :: (Value -> Parser a) -> Object -> Text -> Parser a explicitParseField p obj key = case H.lookup key obj of Nothing -> fail $ "key " ++ show key ++ " not present" Just v -> p v Key key {-# INLINE explicitParseField #-} -- | Variant of '.:?' with explicit parser function. explicitParseFieldMaybe :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a) explicitParseFieldMaybe p obj key = case H.lookup key obj of Nothing -> pure Nothing Just v -> liftParseJSON p (listParser p) v Key key -- listParser isn't used by maybe instance. {-# INLINE explicitParseFieldMaybe #-} -- | Variant of '.:!' with explicit parser function. explicitParseFieldMaybe' :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a) explicitParseFieldMaybe' p obj key = case H.lookup key obj of Nothing -> pure Nothing Just v -> Just <$> p v Key key {-# INLINE explicitParseFieldMaybe' #-} -- | Helper for use in combination with '.:?' to provide default -- values for optional JSON object fields. -- -- This combinator is most useful if the key and value can be absent -- from an object without affecting its validity and we know a default -- value to assign in that case. If the key and value are mandatory, -- use '.:' instead. -- -- Example usage: -- -- @ v1 <- o '.:?' \"opt_field_with_dfl\" .!= \"default_val\" -- v2 <- o '.:' \"mandatory_field\" -- v3 <- o '.:?' \"opt_field2\" -- @ (.!=) :: Parser (Maybe a) -> a -> Parser a pmval .!= val = fromMaybe val <$> pmval {-# INLINE (.!=) #-} -------------------------------------------------------------------------------- -- Generic parseJSON ------------------------------------------------------------------------------- instance GFromJSON arity V1 where -- Whereof we cannot format, thereof we cannot parse: gParseJSON _ _ _ = fail "Attempted to parse empty type" instance OVERLAPPABLE_ (GFromJSON arity a) => GFromJSON arity (M1 i c a) where -- Meta-information, which is not handled elsewhere, is just added to the -- parsed value: gParseJSON opts fargs = fmap M1 . gParseJSON opts fargs instance (FromJSON a) => GFromJSON arity (K1 i a) where -- Constant values are decoded using their FromJSON instance: gParseJSON _opts _ = fmap K1 . parseJSON instance GFromJSON One Par1 where -- Direct occurrences of the last type parameter are decoded with the -- function passed in as an argument: gParseJSON _opts (From1Args pj _) = fmap Par1 . pj instance (FromJSON1 f) => GFromJSON One (Rec1 f) where -- Recursive occurrences of the last type parameter are decoded using their -- FromJSON1 instance: gParseJSON _opts (From1Args pj pjl) = fmap Rec1 . liftParseJSON pj pjl instance GFromJSON arity U1 where -- Empty constructors are expected to be encoded as an empty array: gParseJSON _opts _ v | isEmptyArray v = pure U1 | otherwise = typeMismatch "unit constructor (U1)" v instance ( ConsFromJSON arity a , AllNullary (C1 c a) allNullary , ParseSum arity (C1 c a) allNullary ) => GFromJSON arity (D1 d (C1 c a)) where -- The option 'tagSingleConstructors' determines whether to wrap -- a single-constructor type. gParseJSON opts fargs | tagSingleConstructors opts = fmap M1 . (unTagged :: Tagged allNullary (Parser (C1 c a p)) -> Parser (C1 c a p)) . parseSum opts fargs | otherwise = fmap M1 . fmap M1 . consParseJSON opts fargs instance (ConsFromJSON arity a) => GFromJSON arity (C1 c a) where -- Constructors need to be decoded differently depending on whether they're -- a record or not. This distinction is made by consParseJSON: gParseJSON opts fargs = fmap M1 . consParseJSON opts fargs instance ( FromProduct arity a, FromProduct arity b , ProductSize a, ProductSize b ) => GFromJSON arity (a :*: b) where -- Products are expected to be encoded to an array. Here we check whether we -- got an array of the same size as the product, then parse each of the -- product's elements using parseProduct: gParseJSON opts fargs = withArray "product (:*:)" $ \arr -> let lenArray = V.length arr lenProduct = (unTagged2 :: Tagged2 (a :*: b) Int -> Int) productSize in if lenArray == lenProduct then parseProduct opts fargs arr 0 lenProduct else fail $ "When expecting a product of " ++ show lenProduct ++ " values, encountered an Array of " ++ show lenArray ++ " elements instead" instance ( AllNullary (a :+: b) allNullary , ParseSum arity (a :+: b) allNullary ) => GFromJSON arity (a :+: b) where -- If all constructors of a sum datatype are nullary and the -- 'allNullaryToStringTag' option is set they are expected to be -- encoded as strings. This distinction is made by 'parseSum': gParseJSON opts fargs = (unTagged :: Tagged allNullary (Parser ((a :+: b) d)) -> Parser ((a :+: b) d)) . parseSum opts fargs instance (FromJSON1 f, GFromJSON One g) => GFromJSON One (f :.: g) where -- If an occurrence of the last type parameter is nested inside two -- composed types, it is decoded by using the outermost type's FromJSON1 -- instance to generically decode the innermost type: gParseJSON opts fargs = let gpj = gParseJSON opts fargs in fmap Comp1 . liftParseJSON gpj (listParser gpj) -------------------------------------------------------------------------------- class ParseSum arity f allNullary where parseSum :: Options -> FromArgs arity a -> Value -> Tagged allNullary (Parser (f a)) instance ( SumFromString f , FromPair arity f , FromTaggedObject arity f , FromUntaggedValue arity f ) => ParseSum arity f True where parseSum opts fargs | allNullaryToStringTag opts = Tagged . parseAllNullarySum opts | otherwise = Tagged . parseNonAllNullarySum opts fargs instance ( FromPair arity f , FromTaggedObject arity f , FromUntaggedValue arity f ) => ParseSum arity f False where parseSum opts fargs = Tagged . parseNonAllNullarySum opts fargs -------------------------------------------------------------------------------- parseAllNullarySum :: SumFromString f => Options -> Value -> Parser (f a) parseAllNullarySum opts = withText "Text" $ \key -> maybe (notFound key) return $ parseSumFromString opts key class SumFromString f where parseSumFromString :: Options -> Text -> Maybe (f a) instance (SumFromString a, SumFromString b) => SumFromString (a :+: b) where parseSumFromString opts key = (L1 <$> parseSumFromString opts key) <|> (R1 <$> parseSumFromString opts key) instance (Constructor c) => SumFromString (C1 c U1) where parseSumFromString opts key | key == name = Just $ M1 U1 | otherwise = Nothing where name = pack $ constructorTagModifier opts $ conName (undefined :: t c U1 p) -------------------------------------------------------------------------------- parseNonAllNullarySum :: ( FromPair arity f , FromTaggedObject arity f , FromUntaggedValue arity f ) => Options -> FromArgs arity c -> Value -> Parser (f c) parseNonAllNullarySum opts fargs = case sumEncoding opts of TaggedObject{..} -> withObject "Object" $ \obj -> do tag <- obj .: pack tagFieldName fromMaybe (notFound tag) $ parseFromTaggedObject opts fargs contentsFieldName obj tag ObjectWithSingleField -> withObject "Object" $ \obj -> case H.toList obj of [pair@(tag, _)] -> fromMaybe (notFound tag) $ parsePair opts fargs pair _ -> fail "Object doesn't have a single field" TwoElemArray -> withArray "Array" $ \arr -> if V.length arr == 2 then case V.unsafeIndex arr 0 of String tag -> fromMaybe (notFound tag) $ parsePair opts fargs (tag, V.unsafeIndex arr 1) _ -> fail "First element is not a String" else fail "Array doesn't have 2 elements" UntaggedValue -> parseUntaggedValue opts fargs -------------------------------------------------------------------------------- class FromTaggedObject arity f where parseFromTaggedObject :: Options -> FromArgs arity a -> String -> Object -> Text -> Maybe (Parser (f a)) instance ( FromTaggedObject arity a, FromTaggedObject arity b) => FromTaggedObject arity (a :+: b) where parseFromTaggedObject opts fargs contentsFieldName obj tag = (fmap L1 <$> parseFromTaggedObject opts fargs contentsFieldName obj tag) <|> (fmap R1 <$> parseFromTaggedObject opts fargs contentsFieldName obj tag) instance ( FromTaggedObject' arity f , Constructor c ) => FromTaggedObject arity (C1 c f) where parseFromTaggedObject opts fargs contentsFieldName obj tag | tag == name = Just $ M1 <$> parseFromTaggedObject' opts fargs contentsFieldName obj | otherwise = Nothing where name = pack $ constructorTagModifier opts $ conName (undefined :: t c f p) -------------------------------------------------------------------------------- class FromTaggedObject' arity f where parseFromTaggedObject' :: Options -> FromArgs arity a -> String -> Object -> Parser (f a) class FromTaggedObject'' arity f isRecord where parseFromTaggedObject'' :: Options -> FromArgs arity a -> String -> Object -> Tagged isRecord (Parser (f a)) instance ( IsRecord f isRecord , FromTaggedObject'' arity f isRecord ) => FromTaggedObject' arity f where parseFromTaggedObject' opts fargs contentsFieldName = (unTagged :: Tagged isRecord (Parser (f a)) -> Parser (f a)) . parseFromTaggedObject'' opts fargs contentsFieldName instance (FromRecord arity f) => FromTaggedObject'' arity f True where parseFromTaggedObject'' opts fargs _ = Tagged . parseRecord opts fargs instance (GFromJSON arity f) => FromTaggedObject'' arity f False where parseFromTaggedObject'' opts fargs contentsFieldName = Tagged . (gParseJSON opts fargs <=< (.: pack contentsFieldName)) instance OVERLAPPING_ FromTaggedObject'' arity U1 False where parseFromTaggedObject'' _ _ _ _ = Tagged (pure U1) -------------------------------------------------------------------------------- class ConsFromJSON arity f where consParseJSON :: Options -> FromArgs arity a -> Value -> Parser (f a) class ConsFromJSON' arity f isRecord where consParseJSON' :: Options -> FromArgs arity a -> Value -> Tagged isRecord (Parser (f a)) instance ( IsRecord f isRecord , ConsFromJSON' arity f isRecord ) => ConsFromJSON arity f where consParseJSON opts fargs = (unTagged :: Tagged isRecord (Parser (f a)) -> Parser (f a)) . consParseJSON' opts fargs instance OVERLAPPING_ ( GFromJSON arity a, FromRecord arity (S1 s a) ) => ConsFromJSON' arity (S1 s a) True where consParseJSON' opts fargs | unwrapUnaryRecords opts = Tagged . gParseJSON opts fargs | otherwise = Tagged . withObject "unary record" (parseRecord opts fargs) instance FromRecord arity f => ConsFromJSON' arity f True where consParseJSON' opts fargs = Tagged . withObject "record (:*:)" (parseRecord opts fargs) instance GFromJSON arity f => ConsFromJSON' arity f False where consParseJSON' opts fargs = Tagged . gParseJSON opts fargs -------------------------------------------------------------------------------- class FromRecord arity f where parseRecord :: Options -> FromArgs arity a -> Object -> Parser (f a) instance ( FromRecord arity a , FromRecord arity b ) => FromRecord arity (a :*: b) where parseRecord opts fargs obj = (:*:) <$> parseRecord opts fargs obj <*> parseRecord opts fargs obj instance OVERLAPPABLE_ (Selector s, GFromJSON arity a) => FromRecord arity (S1 s a) where parseRecord opts fargs = ( Key label) . gParseJSON opts fargs <=< (.: label) where label = pack . fieldLabelModifier opts $ selName (undefined :: t s a p) instance INCOHERENT_ (Selector s, FromJSON a) => FromRecord arity (S1 s (K1 i (Maybe a))) where parseRecord opts _ obj = M1 . K1 <$> obj .:? pack label where label = fieldLabelModifier opts $ selName (undefined :: t s (K1 i (Maybe a)) p) -- Parse an Option like a Maybe. instance INCOHERENT_ (Selector s, FromJSON a) => FromRecord arity (S1 s (K1 i (Semigroup.Option a))) where parseRecord opts fargs obj = wrap <$> parseRecord opts fargs obj where wrap :: S1 s (K1 i (Maybe a)) p -> S1 s (K1 i (Semigroup.Option a)) p wrap (M1 (K1 a)) = M1 (K1 (Semigroup.Option a)) -------------------------------------------------------------------------------- class FromProduct arity f where parseProduct :: Options -> FromArgs arity a -> Array -> Int -> Int -> Parser (f a) instance ( FromProduct arity a , FromProduct arity b ) => FromProduct arity (a :*: b) where parseProduct opts fargs arr ix len = (:*:) <$> parseProduct opts fargs arr ix lenL <*> parseProduct opts fargs arr ixR lenR where lenL = len `unsafeShiftR` 1 ixR = ix + lenL lenR = len - lenL instance (GFromJSON arity a) => FromProduct arity (S1 s a) where parseProduct opts fargs arr ix _ = gParseJSON opts fargs $ V.unsafeIndex arr ix -------------------------------------------------------------------------------- class FromPair arity f where parsePair :: Options -> FromArgs arity a -> Pair -> Maybe (Parser (f a)) instance ( FromPair arity a , FromPair arity b ) => FromPair arity (a :+: b) where parsePair opts fargs pair = (fmap L1 <$> parsePair opts fargs pair) <|> (fmap R1 <$> parsePair opts fargs pair) instance ( Constructor c , GFromJSON arity a , ConsFromJSON arity a ) => FromPair arity (C1 c a) where parsePair opts fargs (tag, value) | tag == tag' = Just $ gParseJSON opts fargs value | otherwise = Nothing where tag' = pack $ constructorTagModifier opts $ conName (undefined :: t c a p) -------------------------------------------------------------------------------- class FromUntaggedValue arity f where parseUntaggedValue :: Options -> FromArgs arity a -> Value -> Parser (f a) instance ( FromUntaggedValue arity a , FromUntaggedValue arity b ) => FromUntaggedValue arity (a :+: b) where parseUntaggedValue opts fargs value = L1 <$> parseUntaggedValue opts fargs value <|> R1 <$> parseUntaggedValue opts fargs value instance OVERLAPPABLE_ ( GFromJSON arity a , ConsFromJSON arity a ) => FromUntaggedValue arity (C1 c a) where parseUntaggedValue = gParseJSON instance OVERLAPPING_ ( Constructor c ) => FromUntaggedValue arity (C1 c U1) where parseUntaggedValue opts _ (String s) | s == pack (constructorTagModifier opts (conName (undefined :: t c U1 p))) = pure $ M1 U1 | otherwise = fail $ "Invalid tag: " ++ unpack s parseUntaggedValue _ _ v = typeMismatch (conName (undefined :: t c U1 p)) v -------------------------------------------------------------------------------- notFound :: Text -> Parser a notFound key = fail $ "The key \"" ++ unpack key ++ "\" was not found" {-# INLINE notFound #-} ------------------------------------------------------------------------------- -- Instances ------------------------------------------------------------------------------- ------------------------------------------------------------------------------- -- base ------------------------------------------------------------------------------- instance FromJSON2 Const where liftParseJSON2 p _ _ _ = fmap Const . p {-# INLINE liftParseJSON2 #-} instance FromJSON a => FromJSON1 (Const a) where liftParseJSON _ _ = fmap Const . parseJSON {-# INLINE liftParseJSON #-} instance FromJSON a => FromJSON (Const a b) where {-# INLINE parseJSON #-} parseJSON = fmap Const . parseJSON instance FromJSON1 Maybe where liftParseJSON _ _ Null = pure Nothing liftParseJSON p _ a = Just <$> p a {-# INLINE liftParseJSON #-} instance (FromJSON a) => FromJSON (Maybe a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} instance FromJSON2 Either where liftParseJSON2 pA _ pB _ (Object (H.toList -> [(key, value)])) | key == left = Left <$> pA value Key left | key == right = Right <$> pB value Key right where left, right :: Text left = "Left" right = "Right" liftParseJSON2 _ _ _ _ _ = fail $ "expected an object with a single property " ++ "where the property key should be either " ++ "\"Left\" or \"Right\"" {-# INLINE liftParseJSON2 #-} instance (FromJSON a) => FromJSON1 (Either a) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b) => FromJSON (Either a b) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance FromJSON Void where parseJSON _ = fail "Cannot parse Void" {-# INLINE parseJSON #-} instance FromJSON Bool where parseJSON = withBool "Bool" pure {-# INLINE parseJSON #-} instance FromJSONKey Bool where fromJSONKey = FromJSONKeyTextParser $ \t -> case t of "true" -> pure True "false" -> pure False _ -> fail $ "Cannot parse key into Bool: " ++ T.unpack t instance FromJSON Ordering where parseJSON = withText "Ordering" $ \s -> case s of "LT" -> return LT "EQ" -> return EQ "GT" -> return GT _ -> fail "Parsing Ordering value failed: expected \"LT\", \"EQ\", or \"GT\"" instance FromJSON () where parseJSON = withArray "()" $ \v -> if V.null v then pure () else fail "Expected an empty array" {-# INLINE parseJSON #-} instance FromJSON Char where parseJSON = withText "Char" $ \t -> if T.compareLength t 1 == EQ then pure $ T.head t else fail "Expected a string of length 1" {-# INLINE parseJSON #-} parseJSONList = withText "String" $ pure . T.unpack {-# INLINE parseJSONList #-} instance FromJSON Double where parseJSON = parseRealFloat "Double" {-# INLINE parseJSON #-} instance FromJSONKey Double where fromJSONKey = FromJSONKeyTextParser $ \t -> case t of "NaN" -> pure (0/0) "Infinity" -> pure (1/0) "-Infinity" -> pure (negate 1/0) _ -> Scientific.toRealFloat <$> parseScientificText t instance FromJSON Float where parseJSON = parseRealFloat "Float" {-# INLINE parseJSON #-} instance FromJSONKey Float where fromJSONKey = FromJSONKeyTextParser $ \t -> case t of "NaN" -> pure (0/0) "Infinity" -> pure (1/0) "-Infinity" -> pure (negate 1/0) _ -> Scientific.toRealFloat <$> parseScientificText t instance (FromJSON a, Integral a) => FromJSON (Ratio a) where parseJSON = withObject "Rational" $ \obj -> do numerator <- obj .: "numerator" denominator <- obj .: "denominator" if denominator == 0 then fail "Ratio denominator was 0" else pure $ numerator % denominator {-# INLINE parseJSON #-} -- | This instance includes a bounds check to prevent maliciously -- large inputs to fill up the memory of the target system. You can -- newtype 'Scientific' and provide your own instance using -- 'withScientific' if you want to allow larger inputs. instance HasResolution a => FromJSON (Fixed a) where parseJSON = withBoundedScientific "Fixed" $ pure . realToFrac {-# INLINE parseJSON #-} instance FromJSON Int where parseJSON = parseBoundedIntegral "Int" {-# INLINE parseJSON #-} instance FromJSONKey Int where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int" -- | This instance includes a bounds check to prevent maliciously -- large inputs to fill up the memory of the target system. You can -- newtype 'Scientific' and provide your own instance using -- 'withScientific' if you want to allow larger inputs. instance FromJSON Integer where parseJSON = parseIntegral "Integer" {-# INLINE parseJSON #-} instance FromJSONKey Integer where fromJSONKey = FromJSONKeyTextParser $ parseIntegralText "Integer" instance FromJSON Natural where parseJSON value = do integer :: Integer <- parseIntegral "Natural" value if integer < 0 then fail $ "expected Natural, encountered negative number " <> show integer else pure $ fromIntegral integer instance FromJSONKey Natural where fromJSONKey = FromJSONKeyTextParser $ \text -> do integer :: Integer <- parseIntegralText "Natural" text if integer < 0 then fail $ "expected Natural, encountered negative number " <> show integer else pure $ fromIntegral integer instance FromJSON Int8 where parseJSON = parseBoundedIntegral "Int8" {-# INLINE parseJSON #-} instance FromJSONKey Int8 where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int8" instance FromJSON Int16 where parseJSON = parseBoundedIntegral "Int16" {-# INLINE parseJSON #-} instance FromJSONKey Int16 where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int16" instance FromJSON Int32 where parseJSON = parseBoundedIntegral "Int32" {-# INLINE parseJSON #-} instance FromJSONKey Int32 where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int32" instance FromJSON Int64 where parseJSON = parseBoundedIntegral "Int64" {-# INLINE parseJSON #-} instance FromJSONKey Int64 where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Int64" instance FromJSON Word where parseJSON = parseBoundedIntegral "Word" {-# INLINE parseJSON #-} instance FromJSONKey Word where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word" instance FromJSON Word8 where parseJSON = parseBoundedIntegral "Word8" {-# INLINE parseJSON #-} instance FromJSONKey Word8 where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word8" instance FromJSON Word16 where parseJSON = parseBoundedIntegral "Word16" {-# INLINE parseJSON #-} instance FromJSONKey Word16 where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word16" instance FromJSON Word32 where parseJSON = parseBoundedIntegral "Word32" {-# INLINE parseJSON #-} instance FromJSONKey Word32 where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word32" instance FromJSON Word64 where parseJSON = parseBoundedIntegral "Word64" {-# INLINE parseJSON #-} instance FromJSONKey Word64 where fromJSONKey = FromJSONKeyTextParser $ parseBoundedIntegralText "Word64" instance FromJSON CTime where parseJSON = fmap CTime . parseJSON {-# INLINE parseJSON #-} instance FromJSON Text where parseJSON = withText "Text" pure {-# INLINE parseJSON #-} instance FromJSONKey Text where fromJSONKey = fromJSONKeyCoerce instance FromJSON LT.Text where parseJSON = withText "Lazy Text" $ pure . LT.fromStrict {-# INLINE parseJSON #-} instance FromJSONKey LT.Text where fromJSONKey = FromJSONKeyText LT.fromStrict instance FromJSON Version where parseJSON = withText "Version" parseVersionText {-# INLINE parseJSON #-} instance FromJSONKey Version where fromJSONKey = FromJSONKeyTextParser parseVersionText parseVersionText :: Text -> Parser Version parseVersionText = go . readP_to_S parseVersion . unpack where go [(v,[])] = return v go (_ : xs) = go xs go _ = fail "could not parse Version" ------------------------------------------------------------------------------- -- semigroups NonEmpty ------------------------------------------------------------------------------- instance FromJSON1 NonEmpty where liftParseJSON p _ = withArray "NonEmpty a" $ (>>= ne) . Tr.sequence . zipWith (parseIndexedJSON p) [0..] . V.toList where ne [] = fail "Expected a NonEmpty but got an empty list" ne (x:xs) = pure (x :| xs) {-# INLINE liftParseJSON #-} instance (FromJSON a) => FromJSON (NonEmpty a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- scientific ------------------------------------------------------------------------------- instance FromJSON Scientific where parseJSON = withScientific "Scientific" pure {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- DList ------------------------------------------------------------------------------- instance FromJSON1 DList.DList where liftParseJSON p _ = withArray "DList a" $ fmap DList.fromList . Tr.sequence . zipWith (parseIndexedJSON p) [0..] . V.toList {-# INLINE liftParseJSON #-} instance (FromJSON a) => FromJSON (DList.DList a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- tranformers - Functors ------------------------------------------------------------------------------- instance FromJSON1 Identity where liftParseJSON p _ a = Identity <$> p a {-# INLINE liftParseJSON #-} liftParseJSONList _ p a = fmap Identity <$> p a {-# INLINE liftParseJSONList #-} instance (FromJSON a) => FromJSON (Identity a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} parseJSONList = liftParseJSONList parseJSON parseJSONList {-# INLINE parseJSONList #-} instance (FromJSONKey a) => FromJSONKey (Identity a) where fromJSONKey = coerceFromJSONKeyFunction (fromJSONKey :: FromJSONKeyFunction a) fromJSONKeyList = coerceFromJSONKeyFunction (fromJSONKeyList :: FromJSONKeyFunction [a]) instance (FromJSON1 f, FromJSON1 g) => FromJSON1 (Compose f g) where liftParseJSON p pl a = Compose <$> liftParseJSON g gl a where g = liftParseJSON p pl gl = liftParseJSONList p pl {-# INLINE liftParseJSON #-} liftParseJSONList p pl a = map Compose <$> liftParseJSONList g gl a where g = liftParseJSON p pl gl = liftParseJSONList p pl {-# INLINE liftParseJSONList #-} instance (FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose f g a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} parseJSONList = liftParseJSONList parseJSON parseJSONList {-# INLINE parseJSONList #-} instance (FromJSON1 f, FromJSON1 g) => FromJSON1 (Product f g) where liftParseJSON p pl a = uncurry Pair <$> liftParseJSON2 px pxl py pyl a where px = liftParseJSON p pl pxl = liftParseJSONList p pl py = liftParseJSON p pl pyl = liftParseJSONList p pl {-# INLINE liftParseJSON #-} instance (FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product f g a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} instance (FromJSON1 f, FromJSON1 g) => FromJSON1 (Sum f g) where liftParseJSON p pl (Object (H.toList -> [(key, value)])) | key == inl = InL <$> liftParseJSON p pl value Key inl | key == inr = InR <$> liftParseJSON p pl value Key inl where inl, inr :: Text inl = "InL" inr = "InR" liftParseJSON _ _ _ = fail $ "expected an object with a single property " ++ "where the property key should be either " ++ "\"InL\" or \"InR\"" {-# INLINE liftParseJSON #-} instance (FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum f g a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- containers ------------------------------------------------------------------------------- instance FromJSON1 Seq.Seq where liftParseJSON p _ = withArray "Seq a" $ fmap Seq.fromList . Tr.sequence . zipWith (parseIndexedJSON p) [0..] . V.toList {-# INLINE liftParseJSON #-} instance (FromJSON a) => FromJSON (Seq.Seq a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} instance (Ord a, FromJSON a) => FromJSON (Set.Set a) where parseJSON = fmap Set.fromList . parseJSON {-# INLINE parseJSON #-} instance FromJSON IntSet.IntSet where parseJSON = fmap IntSet.fromList . parseJSON {-# INLINE parseJSON #-} instance FromJSON1 IntMap.IntMap where liftParseJSON p pl = fmap IntMap.fromList . liftParseJSON p' pl' where p' = liftParseJSON2 parseJSON parseJSONList p pl pl' = liftParseJSONList2 parseJSON parseJSONList p pl {-# INLINE liftParseJSON #-} instance FromJSON a => FromJSON (IntMap.IntMap a) where parseJSON = fmap IntMap.fromList . parseJSON {-# INLINE parseJSON #-} instance (FromJSONKey k, Ord k) => FromJSON1 (M.Map k) where liftParseJSON p _ = case fromJSONKey of FromJSONKeyCoerce _-> withObject "Map k v" $ fmap (H.foldrWithKey (M.insert . unsafeCoerce) M.empty) . H.traverseWithKey (\k v -> p v Key k) FromJSONKeyText f -> withObject "Map k v" $ fmap (H.foldrWithKey (M.insert . f) M.empty) . H.traverseWithKey (\k v -> p v Key k) FromJSONKeyTextParser f -> withObject "Map k v" $ H.foldrWithKey (\k v m -> M.insert <$> f k Key k <*> p v Key k <*> m) (pure M.empty) FromJSONKeyValue f -> withArray "Map k v" $ \arr -> fmap M.fromList . Tr.sequence . zipWith (parseIndexedJSONPair f p) [0..] . V.toList $ arr {-# INLINE liftParseJSON #-} instance (FromJSONKey k, Ord k, FromJSON v) => FromJSON (M.Map k v) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} instance FromJSON1 Tree.Tree where liftParseJSON p pl = go where go v = uncurry Tree.Node <$> liftParseJSON2 p pl p' pl' v p' = liftParseJSON go (listParser go) pl'= liftParseJSONList go (listParser go) instance (FromJSON v) => FromJSON (Tree.Tree v) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- uuid ------------------------------------------------------------------------------- instance FromJSON UUID.UUID where parseJSON = withText "UUID" $ maybe (fail "Invalid UUID") pure . UUID.fromText instance FromJSONKey UUID.UUID where fromJSONKey = FromJSONKeyTextParser $ maybe (fail "Invalid UUID") pure . UUID.fromText ------------------------------------------------------------------------------- -- vector ------------------------------------------------------------------------------- instance FromJSON1 Vector where liftParseJSON p _ = withArray "Vector a" $ V.mapM (uncurry $ parseIndexedJSON p) . V.indexed {-# INLINE liftParseJSON #-} instance (FromJSON a) => FromJSON (Vector a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} vectorParseJSON :: (FromJSON a, VG.Vector w a) => String -> Value -> Parser (w a) vectorParseJSON s = withArray s $ fmap V.convert . V.mapM (uncurry $ parseIndexedJSON parseJSON) . V.indexed {-# INLINE vectorParseJSON #-} instance (Storable a, FromJSON a) => FromJSON (VS.Vector a) where parseJSON = vectorParseJSON "Data.Vector.Storable.Vector a" instance (VP.Prim a, FromJSON a) => FromJSON (VP.Vector a) where parseJSON = vectorParseJSON "Data.Vector.Primitive.Vector a" {-# INLINE parseJSON #-} instance (VG.Vector VU.Vector a, FromJSON a) => FromJSON (VU.Vector a) where parseJSON = vectorParseJSON "Data.Vector.Unboxed.Vector a" {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- unordered-containers ------------------------------------------------------------------------------- instance (Eq a, Hashable a, FromJSON a) => FromJSON (HashSet.HashSet a) where parseJSON = fmap HashSet.fromList . parseJSON {-# INLINE parseJSON #-} instance (FromJSONKey k, Eq k, Hashable k) => FromJSON1 (H.HashMap k) where liftParseJSON p _ = case fromJSONKey of FromJSONKeyCoerce _ -> withObject "HashMap ~Text v" $ uc . H.traverseWithKey (\k v -> p v Key k) FromJSONKeyText f -> withObject "HashMap k v" $ fmap (mapKey f) . H.traverseWithKey (\k v -> p v Key k) FromJSONKeyTextParser f -> withObject "HashMap k v" $ H.foldrWithKey (\k v m -> H.insert <$> f k Key k <*> p v Key k <*> m) (pure H.empty) FromJSONKeyValue f -> withArray "Map k v" $ \arr -> fmap H.fromList . Tr.sequence . zipWith (parseIndexedJSONPair f p) [0..] . V.toList $ arr where uc :: Parser (H.HashMap Text v) -> Parser (H.HashMap k v) uc = unsafeCoerce instance (FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (H.HashMap k v) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- aeson ------------------------------------------------------------------------------- instance FromJSON Value where parseJSON = pure {-# INLINE parseJSON #-} instance FromJSON DotNetTime where parseJSON = withText "DotNetTime" $ \t -> let (s,m) = T.splitAt (T.length t - 5) t t' = T.concat [s,".",m] in case parseTime defaultTimeLocale "/Date(%s%Q)/" (unpack t') of Just d -> pure (DotNetTime d) _ -> fail "could not parse .NET time" {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- primitive ------------------------------------------------------------------------------- #if MIN_VERSION_base(4,7,0) instance FromJSON a => FromJSON (PM.Array a) where -- note: we could do better than this if vector exposed the data -- constructor in Data.Vector. parseJSON = fmap Exts.fromList . parseJSON instance FromJSON a => FromJSON (PM.SmallArray a) where parseJSON = fmap Exts.fromList . parseJSON #if MIN_VERSION_primitive(0,6,4) instance (PM.Prim a,FromJSON a) => FromJSON (PM.PrimArray a) where parseJSON = fmap Exts.fromList . parseJSON instance (PM.PrimUnlifted a,FromJSON a) => FromJSON (PM.UnliftedArray a) where parseJSON = fmap Exts.fromList . parseJSON #endif #endif ------------------------------------------------------------------------------- -- time ------------------------------------------------------------------------------- instance FromJSON Day where parseJSON = withText "Day" (Time.run Time.day) instance FromJSONKey Day where fromJSONKey = FromJSONKeyTextParser (Time.run Time.day) instance FromJSON TimeOfDay where parseJSON = withText "TimeOfDay" (Time.run Time.timeOfDay) instance FromJSONKey TimeOfDay where fromJSONKey = FromJSONKeyTextParser (Time.run Time.timeOfDay) instance FromJSON LocalTime where parseJSON = withText "LocalTime" (Time.run Time.localTime) instance FromJSONKey LocalTime where fromJSONKey = FromJSONKeyTextParser (Time.run Time.localTime) -- | Supported string formats: -- -- @YYYY-MM-DD HH:MM Z@ -- @YYYY-MM-DD HH:MM:SS Z@ -- @YYYY-MM-DD HH:MM:SS.SSS Z@ -- -- The first space may instead be a @T@, and the second space is -- optional. The @Z@ represents UTC. The @Z@ may be replaced with a -- time zone offset of the form @+0000@ or @-08:00@, where the first -- two digits are hours, the @:@ is optional and the second two digits -- (also optional) are minutes. instance FromJSON ZonedTime where parseJSON = withText "ZonedTime" (Time.run Time.zonedTime) instance FromJSONKey ZonedTime where fromJSONKey = FromJSONKeyTextParser (Time.run Time.zonedTime) instance FromJSON UTCTime where parseJSON = withText "UTCTime" (Time.run Time.utcTime) instance FromJSONKey UTCTime where fromJSONKey = FromJSONKeyTextParser (Time.run Time.utcTime) -- | This instance includes a bounds check to prevent maliciously -- large inputs to fill up the memory of the target system. You can -- newtype 'Scientific' and provide your own instance using -- 'withScientific' if you want to allow larger inputs. instance FromJSON NominalDiffTime where parseJSON = withBoundedScientific "NominalDiffTime" $ pure . realToFrac {-# INLINE parseJSON #-} -- | This instance includes a bounds check to prevent maliciously -- large inputs to fill up the memory of the target system. You can -- newtype 'Scientific' and provide your own instance using -- 'withScientific' if you want to allow larger inputs. instance FromJSON DiffTime where parseJSON = withBoundedScientific "DiffTime" $ pure . realToFrac {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- base Monoid/Semigroup ------------------------------------------------------------------------------- instance FromJSON1 Monoid.Dual where liftParseJSON p _ = fmap Monoid.Dual . p {-# INLINE liftParseJSON #-} instance FromJSON a => FromJSON (Monoid.Dual a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} instance FromJSON1 Monoid.First where liftParseJSON p p' = fmap Monoid.First . liftParseJSON p p' {-# INLINE liftParseJSON #-} instance FromJSON a => FromJSON (Monoid.First a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} instance FromJSON1 Monoid.Last where liftParseJSON p p' = fmap Monoid.Last . liftParseJSON p p' {-# INLINE liftParseJSON #-} instance FromJSON a => FromJSON (Monoid.Last a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} instance FromJSON1 Semigroup.Min where liftParseJSON p _ a = Semigroup.Min <$> p a {-# INLINE liftParseJSON #-} liftParseJSONList _ p a = fmap Semigroup.Min <$> p a {-# INLINE liftParseJSONList #-} instance (FromJSON a) => FromJSON (Semigroup.Min a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} parseJSONList = liftParseJSONList parseJSON parseJSONList {-# INLINE parseJSONList #-} instance FromJSON1 Semigroup.Max where liftParseJSON p _ a = Semigroup.Max <$> p a {-# INLINE liftParseJSON #-} liftParseJSONList _ p a = fmap Semigroup.Max <$> p a {-# INLINE liftParseJSONList #-} instance (FromJSON a) => FromJSON (Semigroup.Max a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} parseJSONList = liftParseJSONList parseJSON parseJSONList {-# INLINE parseJSONList #-} instance FromJSON1 Semigroup.First where liftParseJSON p _ a = Semigroup.First <$> p a {-# INLINE liftParseJSON #-} liftParseJSONList _ p a = fmap Semigroup.First <$> p a {-# INLINE liftParseJSONList #-} instance (FromJSON a) => FromJSON (Semigroup.First a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} parseJSONList = liftParseJSONList parseJSON parseJSONList {-# INLINE parseJSONList #-} instance FromJSON1 Semigroup.Last where liftParseJSON p _ a = Semigroup.Last <$> p a {-# INLINE liftParseJSON #-} liftParseJSONList _ p a = fmap Semigroup.Last <$> p a {-# INLINE liftParseJSONList #-} instance (FromJSON a) => FromJSON (Semigroup.Last a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} parseJSONList = liftParseJSONList parseJSON parseJSONList {-# INLINE parseJSONList #-} instance FromJSON1 Semigroup.WrappedMonoid where liftParseJSON p _ a = Semigroup.WrapMonoid <$> p a {-# INLINE liftParseJSON #-} liftParseJSONList _ p a = fmap Semigroup.WrapMonoid <$> p a {-# INLINE liftParseJSONList #-} instance (FromJSON a) => FromJSON (Semigroup.WrappedMonoid a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} parseJSONList = liftParseJSONList parseJSON parseJSONList {-# INLINE parseJSONList #-} instance FromJSON1 Semigroup.Option where liftParseJSON p p' = fmap Semigroup.Option . liftParseJSON p p' {-# INLINE liftParseJSON #-} instance FromJSON a => FromJSON (Semigroup.Option a) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} ------------------------------------------------------------------------------- -- tagged ------------------------------------------------------------------------------- instance FromJSON1 Proxy where {-# INLINE liftParseJSON #-} liftParseJSON _ _ Null = pure Proxy liftParseJSON _ _ v = typeMismatch "Proxy" v instance FromJSON (Proxy a) where {-# INLINE parseJSON #-} parseJSON Null = pure Proxy parseJSON v = typeMismatch "Proxy" v instance FromJSON2 Tagged where liftParseJSON2 _ _ p _ = fmap Tagged . p {-# INLINE liftParseJSON2 #-} instance FromJSON1 (Tagged a) where liftParseJSON p _ = fmap Tagged . p {-# INLINE liftParseJSON #-} instance FromJSON b => FromJSON (Tagged a b) where parseJSON = parseJSON1 {-# INLINE parseJSON #-} instance FromJSONKey b => FromJSONKey (Tagged a b) where fromJSONKey = coerceFromJSONKeyFunction (fromJSONKey :: FromJSONKeyFunction b) fromJSONKeyList = (fmap . fmap) Tagged fromJSONKeyList ------------------------------------------------------------------------------- -- Instances for converting from map keys ------------------------------------------------------------------------------- instance (FromJSON a, FromJSON b) => FromJSONKey (a,b) instance (FromJSON a, FromJSON b, FromJSON c) => FromJSONKey (a,b,c) instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSONKey (a,b,c,d) instance FromJSONKey Char where fromJSONKey = FromJSONKeyTextParser $ \t -> if T.length t == 1 then return (T.index t 0) else typeMismatch "Expected Char but String didn't contain exactly one character" (String t) fromJSONKeyList = FromJSONKeyText T.unpack instance (FromJSONKey a, FromJSON a) => FromJSONKey [a] where fromJSONKey = fromJSONKeyList ------------------------------------------------------------------------------- -- Tuple instances, see tuple-instances-from.hs ------------------------------------------------------------------------------- instance FromJSON2 (,) where liftParseJSON2 pA _ pB _ = withArray "(a, b)" $ \t -> let n = V.length t in if n == 2 then (,) <$> parseJSONElemAtIndex pA 0 t <*> parseJSONElemAtIndex pB 1 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 2" {-# INLINE liftParseJSON2 #-} instance (FromJSON a) => FromJSON1 ((,) a) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b) => FromJSON (a, b) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a) => FromJSON2 ((,,) a) where liftParseJSON2 pB _ pC _ = withArray "(a, b, c)" $ \t -> let n = V.length t in if n == 3 then (,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex pB 1 t <*> parseJSONElemAtIndex pC 2 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 3" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b) => FromJSON1 ((,,) a b) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b) => FromJSON2 ((,,,) a b) where liftParseJSON2 pC _ pD _ = withArray "(a, b, c, d)" $ \t -> let n = V.length t in if n == 4 then (,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex pC 2 t <*> parseJSONElemAtIndex pD 3 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 4" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c) => FromJSON1 ((,,,) a b c) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c) => FromJSON2 ((,,,,) a b c) where liftParseJSON2 pD _ pE _ = withArray "(a, b, c, d, e)" $ \t -> let n = V.length t in if n == 5 then (,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex pD 3 t <*> parseJSONElemAtIndex pE 4 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 5" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON1 ((,,,,) a b c d) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON2 ((,,,,,) a b c d) where liftParseJSON2 pE _ pF _ = withArray "(a, b, c, d, e, f)" $ \t -> let n = V.length t in if n == 6 then (,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex pE 4 t <*> parseJSONElemAtIndex pF 5 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 6" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON1 ((,,,,,) a b c d e) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON2 ((,,,,,,) a b c d e) where liftParseJSON2 pF _ pG _ = withArray "(a, b, c, d, e, f, g)" $ \t -> let n = V.length t in if n == 7 then (,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex pF 5 t <*> parseJSONElemAtIndex pG 6 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 7" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON1 ((,,,,,,) a b c d e f) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON2 ((,,,,,,,) a b c d e f) where liftParseJSON2 pG _ pH _ = withArray "(a, b, c, d, e, f, g, h)" $ \t -> let n = V.length t in if n == 8 then (,,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex parseJSON 5 t <*> parseJSONElemAtIndex pG 6 t <*> parseJSONElemAtIndex pH 7 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 8" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON1 ((,,,,,,,) a b c d e f g) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON2 ((,,,,,,,,) a b c d e f g) where liftParseJSON2 pH _ pI _ = withArray "(a, b, c, d, e, f, g, h, i)" $ \t -> let n = V.length t in if n == 9 then (,,,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex parseJSON 5 t <*> parseJSONElemAtIndex parseJSON 6 t <*> parseJSONElemAtIndex pH 7 t <*> parseJSONElemAtIndex pI 8 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 9" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON1 ((,,,,,,,,) a b c d e f g h) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON2 ((,,,,,,,,,) a b c d e f g h) where liftParseJSON2 pI _ pJ _ = withArray "(a, b, c, d, e, f, g, h, i, j)" $ \t -> let n = V.length t in if n == 10 then (,,,,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex parseJSON 5 t <*> parseJSONElemAtIndex parseJSON 6 t <*> parseJSONElemAtIndex parseJSON 7 t <*> parseJSONElemAtIndex pI 8 t <*> parseJSONElemAtIndex pJ 9 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 10" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON1 ((,,,,,,,,,) a b c d e f g h i) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON2 ((,,,,,,,,,,) a b c d e f g h i) where liftParseJSON2 pJ _ pK _ = withArray "(a, b, c, d, e, f, g, h, i, j, k)" $ \t -> let n = V.length t in if n == 11 then (,,,,,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex parseJSON 5 t <*> parseJSONElemAtIndex parseJSON 6 t <*> parseJSONElemAtIndex parseJSON 7 t <*> parseJSONElemAtIndex parseJSON 8 t <*> parseJSONElemAtIndex pJ 9 t <*> parseJSONElemAtIndex pK 10 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 11" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON1 ((,,,,,,,,,,) a b c d e f g h i j) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON2 ((,,,,,,,,,,,) a b c d e f g h i j) where liftParseJSON2 pK _ pL _ = withArray "(a, b, c, d, e, f, g, h, i, j, k, l)" $ \t -> let n = V.length t in if n == 12 then (,,,,,,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex parseJSON 5 t <*> parseJSONElemAtIndex parseJSON 6 t <*> parseJSONElemAtIndex parseJSON 7 t <*> parseJSONElemAtIndex parseJSON 8 t <*> parseJSONElemAtIndex parseJSON 9 t <*> parseJSONElemAtIndex pK 10 t <*> parseJSONElemAtIndex pL 11 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 12" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON1 ((,,,,,,,,,,,) a b c d e f g h i j k) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON2 ((,,,,,,,,,,,,) a b c d e f g h i j k) where liftParseJSON2 pL _ pM _ = withArray "(a, b, c, d, e, f, g, h, i, j, k, l, m)" $ \t -> let n = V.length t in if n == 13 then (,,,,,,,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex parseJSON 5 t <*> parseJSONElemAtIndex parseJSON 6 t <*> parseJSONElemAtIndex parseJSON 7 t <*> parseJSONElemAtIndex parseJSON 8 t <*> parseJSONElemAtIndex parseJSON 9 t <*> parseJSONElemAtIndex parseJSON 10 t <*> parseJSONElemAtIndex pL 11 t <*> parseJSONElemAtIndex pM 12 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 13" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON2 ((,,,,,,,,,,,,,) a b c d e f g h i j k l) where liftParseJSON2 pM _ pN _ = withArray "(a, b, c, d, e, f, g, h, i, j, k, l, m, n)" $ \t -> let n = V.length t in if n == 14 then (,,,,,,,,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex parseJSON 5 t <*> parseJSONElemAtIndex parseJSON 6 t <*> parseJSONElemAtIndex parseJSON 7 t <*> parseJSONElemAtIndex parseJSON 8 t <*> parseJSONElemAtIndex parseJSON 9 t <*> parseJSONElemAtIndex parseJSON 10 t <*> parseJSONElemAtIndex parseJSON 11 t <*> parseJSONElemAtIndex pM 12 t <*> parseJSONElemAtIndex pN 13 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 14" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON2 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m) where liftParseJSON2 pN _ pO _ = withArray "(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)" $ \t -> let n = V.length t in if n == 15 then (,,,,,,,,,,,,,,) <$> parseJSONElemAtIndex parseJSON 0 t <*> parseJSONElemAtIndex parseJSON 1 t <*> parseJSONElemAtIndex parseJSON 2 t <*> parseJSONElemAtIndex parseJSON 3 t <*> parseJSONElemAtIndex parseJSON 4 t <*> parseJSONElemAtIndex parseJSON 5 t <*> parseJSONElemAtIndex parseJSON 6 t <*> parseJSONElemAtIndex parseJSON 7 t <*> parseJSONElemAtIndex parseJSON 8 t <*> parseJSONElemAtIndex parseJSON 9 t <*> parseJSONElemAtIndex parseJSON 10 t <*> parseJSONElemAtIndex parseJSON 11 t <*> parseJSONElemAtIndex parseJSON 12 t <*> parseJSONElemAtIndex pN 13 t <*> parseJSONElemAtIndex pO 14 t else fail $ "cannot unpack array of length " ++ show n ++ " into a tuple of length 15" {-# INLINE liftParseJSON2 #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) where liftParseJSON = liftParseJSON2 parseJSON parseJSONList {-# INLINE liftParseJSON #-} instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where parseJSON = parseJSON2 {-# INLINE parseJSON #-} aeson-1.4.2.0/Data/Aeson/Types/Generic.hs0000644000000000000000000000614700000000000016052 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} #include "overlapping-compat.h" -- | -- Module: Data.Aeson.Types.Generic -- Copyright: (c) 2012-2016 Bryan O'Sullivan -- (c) 2011, 2012 Bas Van Dijk -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Helpers for generic derivations. module Data.Aeson.Types.Generic ( IsRecord , AllNullary , Tagged2(..) , True , False , And , Zero , One , ProductSize(..) ) where import Prelude.Compat import GHC.Generics -------------------------------------------------------------------------------- class IsRecord (f :: * -> *) isRecord | f -> isRecord instance (IsRecord f isRecord) => IsRecord (f :*: g) isRecord #if MIN_VERSION_base(4,9,0) instance OVERLAPPING_ IsRecord (M1 S ('MetaSel 'Nothing u ss ds) f) False #else instance OVERLAPPING_ IsRecord (M1 S NoSelector f) False #endif instance (IsRecord f isRecord) => IsRecord (M1 S c f) isRecord instance IsRecord (K1 i c) True instance IsRecord Par1 True instance IsRecord (Rec1 f) True instance IsRecord (f :.: g) True instance IsRecord U1 False -------------------------------------------------------------------------------- class AllNullary (f :: * -> *) allNullary | f -> allNullary instance ( AllNullary a allNullaryL , AllNullary b allNullaryR , And allNullaryL allNullaryR allNullary ) => AllNullary (a :+: b) allNullary instance AllNullary a allNullary => AllNullary (M1 i c a) allNullary instance AllNullary (a :*: b) False instance AllNullary (a :.: b) False instance AllNullary (K1 i c) False instance AllNullary Par1 False instance AllNullary (Rec1 f) False instance AllNullary U1 True newtype Tagged2 (s :: * -> *) b = Tagged2 {unTagged2 :: b} -------------------------------------------------------------------------------- data True data False class And bool1 bool2 bool3 | bool1 bool2 -> bool3 instance And True True True instance And False False False instance And False True False instance And True False False -------------------------------------------------------------------------------- -- | A type-level indicator that 'ToJSON' or 'FromJSON' is being derived generically. data Zero -- | A type-level indicator that 'ToJSON1' or 'FromJSON1' is being derived generically. data One -------------------------------------------------------------------------------- class ProductSize f where productSize :: Tagged2 f Int instance (ProductSize a, ProductSize b) => ProductSize (a :*: b) where productSize = Tagged2 $ unTagged2 (productSize :: Tagged2 a Int) + unTagged2 (productSize :: Tagged2 b Int) instance ProductSize (S1 s a) where productSize = Tagged2 1 aeson-1.4.2.0/Data/Aeson/Types/Internal.hs0000644000000000000000000005322000000000000016244 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Rank2Types #-} #if __GLASGOW_HASKELL__ >= 800 -- a) THQ works on cross-compilers and unregisterised GHCs -- b) may make compilation faster as no dynamic loading is ever needed (not sure about this) -- c) removes one hindrance to have code inferred as SafeHaskell safe {-# LANGUAGE TemplateHaskellQuotes #-} #else {-# LANGUAGE TemplateHaskell #-} #endif -- | -- Module: Data.Aeson.Types.Internal -- Copyright: (c) 2011-2016 Bryan O'Sullivan -- (c) 2011 MailRank, Inc. -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Types for working with JSON data. module Data.Aeson.Types.Internal ( -- * Core JSON types Value(..) , Array , emptyArray, isEmptyArray , Pair , Object , emptyObject -- * Type conversion , Parser , Result(..) , IResult(..) , JSONPathElement(..) , JSONPath , iparse , parse , parseEither , parseMaybe , modifyFailure , parserThrowError , parserCatchError , formatError , () -- * Constructors and accessors , object -- * Generic and TH encoding configuration , Options( fieldLabelModifier , constructorTagModifier , allNullaryToStringTag , omitNothingFields , sumEncoding , unwrapUnaryRecords , tagSingleConstructors ) , SumEncoding(..) , defaultOptions , defaultTaggedObject -- * Used for changing CamelCase names into something else. , camelTo , camelTo2 -- * Other types , DotNetTime(..) ) where import Prelude.Compat import Control.Applicative (Alternative(..)) import Control.Arrow (first) import Control.DeepSeq (NFData(..)) import Control.Monad (MonadPlus(..), ap) import Data.Char (isLower, isUpper, toLower, isAlpha, isAlphaNum) import Data.Data (Data) import Data.Foldable (foldl') import Data.HashMap.Strict (HashMap) import Data.Hashable (Hashable(..)) import Data.List (intercalate) import Data.Scientific (Scientific) import Data.Semigroup (Semigroup((<>))) import Data.String (IsString(..)) import Data.Text (Text, pack, unpack) import Data.Time (UTCTime) import Data.Time.Format (FormatTime) import Data.Typeable (Typeable) import Data.Vector (Vector) import GHC.Generics (Generic) import qualified Control.Monad.Fail as Fail import qualified Data.HashMap.Strict as H import qualified Data.Scientific as S import qualified Data.Vector as V import qualified Language.Haskell.TH.Syntax as TH #if !MIN_VERSION_unordered_containers(0,2,6) import Data.List (sort) #endif -- | Elements of a JSON path used to describe the location of an -- error. data JSONPathElement = Key Text -- ^ JSON path element of a key into an object, -- \"object.key\". | Index {-# UNPACK #-} !Int -- ^ JSON path element of an index into an -- array, \"array[index]\". deriving (Eq, Show, Typeable, Ord) type JSONPath = [JSONPathElement] -- | The internal result of running a 'Parser'. data IResult a = IError JSONPath String | ISuccess a deriving (Eq, Show, Typeable) -- | The result of running a 'Parser'. data Result a = Error String | Success a deriving (Eq, Show, Typeable) instance NFData JSONPathElement where rnf (Key t) = rnf t rnf (Index i) = rnf i instance (NFData a) => NFData (IResult a) where rnf (ISuccess a) = rnf a rnf (IError path err) = rnf path `seq` rnf err instance (NFData a) => NFData (Result a) where rnf (Success a) = rnf a rnf (Error err) = rnf err instance Functor IResult where fmap f (ISuccess a) = ISuccess (f a) fmap _ (IError path err) = IError path err {-# INLINE fmap #-} instance Functor Result where fmap f (Success a) = Success (f a) fmap _ (Error err) = Error err {-# INLINE fmap #-} instance Monad IResult where return = pure {-# INLINE return #-} ISuccess a >>= k = k a IError path err >>= _ = IError path err {-# INLINE (>>=) #-} fail = Fail.fail {-# INLINE fail #-} instance Fail.MonadFail IResult where fail err = IError [] err {-# INLINE fail #-} instance Monad Result where return = pure {-# INLINE return #-} Success a >>= k = k a Error err >>= _ = Error err {-# INLINE (>>=) #-} fail = Fail.fail {-# INLINE fail #-} instance Fail.MonadFail Result where fail err = Error err {-# INLINE fail #-} instance Applicative IResult where pure = ISuccess {-# INLINE pure #-} (<*>) = ap {-# INLINE (<*>) #-} instance Applicative Result where pure = Success {-# INLINE pure #-} (<*>) = ap {-# INLINE (<*>) #-} instance MonadPlus IResult where mzero = fail "mzero" {-# INLINE mzero #-} mplus a@(ISuccess _) _ = a mplus _ b = b {-# INLINE mplus #-} instance MonadPlus Result where mzero = fail "mzero" {-# INLINE mzero #-} mplus a@(Success _) _ = a mplus _ b = b {-# INLINE mplus #-} instance Alternative IResult where empty = mzero {-# INLINE empty #-} (<|>) = mplus {-# INLINE (<|>) #-} instance Alternative Result where empty = mzero {-# INLINE empty #-} (<|>) = mplus {-# INLINE (<|>) #-} instance Semigroup (IResult a) where (<>) = mplus {-# INLINE (<>) #-} instance Monoid (IResult a) where mempty = fail "mempty" {-# INLINE mempty #-} mappend = (<>) {-# INLINE mappend #-} instance Semigroup (Result a) where (<>) = mplus {-# INLINE (<>) #-} instance Monoid (Result a) where mempty = fail "mempty" {-# INLINE mempty #-} mappend = (<>) {-# INLINE mappend #-} instance Foldable IResult where foldMap _ (IError _ _) = mempty foldMap f (ISuccess y) = f y {-# INLINE foldMap #-} foldr _ z (IError _ _) = z foldr f z (ISuccess y) = f y z {-# INLINE foldr #-} instance Foldable Result where foldMap _ (Error _) = mempty foldMap f (Success y) = f y {-# INLINE foldMap #-} foldr _ z (Error _) = z foldr f z (Success y) = f y z {-# INLINE foldr #-} instance Traversable IResult where traverse _ (IError path err) = pure (IError path err) traverse f (ISuccess a) = ISuccess <$> f a {-# INLINE traverse #-} instance Traversable Result where traverse _ (Error err) = pure (Error err) traverse f (Success a) = Success <$> f a {-# INLINE traverse #-} -- | Failure continuation. type Failure f r = JSONPath -> String -> f r -- | Success continuation. type Success a f r = a -> f r -- | A JSON parser. N.B. This might not fit your usual understanding of -- "parser". Instead you might like to think of 'Parser' as a "parse result", -- i.e. a parser to which the input has already been applied. newtype Parser a = Parser { runParser :: forall f r. JSONPath -> Failure f r -> Success a f r -> f r } instance Monad Parser where m >>= g = Parser $ \path kf ks -> let ks' a = runParser (g a) path kf ks in runParser m path kf ks' {-# INLINE (>>=) #-} return = pure {-# INLINE return #-} fail = Fail.fail {-# INLINE fail #-} instance Fail.MonadFail Parser where fail msg = Parser $ \path kf _ks -> kf (reverse path) msg {-# INLINE fail #-} instance Functor Parser where fmap f m = Parser $ \path kf ks -> let ks' a = ks (f a) in runParser m path kf ks' {-# INLINE fmap #-} instance Applicative Parser where pure a = Parser $ \_path _kf ks -> ks a {-# INLINE pure #-} (<*>) = apP {-# INLINE (<*>) #-} instance Alternative Parser where empty = fail "empty" {-# INLINE empty #-} (<|>) = mplus {-# INLINE (<|>) #-} instance MonadPlus Parser where mzero = fail "mzero" {-# INLINE mzero #-} mplus a b = Parser $ \path kf ks -> let kf' _ _ = runParser b path kf ks in runParser a path kf' ks {-# INLINE mplus #-} instance Semigroup (Parser a) where (<>) = mplus {-# INLINE (<>) #-} instance Monoid (Parser a) where mempty = fail "mempty" {-# INLINE mempty #-} mappend = (<>) {-# INLINE mappend #-} apP :: Parser (a -> b) -> Parser a -> Parser b apP d e = do b <- d b <$> e {-# INLINE apP #-} -- | A JSON \"object\" (key\/value map). type Object = HashMap Text Value -- | A JSON \"array\" (sequence). type Array = Vector Value -- | A JSON value represented as a Haskell value. data Value = Object !Object | Array !Array | String !Text | Number !Scientific | Bool !Bool | Null deriving (Eq, Read, Show, Typeable, Data, Generic) -- | A newtype wrapper for 'UTCTime' that uses the same non-standard -- serialization format as Microsoft .NET, whose -- -- type is by default serialized to JSON as in the following example: -- -- > /Date(1302547608878)/ -- -- The number represents milliseconds since the Unix epoch. newtype DotNetTime = DotNetTime { fromDotNetTime :: UTCTime -- ^ Acquire the underlying value. } deriving (Eq, Ord, Read, Show, Typeable, FormatTime) instance NFData Value where rnf (Object o) = rnf o rnf (Array a) = foldl' (\x y -> rnf y `seq` x) () a rnf (String s) = rnf s rnf (Number n) = rnf n rnf (Bool b) = rnf b rnf Null = () instance IsString Value where fromString = String . pack {-# INLINE fromString #-} hashValue :: Int -> Value -> Int #if MIN_VERSION_unordered_containers(0,2,6) hashValue s (Object o) = s `hashWithSalt` (0::Int) `hashWithSalt` o #else hashValue s (Object o) = foldl' hashWithSalt (s `hashWithSalt` (0::Int)) assocHashesSorted where assocHashesSorted = sort [hash k `hashWithSalt` v | (k, v) <- H.toList o] #endif hashValue s (Array a) = foldl' hashWithSalt (s `hashWithSalt` (1::Int)) a hashValue s (String str) = s `hashWithSalt` (2::Int) `hashWithSalt` str hashValue s (Number n) = s `hashWithSalt` (3::Int) `hashWithSalt` n hashValue s (Bool b) = s `hashWithSalt` (4::Int) `hashWithSalt` b hashValue s Null = s `hashWithSalt` (5::Int) instance Hashable Value where hashWithSalt = hashValue -- @since 0.11.0.0 instance TH.Lift Value where lift Null = [| Null |] lift (Bool b) = [| Bool b |] lift (Number n) = [| Number (S.scientific c e) |] where c = S.coefficient n e = S.base10Exponent n lift (String t) = [| String (pack s) |] where s = unpack t lift (Array a) = [| Array (V.fromList a') |] where a' = V.toList a lift (Object o) = [| Object (H.fromList . map (first pack) $ o') |] where o' = map (first unpack) . H.toList $ o -- | The empty array. emptyArray :: Value emptyArray = Array V.empty -- | Determines if the 'Value' is an empty 'Array'. -- Note that: @isEmptyArray 'emptyArray'@. isEmptyArray :: Value -> Bool isEmptyArray (Array arr) = V.null arr isEmptyArray _ = False -- | The empty object. emptyObject :: Value emptyObject = Object H.empty -- | Run a 'Parser'. parse :: (a -> Parser b) -> a -> Result b parse m v = runParser (m v) [] (const Error) Success {-# INLINE parse #-} -- | Run a 'Parser'. iparse :: (a -> Parser b) -> a -> IResult b iparse m v = runParser (m v) [] IError ISuccess {-# INLINE iparse #-} -- | Run a 'Parser' with a 'Maybe' result type. parseMaybe :: (a -> Parser b) -> a -> Maybe b parseMaybe m v = runParser (m v) [] (\_ _ -> Nothing) Just {-# INLINE parseMaybe #-} -- | Run a 'Parser' with an 'Either' result type. If the parse fails, -- the 'Left' payload will contain an error message. parseEither :: (a -> Parser b) -> a -> Either String b parseEither m v = runParser (m v) [] onError Right where onError path msg = Left (formatError path msg) {-# INLINE parseEither #-} -- | Annotate an error message with a -- error location. formatError :: JSONPath -> String -> String formatError path msg = "Error in " ++ format "$" path ++ ": " ++ msg where format :: String -> JSONPath -> String format pfx [] = pfx format pfx (Index idx:parts) = format (pfx ++ "[" ++ show idx ++ "]") parts format pfx (Key key:parts) = format (pfx ++ formatKey key) parts formatKey :: Text -> String formatKey key | isIdentifierKey strKey = "." ++ strKey | otherwise = "['" ++ escapeKey strKey ++ "']" where strKey = unpack key isIdentifierKey :: String -> Bool isIdentifierKey [] = False isIdentifierKey (x:xs) = isAlpha x && all isAlphaNum xs escapeKey :: String -> String escapeKey = concatMap escapeChar escapeChar :: Char -> String escapeChar '\'' = "\\'" escapeChar '\\' = "\\\\" escapeChar c = [c] -- | A key\/value pair for an 'Object'. type Pair = (Text, Value) -- | Create a 'Value' from a list of name\/value 'Pair's. If duplicate -- keys arise, earlier keys and their associated values win. object :: [Pair] -> Value object = Object . H.fromList {-# INLINE object #-} -- | Add JSON Path context to a parser -- -- When parsing a complex structure, it helps to annotate (sub)parsers -- with context, so that if an error occurs, you can find its location. -- -- > withObject "Person" $ \o -> -- > Person -- > <$> o .: "name" Key "name" -- > <*> o .: "age" Key "age" -- -- (Standard methods like '(.:)' already do this.) -- -- With such annotations, if an error occurs, you will get a JSON Path -- location of that error. -- -- Since 0.10 () :: Parser a -> JSONPathElement -> Parser a p pathElem = Parser $ \path kf ks -> runParser p (pathElem:path) kf ks -- | If the inner @Parser@ failed, modify the failure message using the -- provided function. This allows you to create more descriptive error messages. -- For example: -- -- > parseJSON (Object o) = modifyFailure -- > ("Parsing of the Foo value failed: " ++) -- > (Foo <$> o .: "someField") -- -- Since 0.6.2.0 modifyFailure :: (String -> String) -> Parser a -> Parser a modifyFailure f (Parser p) = Parser $ \path kf ks -> p path (\p' m -> kf p' (f m)) ks -- | Throw a parser error with an additional path. -- -- @since 1.2.1.0 parserThrowError :: JSONPath -> String -> Parser a parserThrowError path' msg = Parser $ \path kf _ks -> kf (reverse path ++ path') msg -- | A handler function to handle previous errors and return to normal execution. -- -- @since 1.2.1.0 parserCatchError :: Parser a -> (JSONPath -> String -> Parser a) -> Parser a parserCatchError (Parser p) handler = Parser $ \path kf ks -> p path (\e msg -> runParser (handler e msg) path kf ks) ks -------------------------------------------------------------------------------- -- Generic and TH encoding configuration -------------------------------------------------------------------------------- -- | Options that specify how to encode\/decode your datatype to\/from JSON. -- -- Options can be set using record syntax on 'defaultOptions' with the fields -- below. data Options = Options { fieldLabelModifier :: String -> String -- ^ Function applied to field labels. -- Handy for removing common record prefixes for example. , constructorTagModifier :: String -> String -- ^ Function applied to constructor tags which could be handy -- for lower-casing them for example. , allNullaryToStringTag :: Bool -- ^ If 'True' the constructors of a datatype, with /all/ -- nullary constructors, will be encoded to just a string with -- the constructor tag. If 'False' the encoding will always -- follow the `sumEncoding`. , omitNothingFields :: Bool -- ^ If 'True' record fields with a 'Nothing' value will be -- omitted from the resulting object. If 'False' the resulting -- object will include those fields mapping to @null@. , sumEncoding :: SumEncoding -- ^ Specifies how to encode constructors of a sum datatype. , unwrapUnaryRecords :: Bool -- ^ Hide the field name when a record constructor has only one -- field, like a newtype. , tagSingleConstructors :: Bool -- ^ Encode types with a single constructor as sums, -- so that `allNullaryToStringTag` and `sumEncoding` apply. } instance Show Options where show (Options f c a o s u t) = "Options {" ++ intercalate ", " [ "fieldLabelModifier =~ " ++ show (f "exampleField") , "constructorTagModifier =~ " ++ show (c "ExampleConstructor") , "allNullaryToStringTag = " ++ show a , "omitNothingFields = " ++ show o , "sumEncoding = " ++ show s , "unwrapUnaryRecords = " ++ show u , "tagSingleConstructors = " ++ show t ] ++ "}" -- | Specifies how to encode constructors of a sum datatype. data SumEncoding = TaggedObject { tagFieldName :: String , contentsFieldName :: String } -- ^ A constructor will be encoded to an object with a field -- 'tagFieldName' which specifies the constructor tag (modified by -- the 'constructorTagModifier'). If the constructor is a record -- the encoded record fields will be unpacked into this object. So -- make sure that your record doesn't have a field with the same -- label as the 'tagFieldName'. Otherwise the tag gets overwritten -- by the encoded value of that field! If the constructor is not a -- record the encoded constructor contents will be stored under -- the 'contentsFieldName' field. | UntaggedValue -- ^ Constructor names won't be encoded. Instead only the contents of the -- constructor will be encoded as if the type had a single constructor. JSON -- encodings have to be disjoint for decoding to work properly. -- -- When decoding, constructors are tried in the order of definition. If some -- encodings overlap, the first one defined will succeed. -- -- /Note:/ Nullary constructors are encoded as strings (using -- 'constructorTagModifier'). Having a nullary constructor alongside a -- single field constructor that encodes to a string leads to ambiguity. -- -- /Note:/ Only the last error is kept when decoding, so in the case of -- malformed JSON, only an error for the last constructor will be reported. | ObjectWithSingleField -- ^ A constructor will be encoded to an object with a single -- field named after the constructor tag (modified by the -- 'constructorTagModifier') which maps to the encoded contents of -- the constructor. | TwoElemArray -- ^ A constructor will be encoded to a 2-element array where the -- first element is the tag of the constructor (modified by the -- 'constructorTagModifier') and the second element the encoded -- contents of the constructor. deriving (Eq, Show) -- | Default encoding 'Options': -- -- @ -- 'Options' -- { 'fieldLabelModifier' = id -- , 'constructorTagModifier' = id -- , 'allNullaryToStringTag' = True -- , 'omitNothingFields' = False -- , 'sumEncoding' = 'defaultTaggedObject' -- , 'unwrapUnaryRecords' = False -- , 'tagSingleConstructors' = False -- } -- @ defaultOptions :: Options defaultOptions = Options { fieldLabelModifier = id , constructorTagModifier = id , allNullaryToStringTag = True , omitNothingFields = False , sumEncoding = defaultTaggedObject , unwrapUnaryRecords = False , tagSingleConstructors = False } -- | Default 'TaggedObject' 'SumEncoding' options: -- -- @ -- defaultTaggedObject = 'TaggedObject' -- { 'tagFieldName' = \"tag\" -- , 'contentsFieldName' = \"contents\" -- } -- @ defaultTaggedObject :: SumEncoding defaultTaggedObject = TaggedObject { tagFieldName = "tag" , contentsFieldName = "contents" } -- | Converts from CamelCase to another lower case, interspersing -- the character between all capital letters and their previous -- entries, except those capital letters that appear together, -- like 'API'. -- -- For use by Aeson template haskell calls. -- -- > camelTo '_' 'CamelCaseAPI' == "camel_case_api" camelTo :: Char -> String -> String {-# DEPRECATED camelTo "Use camelTo2 for better results" #-} camelTo c = lastWasCap True where lastWasCap :: Bool -- ^ Previous was a capital letter -> String -- ^ The remaining string -> String lastWasCap _ [] = [] lastWasCap prev (x : xs) = if isUpper x then if prev then toLower x : lastWasCap True xs else c : toLower x : lastWasCap True xs else x : lastWasCap False xs -- | Better version of 'camelTo'. Example where it works better: -- -- > camelTo '_' 'CamelAPICase' == "camel_apicase" -- > camelTo2 '_' 'CamelAPICase' == "camel_api_case" camelTo2 :: Char -> String -> String camelTo2 c = map toLower . go2 . go1 where go1 "" = "" go1 (x:u:l:xs) | isUpper u && isLower l = x : c : u : l : go1 xs go1 (x:xs) = x : go1 xs go2 "" = "" go2 (l:u:xs) | isLower l && isUpper u = l : c : u : go2 xs go2 (x:xs) = x : go2 xs aeson-1.4.2.0/Data/Aeson/Types/ToJSON.hs0000644000000000000000000027212400000000000015552 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE UndecidableInstances #-} #if __GLASGOW_HASKELL__ >= 706 {-# LANGUAGE PolyKinds #-} #endif #include "overlapping-compat.h" #include "incoherent-compat.h" -- TODO: Drop this when we remove support for Data.Attoparsec.Number {-# OPTIONS_GHC -fno-warn-deprecations #-} module Data.Aeson.Types.ToJSON ( -- * Core JSON classes ToJSON(..) -- * Liftings to unary and binary type constructors , ToJSON1(..) , toJSON1 , toEncoding1 , ToJSON2(..) , toJSON2 , toEncoding2 -- * Generic JSON classes , GToJSON(..) , ToArgs(..) , genericToJSON , genericToEncoding , genericLiftToJSON , genericLiftToEncoding -- * Classes and types for map keys , ToJSONKey(..) , ToJSONKeyFunction(..) , toJSONKeyText , contramapToJSONKeyFunction -- * Object key-value pairs , KeyValue(..) , KeyValuePair(..) , FromPairs(..) -- * Functions needed for documentation -- * Encoding functions , listEncoding , listValue ) where import Prelude.Compat import Control.Applicative (Const(..)) import Control.Monad.ST (ST) import Data.Aeson.Encoding (Encoding, Encoding', Series, dict, emptyArray_) import Data.Aeson.Encoding.Internal ((>*<)) import Data.Aeson.Internal.Functions (mapHashKeyVal, mapKeyVal) import Data.Aeson.Types.Generic (AllNullary, False, IsRecord, One, ProductSize, Tagged2(..), True, Zero, productSize) import Data.Aeson.Types.Internal import Data.Attoparsec.Number (Number(..)) import Data.Bits (unsafeShiftR) import Data.DList (DList) import Data.Fixed (Fixed, HasResolution) import Data.Foldable (toList) import Data.Functor.Compose (Compose(..)) import Data.Functor.Contravariant (Contravariant (..)) import Data.Functor.Identity (Identity(..)) import Data.Functor.Product (Product(..)) import Data.Functor.Sum (Sum(..)) import Data.Int (Int16, Int32, Int64, Int8) import Data.List (intersperse) import Data.List.NonEmpty (NonEmpty(..)) import Data.Semigroup ((<>)) import Data.Proxy (Proxy(..)) import Data.Ratio (Ratio, denominator, numerator) import Data.Scientific (Scientific) import Data.Tagged (Tagged(..)) import Data.Text (Text, pack) import Data.Time (Day, DiffTime, LocalTime, NominalDiffTime, TimeOfDay, UTCTime, ZonedTime) import Data.Time.Format (FormatTime, formatTime) import Data.Time.Locale.Compat (defaultTimeLocale) import Data.Vector (Vector) import Data.Version (Version, showVersion) import Data.Void (Void, absurd) import Data.Word (Word16, Word32, Word64, Word8) import Foreign.Storable (Storable) import Foreign.C.Types (CTime (..)) import GHC.Generics import Numeric.Natural (Natural) import qualified Data.Aeson.Encoding as E import qualified Data.Aeson.Encoding.Internal as E (InArray, comma, econcat, retagEncoding) import qualified Data.ByteString as S import qualified Data.ByteString.Lazy as L import qualified Data.DList as DList import qualified Data.HashMap.Strict as H import qualified Data.HashSet as HashSet import qualified Data.IntMap as IntMap import qualified Data.IntSet as IntSet import qualified Data.List.NonEmpty as NE import qualified Data.Map as M import qualified Data.Monoid as Monoid import qualified Data.Scientific as Scientific import qualified Data.Semigroup as Semigroup import qualified Data.Sequence as Seq import qualified Data.Set as Set import qualified Data.Text as T import qualified Data.Text.Encoding as T import qualified Data.Text.Lazy as LT import qualified Data.Tree as Tree import qualified Data.UUID.Types as UUID import qualified Data.Vector as V import qualified Data.Vector.Generic as VG import qualified Data.Vector.Mutable as VM import qualified Data.Vector.Primitive as VP import qualified Data.Vector.Storable as VS import qualified Data.Vector.Unboxed as VU import qualified Data.Aeson.Encoding.Builder as EB import qualified Data.ByteString.Builder as B import qualified GHC.Exts as Exts import qualified Data.Primitive.Array as PM import qualified Data.Primitive.SmallArray as PM import qualified Data.Primitive.Types as PM #if MIN_VERSION_primitive(0,6,4) import qualified Data.Primitive.UnliftedArray as PM import qualified Data.Primitive.PrimArray as PM #endif #if !(MIN_VERSION_bytestring(0,10,0)) import Foreign.ForeignPtr (withForeignPtr) import Foreign.Marshal.Utils (copyBytes) import Foreign.Ptr (plusPtr) import qualified Data.ByteString.Internal as S import qualified Data.ByteString.Lazy.Internal as L #endif {-# ANN module ("HLint: ignore Reduce duplication"::String) #-} toJSONPair :: (a -> Value) -> (b -> Value) -> (a, b) -> Value toJSONPair a b = liftToJSON2 a (listValue a) b (listValue b) {-# INLINE toJSONPair #-} realFloatToJSON :: RealFloat a => a -> Value realFloatToJSON d | isNaN d || isInfinite d = Null | otherwise = Number $ Scientific.fromFloatDigits d {-# INLINE realFloatToJSON #-} ------------------------------------------------------------------------------- -- Generics ------------------------------------------------------------------------------- -- | Class of generic representation types that can be converted to -- JSON. class GToJSON enc arity f where -- | This method (applied to 'defaultOptions') is used as the -- default generic implementation of 'toJSON' -- (with @enc ~ 'Value'@ and @arity ~ 'Zero'@) -- and 'liftToJSON' (if the @arity@ is 'One'). -- -- It also provides a generic implementation of 'toEncoding' -- (with @enc ~ 'Encoding'@ and @arity ~ 'Zero'@) -- and 'liftToEncoding' (if the @arity@ is 'One'). gToJSON :: Options -> ToArgs enc arity a -> f a -> enc -- | A 'ToArgs' value either stores nothing (for 'ToJSON') or it stores the two -- function arguments that encode occurrences of the type parameter (for -- 'ToJSON1'). data ToArgs res arity a where NoToArgs :: ToArgs res Zero a To1Args :: (a -> res) -> ([a] -> res) -> ToArgs res One a -- | A configurable generic JSON creator. This function applied to -- 'defaultOptions' is used as the default for 'toJSON' when the type -- is an instance of 'Generic'. genericToJSON :: (Generic a, GToJSON Value Zero (Rep a)) => Options -> a -> Value genericToJSON opts = gToJSON opts NoToArgs . from -- | A configurable generic JSON creator. This function applied to -- 'defaultOptions' is used as the default for 'liftToJSON' when the type -- is an instance of 'Generic1'. genericLiftToJSON :: (Generic1 f, GToJSON Value One (Rep1 f)) => Options -> (a -> Value) -> ([a] -> Value) -> f a -> Value genericLiftToJSON opts tj tjl = gToJSON opts (To1Args tj tjl) . from1 -- | A configurable generic JSON encoder. This function applied to -- 'defaultOptions' is used as the default for 'toEncoding' when the type -- is an instance of 'Generic'. genericToEncoding :: (Generic a, GToJSON Encoding Zero (Rep a)) => Options -> a -> Encoding genericToEncoding opts = gToJSON opts NoToArgs . from -- | A configurable generic JSON encoder. This function applied to -- 'defaultOptions' is used as the default for 'liftToEncoding' when the type -- is an instance of 'Generic1'. genericLiftToEncoding :: (Generic1 f, GToJSON Encoding One (Rep1 f)) => Options -> (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding genericLiftToEncoding opts te tel = gToJSON opts (To1Args te tel) . from1 ------------------------------------------------------------------------------- -- Class ------------------------------------------------------------------------------- -- | A type that can be converted to JSON. -- -- Instances in general /must/ specify 'toJSON' and /should/ (but don't need -- to) specify 'toEncoding'. -- -- An example type and instance: -- -- @ -- \-- Allow ourselves to write 'Text' literals. -- {-\# LANGUAGE OverloadedStrings #-} -- -- data Coord = Coord { x :: Double, y :: Double } -- -- instance 'ToJSON' Coord where -- 'toJSON' (Coord x y) = 'object' [\"x\" '.=' x, \"y\" '.=' y] -- -- 'toEncoding' (Coord x y) = 'pairs' (\"x\" '.=' x '<>' \"y\" '.=' y) -- @ -- -- Instead of manually writing your 'ToJSON' instance, there are two options -- to do it automatically: -- -- * "Data.Aeson.TH" provides Template Haskell functions which will derive an -- instance at compile time. The generated instance is optimized for your type -- so it will probably be more efficient than the following option. -- -- * The compiler can provide a default generic implementation for -- 'toJSON'. -- -- To use the second, simply add a @deriving 'Generic'@ clause to your -- datatype and declare a 'ToJSON' instance. If you require nothing other than -- 'defaultOptions', it is sufficient to write (and this is the only -- alternative where the default 'toJSON' implementation is sufficient): -- -- @ -- {-\# LANGUAGE DeriveGeneric \#-} -- -- import "GHC.Generics" -- -- data Coord = Coord { x :: Double, y :: Double } deriving 'Generic' -- -- instance 'ToJSON' Coord where -- 'toEncoding' = 'genericToEncoding' 'defaultOptions' -- @ -- -- If on the other hand you wish to customize the generic decoding, you have -- to implement both methods: -- -- @ -- customOptions = 'defaultOptions' -- { 'fieldLabelModifier' = 'map' 'Data.Char.toUpper' -- } -- -- instance 'ToJSON' Coord where -- 'toJSON' = 'genericToJSON' customOptions -- 'toEncoding' = 'genericToEncoding' customOptions -- @ -- -- Previous versions of this library only had the 'toJSON' method. Adding -- 'toEncoding' had two reasons: -- -- 1. toEncoding is more efficient for the common case that the output of -- 'toJSON' is directly serialized to a @ByteString@. -- Further, expressing either method in terms of the other would be -- non-optimal. -- -- 2. The choice of defaults allows a smooth transition for existing users: -- Existing instances that do not define 'toEncoding' still -- compile and have the correct semantics. This is ensured by making -- the default implementation of 'toEncoding' use 'toJSON'. This produces -- correct results, but since it performs an intermediate conversion to a -- 'Value', it will be less efficient than directly emitting an 'Encoding'. -- (this also means that specifying nothing more than -- @instance ToJSON Coord@ would be sufficient as a generically decoding -- instance, but there probably exists no good reason to not specify -- 'toEncoding' in new instances.) class ToJSON a where -- | Convert a Haskell value to a JSON-friendly intermediate type. toJSON :: a -> Value default toJSON :: (Generic a, GToJSON Value Zero (Rep a)) => a -> Value toJSON = genericToJSON defaultOptions -- | Encode a Haskell value as JSON. -- -- The default implementation of this method creates an -- intermediate 'Value' using 'toJSON'. This provides -- source-level compatibility for people upgrading from older -- versions of this library, but obviously offers no performance -- advantage. -- -- To benefit from direct encoding, you /must/ provide an -- implementation for this method. The easiest way to do so is by -- having your types implement 'Generic' using the @DeriveGeneric@ -- extension, and then have GHC generate a method body as follows. -- -- @ -- instance 'ToJSON' Coord where -- 'toEncoding' = 'genericToEncoding' 'defaultOptions' -- @ toEncoding :: a -> Encoding toEncoding = E.value . toJSON {-# INLINE toEncoding #-} toJSONList :: [a] -> Value toJSONList = listValue toJSON {-# INLINE toJSONList #-} toEncodingList :: [a] -> Encoding toEncodingList = listEncoding toEncoding {-# INLINE toEncodingList #-} ------------------------------------------------------------------------------- -- Object key-value pairs ------------------------------------------------------------------------------- -- | A key-value pair for encoding a JSON object. class KeyValue kv where (.=) :: ToJSON v => Text -> v -> kv infixr 8 .= instance KeyValue Series where name .= value = E.pair name (toEncoding value) {-# INLINE (.=) #-} instance KeyValue Pair where name .= value = (name, toJSON value) {-# INLINE (.=) #-} -- | Constructs a singleton 'H.HashMap'. For calling functions that -- demand an 'Object' for constructing objects. To be used in -- conjunction with 'mconcat'. Prefer to use 'object' where possible. instance KeyValue Object where name .= value = H.singleton name (toJSON value) {-# INLINE (.=) #-} ------------------------------------------------------------------------------- -- Classes and types for map keys ------------------------------------------------------------------------------- -- | Typeclass for types that can be used as the key of a map-like container -- (like 'Map' or 'HashMap'). For example, since 'Text' has a 'ToJSONKey' -- instance and 'Char' has a 'ToJSON' instance, we can encode a value of -- type 'Map' 'Text' 'Char': -- -- >>> LBC8.putStrLn $ encode $ Map.fromList [("foo" :: Text, 'a')] -- {"foo":"a"} -- -- Since 'Int' also has a 'ToJSONKey' instance, we can similarly write: -- -- >>> LBC8.putStrLn $ encode $ Map.fromList [(5 :: Int, 'a')] -- {"5":"a"} -- -- JSON documents only accept strings as object keys. For any type -- from @base@ that has a natural textual representation, it can be -- expected that its 'ToJSONKey' instance will choose that representation. -- -- For data types that lack a natural textual representation, an alternative -- is provided. The map-like container is represented as a JSON array -- instead of a JSON object. Each value in the array is an array with -- exactly two values. The first is the key and the second is the value. -- -- For example, values of type '[Text]' cannot be encoded to a -- string, so a 'Map' with keys of type '[Text]' is encoded as follows: -- -- >>> LBC8.putStrLn $ encode $ Map.fromList [(["foo","bar","baz" :: Text], 'a')] -- [[["foo","bar","baz"],"a"]] -- -- The default implementation of 'ToJSONKey' chooses this method of -- encoding a key, using the 'ToJSON' instance of the type. -- -- To use your own data type as the key in a map, all that is needed -- is to write a 'ToJSONKey' (and possibly a 'FromJSONKey') instance -- for it. If the type cannot be trivially converted to and from 'Text', -- it is recommended that 'ToJSONKeyValue' is used. Since the default -- implementations of the typeclass methods can build this from a -- 'ToJSON' instance, there is nothing that needs to be written: -- -- > data Foo = Foo { fooAge :: Int, fooName :: Text } -- > deriving (Eq,Ord,Generic) -- > instance ToJSON Foo -- > instance ToJSONKey Foo -- -- That's it. We can now write: -- -- >>> let m = Map.fromList [(Foo 4 "bar",'a'),(Foo 6 "arg",'b')] -- >>> LBC8.putStrLn $ encode m -- [[{"fooName":"bar","fooAge":4},"a"],[{"fooName":"arg","fooAge":6},"b"]] -- -- The next case to consider is if we have a type that is a -- newtype wrapper around 'Text'. The recommended approach is to use -- generalized newtype deriving: -- -- > newtype RecordId = RecordId { getRecordId :: Text} -- > deriving (Eq,Ord,ToJSONKey) -- -- Then we may write: -- -- >>> LBC8.putStrLn $ encode $ Map.fromList [(RecordId "abc",'a')] -- {"abc":"a"} -- -- Simple sum types are a final case worth considering. Suppose we have: -- -- > data Color = Red | Green | Blue -- > deriving (Show,Read,Eq,Ord) -- -- It is possible to get the 'ToJSONKey' instance for free as we did -- with 'Foo'. However, in this case, we have a natural way to go to -- and from 'Text' that does not require any escape sequences. So, in -- this example, 'ToJSONKeyText' will be used instead of 'ToJSONKeyValue'. -- The 'Show' instance can be used to help write 'ToJSONKey': -- -- > instance ToJSONKey Color where -- > toJSONKey = ToJSONKeyText f g -- > where f = Text.pack . show -- > g = text . Text.pack . show -- > -- text function is from Data.Aeson.Encoding -- -- The situation of needing to turning function @a -> Text@ into -- a 'ToJSONKeyFunction' is common enough that a special combinator -- is provided for it. The above instance can be rewritten as: -- -- > instance ToJSONKey Color where -- > toJSONKey = toJSONKeyText (Text.pack . show) -- -- The performance of the above instance can be improved by -- not using 'String' as an intermediate step when converting to -- 'Text'. One option for improving performance would be to use -- template haskell machinery from the @text-show@ package. However, -- even with the approach, the 'Encoding' (a wrapper around a bytestring -- builder) is generated by encoding the 'Text' to a 'ByteString', -- an intermediate step that could be avoided. The fastest possible -- implementation would be: -- -- > -- Assuming that OverloadedStrings is enabled -- > instance ToJSONKey Color where -- > toJSONKey = ToJSONKeyText f g -- > where f x = case x of {Red -> "Red";Green ->"Green";Blue -> "Blue"} -- > g x = case x of {Red -> text "Red";Green -> text "Green";Blue -> text "Blue"} -- > -- text function is from Data.Aeson.Encoding -- -- This works because GHC can lift the encoded values out of the case -- statements, which means that they are only evaluated once. This -- approach should only be used when there is a serious need to -- maximize performance. class ToJSONKey a where -- | Strategy for rendering the key for a map-like container. toJSONKey :: ToJSONKeyFunction a default toJSONKey :: ToJSON a => ToJSONKeyFunction a toJSONKey = ToJSONKeyValue toJSON toEncoding -- | This is similar in spirit to the 'showsList' method of 'Show'. -- It makes it possible to give 'String' keys special treatment -- without using @OverlappingInstances@. End users should always -- be able to use the default implementation of this method. toJSONKeyList :: ToJSONKeyFunction [a] default toJSONKeyList :: ToJSON a => ToJSONKeyFunction [a] toJSONKeyList = ToJSONKeyValue toJSON toEncoding data ToJSONKeyFunction a = ToJSONKeyText !(a -> Text) !(a -> Encoding' Text) -- ^ key is encoded to string, produces object | ToJSONKeyValue !(a -> Value) !(a -> Encoding) -- ^ key is encoded to value, produces array -- | Helper for creating textual keys. -- -- @ -- instance 'ToJSONKey' MyKey where -- 'toJSONKey' = 'toJSONKeyText' myKeyToText -- where -- myKeyToText = Text.pack . show -- or showt from text-show -- @ toJSONKeyText :: (a -> Text) -> ToJSONKeyFunction a toJSONKeyText f = ToJSONKeyText f (E.text . f) -- | TODO: should this be exported? toJSONKeyTextEnc :: (a -> Encoding' Text) -> ToJSONKeyFunction a toJSONKeyTextEnc e = ToJSONKeyText tot e where -- TODO: dropAround is also used in stringEncoding, which is unfortunate atm tot = T.dropAround (== '"') . T.decodeLatin1 . lazyToStrictByteString . E.encodingToLazyByteString . e instance Contravariant ToJSONKeyFunction where contramap = contramapToJSONKeyFunction -- | Contravariant map, as 'ToJSONKeyFunction' is a contravariant functor. contramapToJSONKeyFunction :: (b -> a) -> ToJSONKeyFunction a -> ToJSONKeyFunction b contramapToJSONKeyFunction h x = case x of ToJSONKeyText f g -> ToJSONKeyText (f . h) (g . h) ToJSONKeyValue f g -> ToJSONKeyValue (f . h) (g . h) ------------------------------------------------------------------------------- -- Lifings of FromJSON and ToJSON to unary and binary type constructors ------------------------------------------------------------------------------- -- | Lifting of the 'ToJSON' class to unary type constructors. -- -- Instead of manually writing your 'ToJSON1' instance, there are two options -- to do it automatically: -- -- * "Data.Aeson.TH" provides Template Haskell functions which will derive an -- instance at compile time. The generated instance is optimized for your type -- so it will probably be more efficient than the following option. -- -- * The compiler can provide a default generic implementation for -- 'toJSON1'. -- -- To use the second, simply add a @deriving 'Generic1'@ clause to your -- datatype and declare a 'ToJSON1' instance for your datatype without giving -- definitions for 'liftToJSON' or 'liftToEncoding'. -- -- For example: -- -- @ -- {-\# LANGUAGE DeriveGeneric \#-} -- -- import "GHC.Generics" -- -- data Pair = Pair { pairFst :: a, pairSnd :: b } deriving 'Generic1' -- -- instance 'ToJSON' a => 'ToJSON1' (Pair a) -- @ -- -- If the default implementation doesn't give exactly the results you want, -- you can customize the generic encoding with only a tiny amount of -- effort, using 'genericLiftToJSON' and 'genericLiftToEncoding' with -- your preferred 'Options': -- -- @ -- customOptions = 'defaultOptions' -- { 'fieldLabelModifier' = 'map' 'Data.Char.toUpper' -- } -- -- instance 'ToJSON' a => 'ToJSON1' (Pair a) where -- 'liftToJSON' = 'genericLiftToJSON' customOptions -- 'liftToEncoding' = 'genericLiftToEncoding' customOptions -- @ -- -- See also 'ToJSON'. class ToJSON1 f where liftToJSON :: (a -> Value) -> ([a] -> Value) -> f a -> Value default liftToJSON :: (Generic1 f, GToJSON Value One (Rep1 f)) => (a -> Value) -> ([a] -> Value) -> f a -> Value liftToJSON = genericLiftToJSON defaultOptions liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [f a] -> Value liftToJSONList f g = listValue (liftToJSON f g) liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding default liftToEncoding :: (Generic1 f, GToJSON Encoding One (Rep1 f)) => (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding liftToEncoding = genericLiftToEncoding defaultOptions liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [f a] -> Encoding liftToEncodingList f g = listEncoding (liftToEncoding f g) -- | Lift the standard 'toJSON' function through the type constructor. toJSON1 :: (ToJSON1 f, ToJSON a) => f a -> Value toJSON1 = liftToJSON toJSON toJSONList {-# INLINE toJSON1 #-} -- | Lift the standard 'toEncoding' function through the type constructor. toEncoding1 :: (ToJSON1 f, ToJSON a) => f a -> Encoding toEncoding1 = liftToEncoding toEncoding toEncodingList {-# INLINE toEncoding1 #-} -- | Lifting of the 'ToJSON' class to binary type constructors. -- -- Instead of manually writing your 'ToJSON2' instance, "Data.Aeson.TH" -- provides Template Haskell functions which will derive an instance at compile time. -- -- The compiler cannot provide a default generic implementation for 'liftToJSON2', -- unlike 'toJSON' and 'liftToJSON'. class ToJSON2 f where liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> f a b -> Value liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [f a b] -> Value liftToJSONList2 fa ga fb gb = listValue (liftToJSON2 fa ga fb gb) liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> f a b -> Encoding liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [f a b] -> Encoding liftToEncodingList2 fa ga fb gb = listEncoding (liftToEncoding2 fa ga fb gb) -- | Lift the standard 'toJSON' function through the type constructor. toJSON2 :: (ToJSON2 f, ToJSON a, ToJSON b) => f a b -> Value toJSON2 = liftToJSON2 toJSON toJSONList toJSON toJSONList {-# INLINE toJSON2 #-} -- | Lift the standard 'toEncoding' function through the type constructor. toEncoding2 :: (ToJSON2 f, ToJSON a, ToJSON b) => f a b -> Encoding toEncoding2 = liftToEncoding2 toEncoding toEncodingList toEncoding toEncodingList {-# INLINE toEncoding2 #-} ------------------------------------------------------------------------------- -- Encoding functions ------------------------------------------------------------------------------- -- | Helper function to use with 'liftToEncoding'. -- Useful when writing own 'ToJSON1' instances. -- -- @ -- newtype F a = F [a] -- -- -- This instance encodes 'String' as an array of chars -- instance 'ToJSON1' F where -- 'liftToJSON' tj _ (F xs) = 'liftToJSON' tj ('listValue' tj) xs -- 'liftToEncoding' te _ (F xs) = 'liftToEncoding' te ('listEncoding' te) xs -- -- instance 'Data.Aeson.FromJSON.FromJSON1' F where -- 'Data.Aeson.FromJSON.liftParseJSON' p _ v = F \<$\> 'Data.Aeson.FromJSON.liftParseJSON' p ('Data.Aeson.FromJSON.listParser' p) v -- @ listEncoding :: (a -> Encoding) -> [a] -> Encoding listEncoding = E.list {-# INLINE listEncoding #-} -- | Helper function to use with 'liftToJSON', see 'listEncoding'. listValue :: (a -> Value) -> [a] -> Value listValue f = Array . V.fromList . map f {-# INLINE listValue #-} ------------------------------------------------------------------------------- -- [] instances ------------------------------------------------------------------------------- -- These are needed for key-class default definitions instance ToJSON1 [] where liftToJSON _ to' = to' {-# INLINE liftToJSON #-} liftToEncoding _ to' = to' {-# INLINE liftToEncoding #-} instance (ToJSON a) => ToJSON [a] where {-# SPECIALIZE instance ToJSON String #-} {-# SPECIALIZE instance ToJSON [String] #-} {-# SPECIALIZE instance ToJSON [Array] #-} {-# SPECIALIZE instance ToJSON [Object] #-} toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- Generic toJSON / toEncoding ------------------------------------------------------------------------------- instance OVERLAPPABLE_ (GToJSON enc arity a) => GToJSON enc arity (M1 i c a) where -- Meta-information, which is not handled elsewhere, is ignored: gToJSON opts targs = gToJSON opts targs . unM1 {-# INLINE gToJSON #-} instance GToJSON enc One Par1 where -- Direct occurrences of the last type parameter are encoded with the -- function passed in as an argument: gToJSON _opts (To1Args tj _) = tj . unPar1 {-# INLINE gToJSON #-} instance ( ConsToJSON enc arity a , AllNullary (C1 c a) allNullary , SumToJSON enc arity (C1 c a) allNullary ) => GToJSON enc arity (D1 d (C1 c a)) where -- The option 'tagSingleConstructors' determines whether to wrap -- a single-constructor type. gToJSON opts targs | tagSingleConstructors opts = (unTagged :: Tagged allNullary enc -> enc) . sumToJSON opts targs . unM1 | otherwise = consToJSON opts targs . unM1 . unM1 {-# INLINE gToJSON #-} instance (ConsToJSON enc arity a) => GToJSON enc arity (C1 c a) where -- Constructors need to be encoded differently depending on whether they're -- a record or not. This distinction is made by 'consToJSON': gToJSON opts targs = consToJSON opts targs . unM1 {-# INLINE gToJSON #-} instance ( AllNullary (a :+: b) allNullary , SumToJSON enc arity (a :+: b) allNullary ) => GToJSON enc arity (a :+: b) where -- If all constructors of a sum datatype are nullary and the -- 'allNullaryToStringTag' option is set they are encoded to -- strings. This distinction is made by 'sumToJSON': gToJSON opts targs = (unTagged :: Tagged allNullary enc -> enc) . sumToJSON opts targs {-# INLINE gToJSON #-} -------------------------------------------------------------------------------- -- Generic toJSON -- Note: Refactoring 'ToJSON a' to 'ToJSON enc a' (and 'ToJSON1' similarly) is -- possible but makes error messages a bit harder to understand for missing -- instances. instance GToJSON Value arity V1 where -- Empty values do not exist, which makes the job of formatting them -- rather easy: gToJSON _ _ x = x `seq` error "case: V1" {-# INLINE gToJSON #-} instance ToJSON a => GToJSON Value arity (K1 i a) where -- Constant values are encoded using their ToJSON instance: gToJSON _opts _ = toJSON . unK1 {-# INLINE gToJSON #-} instance ToJSON1 f => GToJSON Value One (Rec1 f) where -- Recursive occurrences of the last type parameter are encoded using their -- ToJSON1 instance: gToJSON _opts (To1Args tj tjl) = liftToJSON tj tjl . unRec1 {-# INLINE gToJSON #-} instance GToJSON Value arity U1 where -- Empty constructors are encoded to an empty array: gToJSON _opts _ _ = emptyArray {-# INLINE gToJSON #-} instance ( WriteProduct arity a, WriteProduct arity b , ProductSize a, ProductSize b ) => GToJSON Value arity (a :*: b) where -- Products are encoded to an array. Here we allocate a mutable vector of -- the same size as the product and write the product's elements to it using -- 'writeProduct': gToJSON opts targs p = Array $ V.create $ do mv <- VM.unsafeNew lenProduct writeProduct opts targs mv 0 lenProduct p return mv where lenProduct = (unTagged2 :: Tagged2 (a :*: b) Int -> Int) productSize {-# INLINE gToJSON #-} instance ( ToJSON1 f , GToJSON Value One g ) => GToJSON Value One (f :.: g) where -- If an occurrence of the last type parameter is nested inside two -- composed types, it is encoded by using the outermost type's ToJSON1 -- instance to generically encode the innermost type: gToJSON opts targs = let gtj = gToJSON opts targs in liftToJSON gtj (listValue gtj) . unComp1 {-# INLINE gToJSON #-} -------------------------------------------------------------------------------- -- Generic toEncoding instance ToJSON a => GToJSON Encoding arity (K1 i a) where -- Constant values are encoded using their ToJSON instance: gToJSON _opts _ = toEncoding . unK1 {-# INLINE gToJSON #-} instance ToJSON1 f => GToJSON Encoding One (Rec1 f) where -- Recursive occurrences of the last type parameter are encoded using their -- ToEncoding1 instance: gToJSON _opts (To1Args te tel) = liftToEncoding te tel . unRec1 {-# INLINE gToJSON #-} instance GToJSON Encoding arity U1 where -- Empty constructors are encoded to an empty array: gToJSON _opts _ _ = E.emptyArray_ {-# INLINE gToJSON #-} instance ( EncodeProduct arity a , EncodeProduct arity b ) => GToJSON Encoding arity (a :*: b) where -- Products are encoded to an array. Here we allocate a mutable vector of -- the same size as the product and write the product's elements to it using -- 'encodeProduct': gToJSON opts targs p = E.list E.retagEncoding [encodeProduct opts targs p] {-# INLINE gToJSON #-} instance ( ToJSON1 f , GToJSON Encoding One g ) => GToJSON Encoding One (f :.: g) where -- If an occurrence of the last type parameter is nested inside two -- composed types, it is encoded by using the outermost type's ToJSON1 -- instance to generically encode the innermost type: gToJSON opts targs = let gte = gToJSON opts targs in liftToEncoding gte (listEncoding gte) . unComp1 {-# INLINE gToJSON #-} -------------------------------------------------------------------------------- class SumToJSON enc arity f allNullary where sumToJSON :: Options -> ToArgs enc arity a -> f a -> Tagged allNullary enc instance ( GetConName f , FromString enc , TaggedObject enc arity f , SumToJSON' ObjectWithSingleField enc arity f , SumToJSON' TwoElemArray enc arity f , SumToJSON' UntaggedValue enc arity f ) => SumToJSON enc arity f True where sumToJSON opts targs | allNullaryToStringTag opts = Tagged . fromString . constructorTagModifier opts . getConName | otherwise = Tagged . nonAllNullarySumToJSON opts targs instance ( TaggedObject enc arity f , SumToJSON' ObjectWithSingleField enc arity f , SumToJSON' TwoElemArray enc arity f , SumToJSON' UntaggedValue enc arity f ) => SumToJSON enc arity f False where sumToJSON opts targs = Tagged . nonAllNullarySumToJSON opts targs nonAllNullarySumToJSON :: ( TaggedObject enc arity f , SumToJSON' ObjectWithSingleField enc arity f , SumToJSON' TwoElemArray enc arity f , SumToJSON' UntaggedValue enc arity f ) => Options -> ToArgs enc arity a -> f a -> enc nonAllNullarySumToJSON opts targs = case sumEncoding opts of TaggedObject{..} -> taggedObject opts targs tagFieldName contentsFieldName ObjectWithSingleField -> (unTagged :: Tagged ObjectWithSingleField enc -> enc) . sumToJSON' opts targs TwoElemArray -> (unTagged :: Tagged TwoElemArray enc -> enc) . sumToJSON' opts targs UntaggedValue -> (unTagged :: Tagged UntaggedValue enc -> enc) . sumToJSON' opts targs -------------------------------------------------------------------------------- class FromString enc where fromString :: String -> enc instance FromString Encoding where fromString = toEncoding instance FromString Value where fromString = String . pack -------------------------------------------------------------------------------- class TaggedObject enc arity f where taggedObject :: Options -> ToArgs enc arity a -> String -> String -> f a -> enc instance ( TaggedObject enc arity a , TaggedObject enc arity b ) => TaggedObject enc arity (a :+: b) where taggedObject opts targs tagFieldName contentsFieldName (L1 x) = taggedObject opts targs tagFieldName contentsFieldName x taggedObject opts targs tagFieldName contentsFieldName (R1 x) = taggedObject opts targs tagFieldName contentsFieldName x instance ( IsRecord a isRecord , TaggedObject' enc pairs arity a isRecord , FromPairs enc pairs , FromString enc , KeyValuePair enc pairs , Constructor c ) => TaggedObject enc arity (C1 c a) where taggedObject opts targs tagFieldName contentsFieldName = fromPairs . mappend tag . contents where tag = tagFieldName `pair` (fromString (constructorTagModifier opts (conName (undefined :: t c a p))) :: enc) contents = (unTagged :: Tagged isRecord pairs -> pairs) . taggedObject' opts targs contentsFieldName . unM1 class TaggedObject' enc pairs arity f isRecord where taggedObject' :: Options -> ToArgs enc arity a -> String -> f a -> Tagged isRecord pairs instance ( GToJSON enc arity f , KeyValuePair enc pairs ) => TaggedObject' enc pairs arity f False where taggedObject' opts targs contentsFieldName = Tagged . (contentsFieldName `pair`) . gToJSON opts targs instance OVERLAPPING_ Monoid pairs => TaggedObject' enc pairs arity U1 False where taggedObject' _ _ _ _ = Tagged mempty instance ( RecordToPairs enc pairs arity f ) => TaggedObject' enc pairs arity f True where taggedObject' opts targs _ = Tagged . recordToPairs opts targs -------------------------------------------------------------------------------- -- | Get the name of the constructor of a sum datatype. class GetConName f where getConName :: f a -> String instance (GetConName a, GetConName b) => GetConName (a :+: b) where getConName (L1 x) = getConName x getConName (R1 x) = getConName x instance (Constructor c) => GetConName (C1 c a) where getConName = conName -------------------------------------------------------------------------------- -- Reflection of SumEncoding variants data ObjectWithSingleField data TwoElemArray data UntaggedValue -------------------------------------------------------------------------------- class SumToJSON' s enc arity f where sumToJSON' :: Options -> ToArgs enc arity a -> f a -> Tagged s enc instance ( SumToJSON' s enc arity a , SumToJSON' s enc arity b ) => SumToJSON' s enc arity (a :+: b) where sumToJSON' opts targs (L1 x) = sumToJSON' opts targs x sumToJSON' opts targs (R1 x) = sumToJSON' opts targs x -------------------------------------------------------------------------------- instance ( GToJSON Value arity a , ConsToJSON Value arity a , Constructor c ) => SumToJSON' TwoElemArray Value arity (C1 c a) where sumToJSON' opts targs x = Tagged $ Array $ V.create $ do mv <- VM.unsafeNew 2 VM.unsafeWrite mv 0 $ String $ pack $ constructorTagModifier opts $ conName (undefined :: t c a p) VM.unsafeWrite mv 1 $ gToJSON opts targs x return mv -------------------------------------------------------------------------------- instance ( GToJSON Encoding arity a , ConsToJSON Encoding arity a , Constructor c ) => SumToJSON' TwoElemArray Encoding arity (C1 c a) where sumToJSON' opts targs x = Tagged $ E.list id [ toEncoding (constructorTagModifier opts (conName (undefined :: t c a p))) , gToJSON opts targs x ] -------------------------------------------------------------------------------- class ConsToJSON enc arity f where consToJSON :: Options -> ToArgs enc arity a -> f a -> enc class ConsToJSON' enc arity f isRecord where consToJSON' :: Options -> ToArgs enc arity a -> f a -> Tagged isRecord enc instance ( IsRecord f isRecord , ConsToJSON' enc arity f isRecord ) => ConsToJSON enc arity f where consToJSON opts targs = (unTagged :: Tagged isRecord enc -> enc) . consToJSON' opts targs {-# INLINE consToJSON #-} instance OVERLAPPING_ ( RecordToPairs enc pairs arity (S1 s f) , FromPairs enc pairs , GToJSON enc arity f ) => ConsToJSON' enc arity (S1 s f) True where consToJSON' opts targs | unwrapUnaryRecords opts = Tagged . gToJSON opts targs | otherwise = Tagged . fromPairs . recordToPairs opts targs {-# INLINE consToJSON' #-} instance ( RecordToPairs enc pairs arity f , FromPairs enc pairs ) => ConsToJSON' enc arity f True where consToJSON' opts targs = Tagged . fromPairs . recordToPairs opts targs {-# INLINE consToJSON' #-} instance GToJSON enc arity f => ConsToJSON' enc arity f False where consToJSON' opts targs = Tagged . gToJSON opts targs {-# INLINE consToJSON' #-} -------------------------------------------------------------------------------- class RecordToPairs enc pairs arity f where -- 1st element: whole thing -- 2nd element: in case the record has only 1 field, just the value -- of the field (without the key); 'Nothing' otherwise recordToPairs :: Options -> ToArgs enc arity a -> f a -> pairs instance ( Monoid pairs , RecordToPairs enc pairs arity a , RecordToPairs enc pairs arity b ) => RecordToPairs enc pairs arity (a :*: b) where recordToPairs opts (targs :: ToArgs enc arity p) (a :*: b) = pairsOf a `mappend` pairsOf b where pairsOf :: (RecordToPairs enc pairs arity f) => f p -> pairs pairsOf = recordToPairs opts targs {-# INLINE recordToPairs #-} instance ( Selector s , GToJSON enc arity a , KeyValuePair enc pairs ) => RecordToPairs enc pairs arity (S1 s a) where recordToPairs = fieldToPair {-# INLINE recordToPairs #-} instance INCOHERENT_ ( Selector s , GToJSON enc arity (K1 i (Maybe a)) , KeyValuePair enc pairs , Monoid pairs ) => RecordToPairs enc pairs arity (S1 s (K1 i (Maybe a))) where recordToPairs opts _ (M1 k1) | omitNothingFields opts , K1 Nothing <- k1 = mempty recordToPairs opts targs m1 = fieldToPair opts targs m1 {-# INLINE recordToPairs #-} instance INCOHERENT_ ( Selector s , GToJSON enc arity (K1 i (Maybe a)) , KeyValuePair enc pairs , Monoid pairs ) => RecordToPairs enc pairs arity (S1 s (K1 i (Semigroup.Option a))) where recordToPairs opts targs = recordToPairs opts targs . unwrap where unwrap :: S1 s (K1 i (Semigroup.Option a)) p -> S1 s (K1 i (Maybe a)) p unwrap (M1 (K1 (Semigroup.Option a))) = M1 (K1 a) {-# INLINE recordToPairs #-} fieldToPair :: (Selector s , GToJSON enc arity a , KeyValuePair enc pairs) => Options -> ToArgs enc arity p -> S1 s a p -> pairs fieldToPair opts targs m1 = let key = fieldLabelModifier opts (selName m1) value = gToJSON opts targs (unM1 m1) in key `pair` value {-# INLINE fieldToPair #-} -------------------------------------------------------------------------------- class WriteProduct arity f where writeProduct :: Options -> ToArgs Value arity a -> VM.MVector s Value -> Int -- ^ index -> Int -- ^ length -> f a -> ST s () instance ( WriteProduct arity a , WriteProduct arity b ) => WriteProduct arity (a :*: b) where writeProduct opts targs mv ix len (a :*: b) = do writeProduct opts targs mv ix lenL a writeProduct opts targs mv ixR lenR b where lenL = len `unsafeShiftR` 1 lenR = len - lenL ixR = ix + lenL {-# INLINE writeProduct #-} instance OVERLAPPABLE_ (GToJSON Value arity a) => WriteProduct arity a where writeProduct opts targs mv ix _ = VM.unsafeWrite mv ix . gToJSON opts targs {-# INLINE writeProduct #-} -------------------------------------------------------------------------------- class EncodeProduct arity f where encodeProduct :: Options -> ToArgs Encoding arity a -> f a -> Encoding' E.InArray instance ( EncodeProduct arity a , EncodeProduct arity b ) => EncodeProduct arity (a :*: b) where encodeProduct opts targs (a :*: b) | omitNothingFields opts = E.econcat $ intersperse E.comma $ filter (not . E.nullEncoding) [encodeProduct opts targs a, encodeProduct opts targs b] encodeProduct opts targs (a :*: b) = encodeProduct opts targs a >*< encodeProduct opts targs b {-# INLINE encodeProduct #-} instance OVERLAPPABLE_ (GToJSON Encoding arity a) => EncodeProduct arity a where encodeProduct opts targs a = E.retagEncoding $ gToJSON opts targs a {-# INLINE encodeProduct #-} -------------------------------------------------------------------------------- instance ( GToJSON enc arity a , ConsToJSON enc arity a , FromPairs enc pairs , KeyValuePair enc pairs , Constructor c ) => SumToJSON' ObjectWithSingleField enc arity (C1 c a) where sumToJSON' opts targs = Tagged . fromPairs . (typ `pair`) . gToJSON opts targs where typ = constructorTagModifier opts $ conName (undefined :: t c a p) -------------------------------------------------------------------------------- instance OVERLAPPABLE_ ( ConsToJSON enc arity a ) => SumToJSON' UntaggedValue enc arity (C1 c a) where sumToJSON' opts targs = Tagged . gToJSON opts targs instance OVERLAPPING_ ( Constructor c , FromString enc ) => SumToJSON' UntaggedValue enc arity (C1 c U1) where sumToJSON' opts _ _ = Tagged . fromString $ constructorTagModifier opts $ conName (undefined :: t c U1 p) ------------------------------------------------------------------------------- -- Instances ------------------------------------------------------------------------------- ------------------------------------------------------------------------------- -- base ------------------------------------------------------------------------------- instance ToJSON2 Const where liftToJSON2 t _ _ _ (Const x) = t x {-# INLINE liftToJSON2 #-} liftToEncoding2 t _ _ _ (Const x) = t x {-# INLINE liftToEncoding2 #-} instance ToJSON a => ToJSON1 (Const a) where liftToJSON _ _ (Const x) = toJSON x {-# INLINE liftToJSON #-} liftToEncoding _ _ (Const x) = toEncoding x {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Const a b) where toJSON (Const x) = toJSON x {-# INLINE toJSON #-} toEncoding (Const x) = toEncoding x {-# INLINE toEncoding #-} instance ToJSON1 Maybe where liftToJSON t _ (Just a) = t a liftToJSON _ _ Nothing = Null {-# INLINE liftToJSON #-} liftToEncoding t _ (Just a) = t a liftToEncoding _ _ Nothing = E.null_ {-# INLINE liftToEncoding #-} instance (ToJSON a) => ToJSON (Maybe a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON2 Either where liftToJSON2 toA _ _toB _ (Left a) = Object $ H.singleton "Left" (toA a) liftToJSON2 _toA _ toB _ (Right b) = Object $ H.singleton "Right" (toB b) {-# INLINE liftToJSON2 #-} liftToEncoding2 toA _ _toB _ (Left a) = E.pairs $ E.pair "Left" $ toA a liftToEncoding2 _toA _ toB _ (Right b) = E.pairs $ E.pair "Right" $ toB b {-# INLINE liftToEncoding2 #-} instance (ToJSON a) => ToJSON1 (Either a) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b) => ToJSON (Either a b) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance ToJSON Void where toJSON = absurd {-# INLINE toJSON #-} toEncoding = absurd {-# INLINE toEncoding #-} instance ToJSON Bool where toJSON = Bool {-# INLINE toJSON #-} toEncoding = E.bool {-# INLINE toEncoding #-} instance ToJSONKey Bool where toJSONKey = toJSONKeyText $ \x -> if x then "true" else "false" instance ToJSON Ordering where toJSON = toJSON . orderingToText toEncoding = toEncoding . orderingToText orderingToText :: Ordering -> T.Text orderingToText o = case o of LT -> "LT" EQ -> "EQ" GT -> "GT" instance ToJSON () where toJSON _ = emptyArray {-# INLINE toJSON #-} toEncoding _ = emptyArray_ {-# INLINE toEncoding #-} instance ToJSON Char where toJSON = String . T.singleton {-# INLINE toJSON #-} toJSONList = String . T.pack {-# INLINE toJSONList #-} toEncoding = E.string . (:[]) {-# INLINE toEncoding #-} toEncodingList = E.string {-# INLINE toEncodingList #-} instance ToJSON Double where toJSON = realFloatToJSON {-# INLINE toJSON #-} toEncoding = E.double {-# INLINE toEncoding #-} instance ToJSONKey Double where toJSONKey = toJSONKeyTextEnc E.doubleText {-# INLINE toJSONKey #-} instance ToJSON Number where toJSON (D d) = toJSON d toJSON (I i) = toJSON i {-# INLINE toJSON #-} toEncoding (D d) = toEncoding d toEncoding (I i) = toEncoding i {-# INLINE toEncoding #-} instance ToJSON Float where toJSON = realFloatToJSON {-# INLINE toJSON #-} toEncoding = E.float {-# INLINE toEncoding #-} instance ToJSONKey Float where toJSONKey = toJSONKeyTextEnc E.floatText {-# INLINE toJSONKey #-} instance (ToJSON a, Integral a) => ToJSON (Ratio a) where toJSON r = object [ "numerator" .= numerator r , "denominator" .= denominator r ] {-# INLINE toJSON #-} toEncoding r = E.pairs $ "numerator" .= numerator r <> "denominator" .= denominator r {-# INLINE toEncoding #-} instance HasResolution a => ToJSON (Fixed a) where toJSON = Number . realToFrac {-# INLINE toJSON #-} toEncoding = E.scientific . realToFrac {-# INLINE toEncoding #-} instance HasResolution a => ToJSONKey (Fixed a) where toJSONKey = toJSONKeyTextEnc (E.scientificText . realToFrac) {-# INLINE toJSONKey #-} instance ToJSON Int where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.int {-# INLINE toEncoding #-} instance ToJSONKey Int where toJSONKey = toJSONKeyTextEnc E.intText {-# INLINE toJSONKey #-} instance ToJSON Integer where toJSON = Number . fromInteger {-# INLINE toJSON #-} toEncoding = E.integer {-# INLINE toEncoding #-} instance ToJSONKey Integer where toJSONKey = toJSONKeyTextEnc E.integerText {-# INLINE toJSONKey #-} instance ToJSON Natural where toJSON = toJSON . toInteger {-# INLINE toJSON #-} toEncoding = toEncoding . toInteger {-# INLINE toEncoding #-} instance ToJSONKey Natural where toJSONKey = toJSONKeyTextEnc (E.integerText . toInteger) {-# INLINE toJSONKey #-} instance ToJSON Int8 where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.int8 {-# INLINE toEncoding #-} instance ToJSONKey Int8 where toJSONKey = toJSONKeyTextEnc E.int8Text {-# INLINE toJSONKey #-} instance ToJSON Int16 where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.int16 {-# INLINE toEncoding #-} instance ToJSONKey Int16 where toJSONKey = toJSONKeyTextEnc E.int16Text {-# INLINE toJSONKey #-} instance ToJSON Int32 where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.int32 {-# INLINE toEncoding #-} instance ToJSONKey Int32 where toJSONKey = toJSONKeyTextEnc E.int32Text {-# INLINE toJSONKey #-} instance ToJSON Int64 where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.int64 {-# INLINE toEncoding #-} instance ToJSONKey Int64 where toJSONKey = toJSONKeyTextEnc E.int64Text {-# INLINE toJSONKey #-} instance ToJSON Word where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.word {-# INLINE toEncoding #-} instance ToJSONKey Word where toJSONKey = toJSONKeyTextEnc E.wordText {-# INLINE toJSONKey #-} instance ToJSON Word8 where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.word8 {-# INLINE toEncoding #-} instance ToJSONKey Word8 where toJSONKey = toJSONKeyTextEnc E.word8Text {-# INLINE toJSONKey #-} instance ToJSON Word16 where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.word16 {-# INLINE toEncoding #-} instance ToJSONKey Word16 where toJSONKey = toJSONKeyTextEnc E.word16Text {-# INLINE toJSONKey #-} instance ToJSON Word32 where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.word32 {-# INLINE toEncoding #-} instance ToJSONKey Word32 where toJSONKey = toJSONKeyTextEnc E.word32Text {-# INLINE toJSONKey #-} instance ToJSON Word64 where toJSON = Number . fromIntegral {-# INLINE toJSON #-} toEncoding = E.word64 {-# INLINE toEncoding #-} instance ToJSONKey Word64 where toJSONKey = toJSONKeyTextEnc E.word64Text {-# INLINE toJSONKey #-} instance ToJSON CTime where toJSON (CTime i) = toJSON i {-# INLINE toJSON #-} toEncoding (CTime i) = toEncoding i {-# INLINE toEncoding #-} instance ToJSON Text where toJSON = String {-# INLINE toJSON #-} toEncoding = E.text {-# INLINE toEncoding #-} instance ToJSONKey Text where toJSONKey = toJSONKeyText id {-# INLINE toJSONKey #-} instance ToJSON LT.Text where toJSON = String . LT.toStrict {-# INLINE toJSON #-} toEncoding = E.lazyText {-# INLINE toEncoding #-} instance ToJSONKey LT.Text where toJSONKey = toJSONKeyText LT.toStrict instance ToJSON Version where toJSON = toJSON . showVersion {-# INLINE toJSON #-} toEncoding = toEncoding . showVersion {-# INLINE toEncoding #-} instance ToJSONKey Version where toJSONKey = toJSONKeyText (T.pack . showVersion) ------------------------------------------------------------------------------- -- semigroups NonEmpty ------------------------------------------------------------------------------- instance ToJSON1 NonEmpty where liftToJSON t _ = listValue t . NE.toList {-# INLINE liftToJSON #-} liftToEncoding t _ = listEncoding t . NE.toList {-# INLINE liftToEncoding #-} instance (ToJSON a) => ToJSON (NonEmpty a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- scientific ------------------------------------------------------------------------------- instance ToJSON Scientific where toJSON = Number {-# INLINE toJSON #-} toEncoding = E.scientific {-# INLINE toEncoding #-} instance ToJSONKey Scientific where toJSONKey = toJSONKeyTextEnc E.scientificText ------------------------------------------------------------------------------- -- DList ------------------------------------------------------------------------------- instance ToJSON1 DList.DList where liftToJSON t _ = listValue t . toList {-# INLINE liftToJSON #-} liftToEncoding t _ = listEncoding t . toList {-# INLINE liftToEncoding #-} instance (ToJSON a) => ToJSON (DList.DList a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- transformers - Functors ------------------------------------------------------------------------------- instance ToJSON1 Identity where liftToJSON t _ (Identity a) = t a {-# INLINE liftToJSON #-} liftToJSONList _ tl xs = tl (map runIdentity xs) {-# INLINE liftToJSONList #-} liftToEncoding t _ (Identity a) = t a {-# INLINE liftToEncoding #-} liftToEncodingList _ tl xs = tl (map runIdentity xs) {-# INLINE liftToEncodingList #-} instance (ToJSON a) => ToJSON (Identity a) where toJSON = toJSON1 {-# INLINE toJSON #-} toJSONList = liftToJSONList toJSON toJSONList {-# INLINE toJSONList #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} toEncodingList = liftToEncodingList toEncoding toEncodingList {-# INLINE toEncodingList #-} instance (ToJSONKey a) => ToJSONKey (Identity a) where toJSONKey = contramapToJSONKeyFunction runIdentity toJSONKey toJSONKeyList = contramapToJSONKeyFunction (map runIdentity) toJSONKeyList instance (ToJSON1 f, ToJSON1 g) => ToJSON1 (Compose f g) where liftToJSON tv tvl (Compose x) = liftToJSON g gl x where g = liftToJSON tv tvl gl = liftToJSONList tv tvl {-# INLINE liftToJSON #-} liftToJSONList te tel xs = liftToJSONList g gl (map getCompose xs) where g = liftToJSON te tel gl = liftToJSONList te tel {-# INLINE liftToJSONList #-} liftToEncoding te tel (Compose x) = liftToEncoding g gl x where g = liftToEncoding te tel gl = liftToEncodingList te tel {-# INLINE liftToEncoding #-} liftToEncodingList te tel xs = liftToEncodingList g gl (map getCompose xs) where g = liftToEncoding te tel gl = liftToEncodingList te tel {-# INLINE liftToEncodingList #-} instance (ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose f g a) where toJSON = toJSON1 {-# INLINE toJSON #-} toJSONList = liftToJSONList toJSON toJSONList {-# INLINE toJSONList #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} toEncodingList = liftToEncodingList toEncoding toEncodingList {-# INLINE toEncodingList #-} instance (ToJSON1 f, ToJSON1 g) => ToJSON1 (Product f g) where liftToJSON tv tvl (Pair x y) = liftToJSON2 tx txl ty tyl (x, y) where tx = liftToJSON tv tvl txl = liftToJSONList tv tvl ty = liftToJSON tv tvl tyl = liftToJSONList tv tvl liftToEncoding te tel (Pair x y) = liftToEncoding2 tx txl ty tyl (x, y) where tx = liftToEncoding te tel txl = liftToEncodingList te tel ty = liftToEncoding te tel tyl = liftToEncodingList te tel instance (ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product f g a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance (ToJSON1 f, ToJSON1 g) => ToJSON1 (Sum f g) where liftToJSON tv tvl (InL x) = Object $ H.singleton "InL" (liftToJSON tv tvl x) liftToJSON tv tvl (InR y) = Object $ H.singleton "InR" (liftToJSON tv tvl y) liftToEncoding te tel (InL x) = E.pairs $ E.pair "InL" $ liftToEncoding te tel x liftToEncoding te tel (InR y) = E.pairs $ E.pair "InR" $ liftToEncoding te tel y instance (ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum f g a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- containers ------------------------------------------------------------------------------- instance ToJSON1 Seq.Seq where liftToJSON t _ = listValue t . toList {-# INLINE liftToJSON #-} liftToEncoding t _ = listEncoding t . toList {-# INLINE liftToEncoding #-} instance (ToJSON a) => ToJSON (Seq.Seq a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Set.Set where liftToJSON t _ = listValue t . Set.toList {-# INLINE liftToJSON #-} liftToEncoding t _ = listEncoding t . Set.toList {-# INLINE liftToEncoding #-} instance (ToJSON a) => ToJSON (Set.Set a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON IntSet.IntSet where toJSON = toJSON . IntSet.toList {-# INLINE toJSON #-} toEncoding = toEncoding . IntSet.toList {-# INLINE toEncoding #-} instance ToJSON1 IntMap.IntMap where liftToJSON t tol = liftToJSON to' tol' . IntMap.toList where to' = liftToJSON2 toJSON toJSONList t tol tol' = liftToJSONList2 toJSON toJSONList t tol {-# INLINE liftToJSON #-} liftToEncoding t tol = liftToEncoding to' tol' . IntMap.toList where to' = liftToEncoding2 toEncoding toEncodingList t tol tol' = liftToEncodingList2 toEncoding toEncodingList t tol {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (IntMap.IntMap a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSONKey k => ToJSON1 (M.Map k) where liftToJSON g _ = case toJSONKey of ToJSONKeyText f _ -> Object . mapHashKeyVal f g ToJSONKeyValue f _ -> Array . V.fromList . map (toJSONPair f g) . M.toList {-# INLINE liftToJSON #-} liftToEncoding g _ = case toJSONKey of ToJSONKeyText _ f -> dict f g M.foldrWithKey ToJSONKeyValue _ f -> listEncoding (pairEncoding f) . M.toList where pairEncoding f (a, b) = E.list id [f a, g b] {-# INLINE liftToEncoding #-} instance (ToJSON v, ToJSONKey k) => ToJSON (M.Map k v) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Tree.Tree where liftToJSON t tol = go where go (Tree.Node root branches) = liftToJSON2 t tol to' tol' (root, branches) to' = liftToJSON go (listValue go) tol' = liftToJSONList go (listValue go) {-# INLINE liftToJSON #-} liftToEncoding t tol = go where go (Tree.Node root branches) = liftToEncoding2 t tol to' tol' (root, branches) to' = liftToEncoding go (listEncoding go) tol' = liftToEncodingList go (listEncoding go) {-# INLINE liftToEncoding #-} instance (ToJSON v) => ToJSON (Tree.Tree v) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- uuid ------------------------------------------------------------------------------- instance ToJSON UUID.UUID where toJSON = toJSON . UUID.toText toEncoding = E.unsafeToEncoding . EB.quote . B.byteString . UUID.toASCIIBytes instance ToJSONKey UUID.UUID where toJSONKey = ToJSONKeyText UUID.toText $ E.unsafeToEncoding . EB.quote . B.byteString . UUID.toASCIIBytes ------------------------------------------------------------------------------- -- vector ------------------------------------------------------------------------------- instance ToJSON1 Vector where liftToJSON t _ = Array . V.map t {-# INLINE liftToJSON #-} liftToEncoding t _ = listEncoding t . V.toList {-# INLINE liftToEncoding #-} instance (ToJSON a) => ToJSON (Vector a) where {-# SPECIALIZE instance ToJSON Array #-} toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} encodeVector :: (ToJSON a, VG.Vector v a) => v a -> Encoding encodeVector = listEncoding toEncoding . VG.toList {-# INLINE encodeVector #-} vectorToJSON :: (VG.Vector v a, ToJSON a) => v a -> Value vectorToJSON = Array . V.map toJSON . V.convert {-# INLINE vectorToJSON #-} instance (Storable a, ToJSON a) => ToJSON (VS.Vector a) where toJSON = vectorToJSON {-# INLINE toJSON #-} toEncoding = encodeVector {-# INLINE toEncoding #-} instance (VP.Prim a, ToJSON a) => ToJSON (VP.Vector a) where toJSON = vectorToJSON {-# INLINE toJSON #-} toEncoding = encodeVector {-# INLINE toEncoding #-} instance (VG.Vector VU.Vector a, ToJSON a) => ToJSON (VU.Vector a) where toJSON = vectorToJSON {-# INLINE toJSON #-} toEncoding = encodeVector {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- unordered-containers ------------------------------------------------------------------------------- instance ToJSON1 HashSet.HashSet where liftToJSON t _ = listValue t . HashSet.toList {-# INLINE liftToJSON #-} liftToEncoding t _ = listEncoding t . HashSet.toList {-# INLINE liftToEncoding #-} instance (ToJSON a) => ToJSON (HashSet.HashSet a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSONKey k => ToJSON1 (H.HashMap k) where liftToJSON g _ = case toJSONKey of ToJSONKeyText f _ -> Object . mapKeyVal f g ToJSONKeyValue f _ -> Array . V.fromList . map (toJSONPair f g) . H.toList {-# INLINE liftToJSON #-} -- liftToEncoding :: forall a. (a -> Encoding) -> ([a] -> Encoding) -> H.HashMap k a -> Encoding liftToEncoding g _ = case toJSONKey of ToJSONKeyText _ f -> dict f g H.foldrWithKey ToJSONKeyValue _ f -> listEncoding (pairEncoding f) . H.toList where pairEncoding f (a, b) = E.list id [f a, g b] {-# INLINE liftToEncoding #-} instance (ToJSON v, ToJSONKey k) => ToJSON (H.HashMap k v) where {-# SPECIALIZE instance ToJSON Object #-} toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- aeson ------------------------------------------------------------------------------- instance ToJSON Value where toJSON a = a {-# INLINE toJSON #-} toEncoding = E.value {-# INLINE toEncoding #-} instance ToJSON DotNetTime where toJSON = toJSON . dotNetTime toEncoding = toEncoding . dotNetTime dotNetTime :: DotNetTime -> String dotNetTime (DotNetTime t) = secs ++ formatMillis t ++ ")/" where secs = formatTime defaultTimeLocale "/Date(%s" t formatMillis :: (FormatTime t) => t -> String formatMillis = take 3 . formatTime defaultTimeLocale "%q" ------------------------------------------------------------------------------- -- primitive ------------------------------------------------------------------------------- #if MIN_VERSION_base(4,7,0) instance ToJSON a => ToJSON (PM.Array a) where -- note: we could do better than this if vector exposed the data -- constructor in Data.Vector. toJSON = toJSON . Exts.toList toEncoding = toEncoding . Exts.toList instance ToJSON a => ToJSON (PM.SmallArray a) where toJSON = toJSON . Exts.toList toEncoding = toEncoding . Exts.toList #if (MIN_VERSION_primitive(0,6,4)) instance (PM.Prim a,ToJSON a) => ToJSON (PM.PrimArray a) where toJSON = toJSON . Exts.toList toEncoding = toEncoding . Exts.toList instance (PM.PrimUnlifted a,ToJSON a) => ToJSON (PM.UnliftedArray a) where toJSON = toJSON . Exts.toList toEncoding = toEncoding . Exts.toList #endif #endif ------------------------------------------------------------------------------- -- time ------------------------------------------------------------------------------- instance ToJSON Day where toJSON = stringEncoding . E.day toEncoding = E.day instance ToJSONKey Day where toJSONKey = toJSONKeyTextEnc E.day instance ToJSON TimeOfDay where toJSON = stringEncoding . E.timeOfDay toEncoding = E.timeOfDay instance ToJSONKey TimeOfDay where toJSONKey = toJSONKeyTextEnc E.timeOfDay instance ToJSON LocalTime where toJSON = stringEncoding . E.localTime toEncoding = E.localTime instance ToJSONKey LocalTime where toJSONKey = toJSONKeyTextEnc E.localTime instance ToJSON ZonedTime where toJSON = stringEncoding . E.zonedTime toEncoding = E.zonedTime instance ToJSONKey ZonedTime where toJSONKey = toJSONKeyTextEnc E.zonedTime instance ToJSON UTCTime where toJSON = stringEncoding . E.utcTime toEncoding = E.utcTime instance ToJSONKey UTCTime where toJSONKey = toJSONKeyTextEnc E.utcTime -- | Encode something t a JSON string. stringEncoding :: Encoding' Text -> Value stringEncoding = String . T.dropAround (== '"') . T.decodeLatin1 . lazyToStrictByteString . E.encodingToLazyByteString {-# INLINE stringEncoding #-} instance ToJSON NominalDiffTime where toJSON = Number . realToFrac {-# INLINE toJSON #-} toEncoding = E.scientific . realToFrac {-# INLINE toEncoding #-} instance ToJSON DiffTime where toJSON = Number . realToFrac {-# INLINE toJSON #-} toEncoding = E.scientific . realToFrac {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- base Monoid/Semigroup ------------------------------------------------------------------------------- instance ToJSON1 Monoid.Dual where liftToJSON t _ = t . Monoid.getDual {-# INLINE liftToJSON #-} liftToEncoding t _ = t . Monoid.getDual {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Monoid.Dual a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Monoid.First where liftToJSON t to' = liftToJSON t to' . Monoid.getFirst {-# INLINE liftToJSON #-} liftToEncoding t to' = liftToEncoding t to' . Monoid.getFirst {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Monoid.First a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Monoid.Last where liftToJSON t to' = liftToJSON t to' . Monoid.getLast {-# INLINE liftToJSON #-} liftToEncoding t to' = liftToEncoding t to' . Monoid.getLast {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Monoid.Last a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Semigroup.Min where liftToJSON t _ (Semigroup.Min x) = t x {-# INLINE liftToJSON #-} liftToEncoding t _ (Semigroup.Min x) = t x {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Semigroup.Min a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Semigroup.Max where liftToJSON t _ (Semigroup.Max x) = t x {-# INLINE liftToJSON #-} liftToEncoding t _ (Semigroup.Max x) = t x {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Semigroup.Max a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Semigroup.First where liftToJSON t _ (Semigroup.First x) = t x {-# INLINE liftToJSON #-} liftToEncoding t _ (Semigroup.First x) = t x {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Semigroup.First a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Semigroup.Last where liftToJSON t _ (Semigroup.Last x) = t x {-# INLINE liftToJSON #-} liftToEncoding t _ (Semigroup.Last x) = t x {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Semigroup.Last a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Semigroup.WrappedMonoid where liftToJSON t _ (Semigroup.WrapMonoid x) = t x {-# INLINE liftToJSON #-} liftToEncoding t _ (Semigroup.WrapMonoid x) = t x {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Semigroup.WrappedMonoid a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSON1 Semigroup.Option where liftToJSON t to' = liftToJSON t to' . Semigroup.getOption {-# INLINE liftToJSON #-} liftToEncoding t to' = liftToEncoding t to' . Semigroup.getOption {-# INLINE liftToEncoding #-} instance ToJSON a => ToJSON (Semigroup.Option a) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- tagged ------------------------------------------------------------------------------- instance ToJSON1 Proxy where liftToJSON _ _ _ = Null {-# INLINE liftToJSON #-} liftToEncoding _ _ _ = E.null_ {-# INLINE liftToEncoding #-} instance ToJSON (Proxy a) where toJSON _ = Null {-# INLINE toJSON #-} toEncoding _ = E.null_ {-# INLINE toEncoding #-} instance ToJSON2 Tagged where liftToJSON2 _ _ t _ (Tagged x) = t x {-# INLINE liftToJSON2 #-} liftToEncoding2 _ _ t _ (Tagged x) = t x {-# INLINE liftToEncoding2 #-} instance ToJSON1 (Tagged a) where liftToJSON t _ (Tagged x) = t x {-# INLINE liftToJSON #-} liftToEncoding t _ (Tagged x) = t x {-# INLINE liftToEncoding #-} instance ToJSON b => ToJSON (Tagged a b) where toJSON = toJSON1 {-# INLINE toJSON #-} toEncoding = toEncoding1 {-# INLINE toEncoding #-} instance ToJSONKey b => ToJSONKey (Tagged a b) where toJSONKey = contramapToJSONKeyFunction unTagged toJSONKey toJSONKeyList = contramapToJSONKeyFunction (fmap unTagged) toJSONKeyList ------------------------------------------------------------------------------- -- Instances for converting t map keys ------------------------------------------------------------------------------- instance (ToJSON a, ToJSON b) => ToJSONKey (a,b) instance (ToJSON a, ToJSON b, ToJSON c) => ToJSONKey (a,b,c) instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSONKey (a,b,c,d) instance ToJSONKey Char where toJSONKey = ToJSONKeyText T.singleton (E.string . (:[])) toJSONKeyList = toJSONKeyText T.pack instance (ToJSONKey a, ToJSON a) => ToJSONKey [a] where toJSONKey = toJSONKeyList ------------------------------------------------------------------------------- -- Tuple instances ------------------------------------------------------------------------------- instance ToJSON2 (,) where liftToJSON2 toA _ toB _ (a, b) = Array $ V.create $ do mv <- VM.unsafeNew 2 VM.unsafeWrite mv 0 (toA a) VM.unsafeWrite mv 1 (toB b) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toA _ toB _ (a, b) = E.list id [toA a, toB b] {-# INLINE liftToEncoding2 #-} instance (ToJSON a) => ToJSON1 ((,) a) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b) => ToJSON (a, b) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a) => ToJSON2 ((,,) a) where liftToJSON2 toB _ toC _ (a, b, c) = Array $ V.create $ do mv <- VM.unsafeNew 3 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toB b) VM.unsafeWrite mv 2 (toC c) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toB _ toC _ (a, b, c) = E.list id [ toEncoding a , toB b , toC c ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b) => ToJSON1 ((,,) a b) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b) => ToJSON2 ((,,,) a b) where liftToJSON2 toC _ toD _ (a, b, c, d) = Array $ V.create $ do mv <- VM.unsafeNew 4 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toC c) VM.unsafeWrite mv 3 (toD d) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toC _ toD _ (a, b, c, d) = E.list id [ toEncoding a , toEncoding b , toC c , toD d ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c) => ToJSON1 ((,,,) a b c) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c) => ToJSON2 ((,,,,) a b c) where liftToJSON2 toD _ toE _ (a, b, c, d, e) = Array $ V.create $ do mv <- VM.unsafeNew 5 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toD d) VM.unsafeWrite mv 4 (toE e) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toD _ toE _ (a, b, c, d, e) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toD d , toE e ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON1 ((,,,,) a b c d) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON2 ((,,,,,) a b c d) where liftToJSON2 toE _ toF _ (a, b, c, d, e, f) = Array $ V.create $ do mv <- VM.unsafeNew 6 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toE e) VM.unsafeWrite mv 5 (toF f) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toE _ toF _ (a, b, c, d, e, f) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toE e , toF f ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON1 ((,,,,,) a b c d e) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON2 ((,,,,,,) a b c d e) where liftToJSON2 toF _ toG _ (a, b, c, d, e, f, g) = Array $ V.create $ do mv <- VM.unsafeNew 7 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toF f) VM.unsafeWrite mv 6 (toG g) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toF _ toG _ (a, b, c, d, e, f, g) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toF f , toG g ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON1 ((,,,,,,) a b c d e f) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON2 ((,,,,,,,) a b c d e f) where liftToJSON2 toG _ toH _ (a, b, c, d, e, f, g, h) = Array $ V.create $ do mv <- VM.unsafeNew 8 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toJSON f) VM.unsafeWrite mv 6 (toG g) VM.unsafeWrite mv 7 (toH h) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toG _ toH _ (a, b, c, d, e, f, g, h) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toEncoding f , toG g , toH h ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON1 ((,,,,,,,) a b c d e f g) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON2 ((,,,,,,,,) a b c d e f g) where liftToJSON2 toH _ toI _ (a, b, c, d, e, f, g, h, i) = Array $ V.create $ do mv <- VM.unsafeNew 9 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toJSON f) VM.unsafeWrite mv 6 (toJSON g) VM.unsafeWrite mv 7 (toH h) VM.unsafeWrite mv 8 (toI i) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toH _ toI _ (a, b, c, d, e, f, g, h, i) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toEncoding f , toEncoding g , toH h , toI i ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON1 ((,,,,,,,,) a b c d e f g h) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON2 ((,,,,,,,,,) a b c d e f g h) where liftToJSON2 toI _ toJ _ (a, b, c, d, e, f, g, h, i, j) = Array $ V.create $ do mv <- VM.unsafeNew 10 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toJSON f) VM.unsafeWrite mv 6 (toJSON g) VM.unsafeWrite mv 7 (toJSON h) VM.unsafeWrite mv 8 (toI i) VM.unsafeWrite mv 9 (toJ j) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toI _ toJ _ (a, b, c, d, e, f, g, h, i, j) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toEncoding f , toEncoding g , toEncoding h , toI i , toJ j ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON1 ((,,,,,,,,,) a b c d e f g h i) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON2 ((,,,,,,,,,,) a b c d e f g h i) where liftToJSON2 toJ _ toK _ (a, b, c, d, e, f, g, h, i, j, k) = Array $ V.create $ do mv <- VM.unsafeNew 11 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toJSON f) VM.unsafeWrite mv 6 (toJSON g) VM.unsafeWrite mv 7 (toJSON h) VM.unsafeWrite mv 8 (toJSON i) VM.unsafeWrite mv 9 (toJ j) VM.unsafeWrite mv 10 (toK k) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toJ _ toK _ (a, b, c, d, e, f, g, h, i, j, k) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toEncoding f , toEncoding g , toEncoding h , toEncoding i , toJ j , toK k ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON1 ((,,,,,,,,,,) a b c d e f g h i j) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON2 ((,,,,,,,,,,,) a b c d e f g h i j) where liftToJSON2 toK _ toL _ (a, b, c, d, e, f, g, h, i, j, k, l) = Array $ V.create $ do mv <- VM.unsafeNew 12 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toJSON f) VM.unsafeWrite mv 6 (toJSON g) VM.unsafeWrite mv 7 (toJSON h) VM.unsafeWrite mv 8 (toJSON i) VM.unsafeWrite mv 9 (toJSON j) VM.unsafeWrite mv 10 (toK k) VM.unsafeWrite mv 11 (toL l) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toK _ toL _ (a, b, c, d, e, f, g, h, i, j, k, l) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toEncoding f , toEncoding g , toEncoding h , toEncoding i , toEncoding j , toK k , toL l ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON1 ((,,,,,,,,,,,) a b c d e f g h i j k) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON2 ((,,,,,,,,,,,,) a b c d e f g h i j k) where liftToJSON2 toL _ toM _ (a, b, c, d, e, f, g, h, i, j, k, l, m) = Array $ V.create $ do mv <- VM.unsafeNew 13 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toJSON f) VM.unsafeWrite mv 6 (toJSON g) VM.unsafeWrite mv 7 (toJSON h) VM.unsafeWrite mv 8 (toJSON i) VM.unsafeWrite mv 9 (toJSON j) VM.unsafeWrite mv 10 (toJSON k) VM.unsafeWrite mv 11 (toL l) VM.unsafeWrite mv 12 (toM m) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toL _ toM _ (a, b, c, d, e, f, g, h, i, j, k, l, m) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toEncoding f , toEncoding g , toEncoding h , toEncoding i , toEncoding j , toEncoding k , toL l , toM m ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON2 ((,,,,,,,,,,,,,) a b c d e f g h i j k l) where liftToJSON2 toM _ toN _ (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = Array $ V.create $ do mv <- VM.unsafeNew 14 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toJSON f) VM.unsafeWrite mv 6 (toJSON g) VM.unsafeWrite mv 7 (toJSON h) VM.unsafeWrite mv 8 (toJSON i) VM.unsafeWrite mv 9 (toJSON j) VM.unsafeWrite mv 10 (toJSON k) VM.unsafeWrite mv 11 (toJSON l) VM.unsafeWrite mv 12 (toM m) VM.unsafeWrite mv 13 (toN n) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toM _ toN _ (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toEncoding f , toEncoding g , toEncoding h , toEncoding i , toEncoding j , toEncoding k , toEncoding l , toM m , toN n ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON2 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m) where liftToJSON2 toN _ toO _ (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = Array $ V.create $ do mv <- VM.unsafeNew 15 VM.unsafeWrite mv 0 (toJSON a) VM.unsafeWrite mv 1 (toJSON b) VM.unsafeWrite mv 2 (toJSON c) VM.unsafeWrite mv 3 (toJSON d) VM.unsafeWrite mv 4 (toJSON e) VM.unsafeWrite mv 5 (toJSON f) VM.unsafeWrite mv 6 (toJSON g) VM.unsafeWrite mv 7 (toJSON h) VM.unsafeWrite mv 8 (toJSON i) VM.unsafeWrite mv 9 (toJSON j) VM.unsafeWrite mv 10 (toJSON k) VM.unsafeWrite mv 11 (toJSON l) VM.unsafeWrite mv 12 (toJSON m) VM.unsafeWrite mv 13 (toN n) VM.unsafeWrite mv 14 (toO o) return mv {-# INLINE liftToJSON2 #-} liftToEncoding2 toN _ toO _ (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = E.list id [ toEncoding a , toEncoding b , toEncoding c , toEncoding d , toEncoding e , toEncoding f , toEncoding g , toEncoding h , toEncoding i , toEncoding j , toEncoding k , toEncoding l , toEncoding m , toN n , toO o ] {-# INLINE liftToEncoding2 #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) where liftToJSON = liftToJSON2 toJSON toJSONList {-# INLINE liftToJSON #-} liftToEncoding = liftToEncoding2 toEncoding toEncodingList {-# INLINE liftToEncoding #-} instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where toJSON = toJSON2 {-# INLINE toJSON #-} toEncoding = toEncoding2 {-# INLINE toEncoding #-} ------------------------------------------------------------------------------- -- pre-bytestring-0.10 compatibility ------------------------------------------------------------------------------- {-# INLINE lazyToStrictByteString #-} lazyToStrictByteString :: L.ByteString -> S.ByteString #if MIN_VERSION_bytestring(0,10,0) lazyToStrictByteString = L.toStrict #else lazyToStrictByteString = packChunks -- packChunks is taken from the blaze-builder package. -- | Pack the chunks of a lazy bytestring into a single strict bytestring. packChunks :: L.ByteString -> S.ByteString packChunks lbs = S.unsafeCreate (fromIntegral $ L.length lbs) (copyChunks lbs) where copyChunks L.Empty _pf = return () copyChunks (L.Chunk (S.PS fpbuf o l) lbs') pf = do withForeignPtr fpbuf $ \pbuf -> copyBytes pf (pbuf `plusPtr` o) l copyChunks lbs' (pf `plusPtr` l) #endif -------------------------------------------------------------------------------- -- | Wrap a list of pairs as an object. class Monoid pairs => FromPairs enc pairs | enc -> pairs where fromPairs :: pairs -> enc instance (a ~ Value) => FromPairs (Encoding' a) Series where fromPairs = E.pairs instance FromPairs Value (DList Pair) where fromPairs = object . toList -- | Like 'KeyValue' but the value is already converted to JSON -- ('Value' or 'Encoding'), and the result actually represents lists of pairs -- so it can be readily concatenated. class Monoid kv => KeyValuePair v kv where pair :: String -> v -> kv instance (v ~ Value) => KeyValuePair v (DList Pair) where pair k v = DList.singleton (pack k .= v) instance (e ~ Encoding) => KeyValuePair e Series where pair = E.pairStr aeson-1.4.2.0/LICENSE0000644000000000000000000000266700000000000012130 0ustar0000000000000000Copyright (c) 2011, MailRank, Inc. All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 3. Neither the name of the author nor the names of his contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTORS ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. aeson-1.4.2.0/README.markdown0000755000000000000000000000146700000000000013624 0ustar0000000000000000# Welcome to `aeson` [![Hackage](https://img.shields.io/hackage/v/aeson.svg)](https://hackage.haskell.org/package/aeson) [![Build Status](https://travis-ci.org/bos/aeson.svg)](https://travis-ci.org/bos/aeson) aeson is a fast Haskell library for working with JSON data. # Join in! We are happy to receive bug reports, fixes, documentation enhancements, and other improvements. Please report bugs via the [github issue tracker](http://github.com/bos/aeson/issues). Master [git repository](http://github.com/bos/aeson): * `git clone git://github.com/bos/aeson.git` See what's changed in recent (and upcoming) releases: * https://github.com/bos/aeson/blob/master/changelog.md (You can create and contribute changes using either git or Mercurial.) # Authors This library was originally written by Bryan O'Sullivan. aeson-1.4.2.0/Setup.lhs0000644000000000000000000000011400000000000012714 0ustar0000000000000000#!/usr/bin/env runhaskell > import Distribution.Simple > main = defaultMain aeson-1.4.2.0/aeson.cabal0000644000000000000000000001511400000000000013203 0ustar0000000000000000name: aeson version: 1.4.2.0 license: BSD3 license-file: LICENSE category: Text, Web, JSON copyright: (c) 2011-2016 Bryan O'Sullivan (c) 2011 MailRank, Inc. author: Bryan O'Sullivan maintainer: Adam Bergmark stability: experimental tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.3, GHC == 8.0.1 synopsis: Fast JSON parsing and encoding cabal-version: >= 1.10 homepage: https://github.com/bos/aeson bug-reports: https://github.com/bos/aeson/issues build-type: Simple description: A JSON parsing and encoding library optimized for ease of use and high performance. . To get started, see the documentation for the @Data.Aeson@ module below. . (A note on naming: in Greek mythology, Aeson was the father of Jason.) extra-source-files: *.yaml README.markdown benchmarks/*.cabal benchmarks/*.hs benchmarks/*.py benchmarks/Compare/*.hs benchmarks/Makefile benchmarks/Typed/*.hs benchmarks/json-data/*.json cbits/*.c changelog.md examples/*.cabal examples/*.hs examples/Twitter/*.hs ffi/Data/Aeson/Parser/*.hs include/*.h tests/JSONTestSuite/test_parsing/*.json tests/JSONTestSuite/test_transform/*.json pure/Data/Aeson/Parser/*.hs flag developer description: operate in developer mode default: False manual: True flag fast description: compile without optimizations default: False manual: True flag bytestring-builder description: Depend on the bytestring-builder package for backwards compatibility. default: False manual: False flag cffi description: Controls whether to include c-ffi bits or pure haskell. Default to False for security. default: False manual: True library default-language: Haskell2010 hs-source-dirs: . attoparsec-iso8601/ exposed-modules: Data.Aeson Data.Aeson.Encoding Data.Aeson.Parser Data.Aeson.Text Data.Aeson.Types Data.Aeson.TH Data.Aeson.QQ.Simple Data.Aeson.Encoding.Internal Data.Aeson.Internal Data.Aeson.Internal.Time Data.Aeson.Parser.Internal -- Deprecated modules exposed-modules: Data.Aeson.Encode other-modules: Data.Aeson.Compat Data.Aeson.Encoding.Builder Data.Aeson.Internal.Functions Data.Aeson.Parser.Unescape Data.Aeson.Parser.Time Data.Aeson.Types.FromJSON Data.Aeson.Types.Generic Data.Aeson.Types.ToJSON Data.Aeson.Types.Class Data.Aeson.Types.Internal Data.Attoparsec.Time Data.Attoparsec.Time.Internal -- GHC bundled libs build-depends: base >= 4.5.0.0 && < 5, containers >= 0.4.2.1 && < 0.7, deepseq >= 1.3.0.0 && < 1.5, ghc-prim >= 0.2 && < 0.6, template-haskell >= 2.7.0.0 && < 2.15, text >= 1.2.3.0 && < 1.3, time >= 1.4 && < 1.9 -- Compat build-depends: base-compat >= 0.9.1 && < 0.11 if flag(bytestring-builder) build-depends: bytestring >= 0.9.2 && < 0.10.4, bytestring-builder >= 0.10.4 && < 1 else build-depends: bytestring >= 0.10.4 && < 0.11 if !impl(ghc >= 8.6) build-depends: contravariant >=1.4.1 && <1.6 if !impl(ghc >= 8.0) -- `Data.Semigroup` and `Control.Monad.Fail` and `Control.Monad.IO.Class` are available in base only since GHC 8.0 / base 4.9 build-depends: semigroups >= 0.18.5 && < 0.19, transformers >= 0.3.0.0 && < 0.6, transformers-compat >= 0.6.2 && < 0.7, fail == 4.9.* if !impl(ghc >= 7.10) -- `Numeric.Natural` is available in base only since GHC 7.10 / base 4.8 build-depends: nats >= 1.1.1 && < 1.2, void >= 0.7.2 && < 0.8 -- cannot use latest version build-depends: unordered-containers >= 0.2.8.0 && < 0.3, -- not in LTS-12.10 tagged >= 0.8.5 && < 0.9, primitive >= 0.6.3.0 && < 0.7 -- Other dependencies build-depends: attoparsec >= 0.13.2.2 && < 0.14, dlist >= 0.8.0.4 && < 0.9, hashable >= 1.2.7.0 && < 1.3, scientific >= 0.3.6.2 && < 0.4, th-abstraction >= 0.2.8.0 && < 0.3, time-locale-compat >= 0.1.1.5 && < 0.2, uuid-types >= 1.0.3 && < 1.1, vector >= 0.12.0.1 && < 0.13 ghc-options: -Wall if flag(developer) ghc-options: -Werror ghc-prof-options: -auto-all if flag(fast) ghc-options: -O0 else ghc-options: -O2 include-dirs: include if impl(ghcjs) || !flag(cffi) hs-source-dirs: pure other-modules: Data.Aeson.Parser.UnescapePure else c-sources: cbits/unescape_string.c cpp-options: -DCFFI hs-source-dirs: ffi other-modules: Data.Aeson.Parser.UnescapeFFI test-suite tests default-language: Haskell2010 type: exitcode-stdio-1.0 hs-source-dirs: tests ffi pure main-is: Tests.hs c-sources: cbits/unescape_string.c ghc-options: -Wall -threaded -rtsopts other-modules: Data.Aeson.Parser.UnescapeFFI Data.Aeson.Parser.UnescapePure DataFamilies.Properties DataFamilies.Instances DataFamilies.Encoders DataFamilies.Types Encoders ErrorMessages Functions Instances Options Properties SerializationFormatSpec Types UnitTests UnitTests.NullaryConstructors build-depends: QuickCheck >= 2.10.0.1 && < 2.12, aeson, integer-logarithms >= 1 && <1.1, attoparsec, base, base-compat, base-orphans >= 0.5.3 && <0.8, base16-bytestring, containers, directory, dlist, filepath, generic-deriving >= 1.10 && < 1.13, ghc-prim >= 0.2, hashable >= 1.2.4.0, scientific, tagged, template-haskell, tasty, tasty-hunit, tasty-quickcheck, text, time, time-locale-compat, unordered-containers, uuid-types, vector, quickcheck-instances >= 0.3.16 if flag(bytestring-builder) build-depends: bytestring >= 0.9 && < 0.10.4, bytestring-builder >= 0.10.4 && < 1 else build-depends: bytestring >= 0.10.4 if !impl(ghc >= 8.0) build-depends: semigroups >= 0.18.2 && < 0.19, transformers >= 0.2.2.0, transformers-compat >= 0.3 if !impl(ghc >= 7.10) build-depends: nats >=1 && <1.2, void >=0.7.2 && <0.8 if impl(ghc >= 7.8) build-depends: hashable-time >= 0.2 && <0.3 if flag(fast) ghc-options: -fno-enable-rewrite-rules source-repository head type: git location: git://github.com/bos/aeson.git aeson-1.4.2.0/attoparsec-iso8601/Data/Attoparsec/0000755000000000000000000000000000000000000017342 5ustar0000000000000000aeson-1.4.2.0/attoparsec-iso8601/Data/Attoparsec/Time.hs0000644000000000000000000001122700000000000020577 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} -- | -- Module: Data.Aeson.Parser.Time -- Copyright: (c) 2015-2016 Bryan O'Sullivan -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable -- -- Parsers for parsing dates and times. module Data.Attoparsec.Time ( day , localTime , timeOfDay , timeZone , utcTime , zonedTime ) where import Prelude.Compat import Control.Applicative ((<|>)) import Control.Monad (void, when) import Data.Attoparsec.Text as A import Data.Attoparsec.Time.Internal (toPico) import Data.Bits ((.&.)) import Data.Char (isDigit, ord) import Data.Fixed (Pico) import Data.Int (Int64) import Data.Maybe (fromMaybe) import Data.Time.Calendar (Day, fromGregorianValid) import Data.Time.Clock (UTCTime(..)) import qualified Data.Text as T import qualified Data.Time.LocalTime as Local -- | Parse a date of the form @[+,-]YYYY-MM-DD@. day :: Parser Day day = do absOrNeg <- negate <$ char '-' <|> id <$ char '+' <|> pure id y <- (decimal <* char '-') <|> fail "date must be of form [+,-]YYYY-MM-DD" m <- (twoDigits <* char '-') <|> fail "date must be of form [+,-]YYYY-MM-DD" d <- twoDigits <|> fail "date must be of form [+,-]YYYY-MM-DD" maybe (fail "invalid date") return (fromGregorianValid (absOrNeg y) m d) -- | Parse a two-digit integer (e.g. day of month, hour). twoDigits :: Parser Int twoDigits = do a <- digit b <- digit let c2d c = ord c .&. 15 return $! c2d a * 10 + c2d b -- | Parse a time of the form @HH:MM[:SS[.SSS]]@. timeOfDay :: Parser Local.TimeOfDay timeOfDay = do h <- twoDigits m <- char ':' *> twoDigits s <- option 0 (char ':' *> seconds) if h < 24 && m < 60 && s < 61 then return (Local.TimeOfDay h m s) else fail "invalid time" data T = T {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 -- | Parse a count of seconds, with the integer part being two digits -- long. seconds :: Parser Pico seconds = do real <- twoDigits mc <- peekChar case mc of Just '.' -> do t <- anyChar *> takeWhile1 isDigit return $! parsePicos real t _ -> return $! fromIntegral real where parsePicos a0 t = toPico (fromIntegral (t' * 10^n)) where T n t' = T.foldl' step (T 12 (fromIntegral a0)) t step ma@(T m a) c | m <= 0 = ma | otherwise = T (m-1) (10 * a + fromIntegral (ord c) .&. 15) -- | Parse a time zone, and return 'Nothing' if the offset from UTC is -- zero. (This makes some speedups possible.) timeZone :: Parser (Maybe Local.TimeZone) timeZone = do let maybeSkip c = do ch <- peekChar'; when (ch == c) (void anyChar) maybeSkip ' ' ch <- satisfy $ \c -> c == 'Z' || c == '+' || c == '-' if ch == 'Z' then return Nothing else do h <- twoDigits mm <- peekChar m <- case mm of Just ':' -> anyChar *> twoDigits Just d | isDigit d -> twoDigits _ -> return 0 let off | ch == '-' = negate off0 | otherwise = off0 off0 = h * 60 + m case undefined of _ | off == 0 -> return Nothing | off < -720 || off > 840 || m > 59 -> fail "invalid time zone offset" | otherwise -> let !tz = Local.minutesToTimeZone off in return (Just tz) -- | Parse a date and time, of the form @YYYY-MM-DD HH:MM[:SS[.SSS]]@. -- The space may be replaced with a @T@. The number of seconds is optional -- and may be followed by a fractional component. localTime :: Parser Local.LocalTime localTime = Local.LocalTime <$> day <* daySep <*> timeOfDay where daySep = satisfy (\c -> c == 'T' || c == ' ') -- | Behaves as 'zonedTime', but converts any time zone offset into a -- UTC time. utcTime :: Parser UTCTime utcTime = do lt@(Local.LocalTime d t) <- localTime mtz <- timeZone case mtz of Nothing -> let !tt = Local.timeOfDayToTime t in return (UTCTime d tt) Just tz -> return $! Local.localTimeToUTC tz lt -- | Parse a date with time zone info. Acceptable formats: -- -- @YYYY-MM-DD HH:MM Z@ -- @YYYY-MM-DD HH:MM:SS Z@ -- @YYYY-MM-DD HH:MM:SS.SSS Z@ -- -- The first space may instead be a @T@, and the second space is -- optional. The @Z@ represents UTC. The @Z@ may be replaced with a -- time zone offset of the form @+0000@ or @-08:00@, where the first -- two digits are hours, the @:@ is optional and the second two digits -- (also optional) are minutes. zonedTime :: Parser Local.ZonedTime zonedTime = Local.ZonedTime <$> localTime <*> (fromMaybe utc <$> timeZone) utc :: Local.TimeZone utc = Local.TimeZone 0 False "" aeson-1.4.2.0/attoparsec-iso8601/Data/Attoparsec/Time/0000755000000000000000000000000000000000000020240 5ustar0000000000000000aeson-1.4.2.0/attoparsec-iso8601/Data/Attoparsec/Time/Internal.hs0000644000000000000000000000341600000000000022354 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE NoImplicitPrelude #-} -- | -- Module: Data.Aeson.Internal.Time -- Copyright: (c) 2015-2016 Bryan O'Sullivan -- License: BSD3 -- Maintainer: Bryan O'Sullivan -- Stability: experimental -- Portability: portable module Data.Attoparsec.Time.Internal ( TimeOfDay64(..) , fromPico , toPico , diffTimeOfDay64 , toTimeOfDay64 ) where import Prelude.Compat import Data.Int (Int64) import Data.Time import Unsafe.Coerce (unsafeCoerce) #if MIN_VERSION_time(1,6,0) import Data.Time.Clock (diffTimeToPicoseconds) #endif #if MIN_VERSION_base(4,7,0) import Data.Fixed (Pico, Fixed(MkFixed)) #else import Data.Fixed (Pico) #endif #if !MIN_VERSION_time(1,6,0) diffTimeToPicoseconds :: DiffTime -> Integer diffTimeToPicoseconds = unsafeCoerce #endif #if MIN_VERSION_base(4,7,0) toPico :: Integer -> Pico toPico = MkFixed fromPico :: Pico -> Integer fromPico (MkFixed i) = i #else toPico :: Integer -> Pico toPico = unsafeCoerce fromPico :: Pico -> Integer fromPico = unsafeCoerce #endif -- | Like TimeOfDay, but using a fixed-width integer for seconds. data TimeOfDay64 = TOD {-# UNPACK #-} !Int {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 posixDayLength :: DiffTime posixDayLength = 86400 diffTimeOfDay64 :: DiffTime -> TimeOfDay64 diffTimeOfDay64 t | t >= posixDayLength = TOD 23 59 (60000000000000 + pico (t - posixDayLength)) | otherwise = TOD (fromIntegral h) (fromIntegral m) s where (h,mp) = pico t `quotRem` 3600000000000000 (m,s) = mp `quotRem` 60000000000000 pico = fromIntegral . diffTimeToPicoseconds toTimeOfDay64 :: TimeOfDay -> TimeOfDay64 toTimeOfDay64 (TimeOfDay h m s) = TOD h m (fromIntegral (fromPico s)) aeson-1.4.2.0/benchmarks/0000755000000000000000000000000000000000000013225 5ustar0000000000000000aeson-1.4.2.0/benchmarks/AesonEncode.hs0000755000000000000000000000251000000000000015745 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Prelude.Compat import Control.DeepSeq import Control.Monad import Data.Aeson import Data.Attoparsec.ByteString (IResult(..), parseWith) import Data.Char (isDigit) import Data.Time.Clock import System.Environment (getArgs) import System.IO import qualified Data.ByteString as B main :: IO () main = do args0 <- getArgs let (cnt,args) = case args0 of (i:c:a) | all isDigit i && all isDigit c -> (c,a) (c:a) -> (c,a) [] -> error "Unexpected empty list" let count = read cnt :: Int forM_ args $ \arg -> withFile arg ReadMode $ \h -> do putStrLn $ arg ++ ":" let refill = B.hGet h 16384 result0 <- parseWith refill json =<< refill r0 <- case result0 of Done _ r -> return r _ -> fail $ "failed to read " ++ show arg start <- getCurrentTime let loop !n r | n >= count = return () | otherwise = {-# SCC "loop" #-} rnf (encode r) `seq` loop (n+1) r loop 0 r0 delta <- flip diffUTCTime start `fmap` getCurrentTime let rate = fromIntegral count / realToFrac delta :: Double putStrLn $ " " ++ cnt ++ " good, " ++ show delta putStrLn $ " " ++ show (round rate :: Int) ++ " per second" aeson-1.4.2.0/benchmarks/AesonFoldable.hs0000755000000000000000000000447100000000000016270 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Criterion.Main import Prelude.Compat import Data.Foldable (toList) import qualified Data.Aeson as A import qualified Data.Sequence as S import qualified Data.Vector as V import qualified Data.Vector.Unboxed as U ------------------------------------------------------------------------------- -- List ------------------------------------------------------------------------------- newtype L f = L { getL :: f Int } instance Foldable f => A.ToJSON (L f) where toJSON = error "do not use this" toEncoding = A.toEncoding . toList . getL ------------------------------------------------------------------------------- -- Foldable ------------------------------------------------------------------------------- newtype F f = F { getF :: f Int } instance Foldable f => A.ToJSON (F f) where toJSON = error "do not use this" toEncoding = A.foldable . getF ------------------------------------------------------------------------------- -- Values ------------------------------------------------------------------------------- valueList :: [Int] valueList = [1..1000] valueSeq :: S.Seq Int valueSeq = S.fromList valueList valueVector :: V.Vector Int valueVector = V.fromList valueList valueUVector :: U.Vector Int valueUVector = U.fromList valueList ------------------------------------------------------------------------------- -- Main ------------------------------------------------------------------------------- benchEncode :: A.ToJSON a => String -> a -> Benchmark benchEncode name val = bench ("A " ++ name) $ nf A.encode val main :: IO () main = defaultMain [ bgroup "encode" [ bgroup "List" [ benchEncode "-" valueList , benchEncode "L" $ L valueList , benchEncode "F" $ F valueList ] , bgroup "Seq" [ benchEncode "-" valueSeq , benchEncode "L" $ L valueSeq , benchEncode "F" $ F valueSeq ] , bgroup "Vector" [ benchEncode "-" valueVector , benchEncode "L" $ L valueVector , benchEncode "F" $ F valueVector ] , bgroup "Vector.Unboxed" [ benchEncode "-" valueUVector ] ] ] aeson-1.4.2.0/benchmarks/AesonMap.hs0000755000000000000000000001413700000000000015275 0ustar0000000000000000{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RankNTypes #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Main (main) where import Prelude.Compat import Control.DeepSeq import Criterion.Main import Data.Hashable import Data.Proxy (Proxy (..)) import Data.Tagged (Tagged (..)) import Data.Aeson import Data.Aeson.Types (fromJSONKeyCoerce) import qualified Data.ByteString.Lazy as LBS import qualified Data.HashMap.Strict as HM import qualified Data.Map as M import qualified Data.Text as T value :: Int -> HM.HashMap T.Text T.Text value n = HM.fromList $ map f [1..n] where f m = let t = T.pack (show m) in (t, t) ------------------------------------------------------------------------------- -- Orphans ------------------------------------------------------------------------------- instance Hashable b => Hashable (Tagged a b) where hashWithSalt salt (Tagged a) = hashWithSalt salt a ------------------------------------------------------------------------------- -- Text ------------------------------------------------------------------------------- newtype T1 = T1 T.Text deriving (Eq, Ord) instance NFData T1 where rnf (T1 t) = rnf t instance Hashable T1 where hashWithSalt salt (T1 t) = hashWithSalt salt t instance FromJSON T1 where parseJSON = withText "T1" $ pure . T1 instance FromJSONKey T1 where fromJSONKey = FromJSONKeyText T1 ------------------------------------------------------------------------------- -- Coerce ------------------------------------------------------------------------------- newtype T2 = T2 T.Text deriving (Eq, Ord) instance NFData T2 where rnf (T2 t) = rnf t instance Hashable T2 where hashWithSalt salt (T2 t) = hashWithSalt salt t instance FromJSON T2 where parseJSON = withText "T2" $ pure . T2 instance FromJSONKey T2 where fromJSONKey = fromJSONKeyCoerce ------------------------------------------------------------------------------- -- TextParser ------------------------------------------------------------------------------- newtype T3 = T3 T.Text deriving (Eq, Ord) instance NFData T3 where rnf (T3 t) = rnf t instance Hashable T3 where hashWithSalt salt (T3 t) = hashWithSalt salt t instance FromJSON T3 where parseJSON = withText "T3" $ pure . T3 instance FromJSONKey T3 where fromJSONKey = FromJSONKeyTextParser (pure . T3) ------------------------------------------------------------------------------- -- Values ------------------------------------------------------------------------------- value10, value100, value1000, value10000 :: HM.HashMap T.Text T.Text value10 = value 10 value100 = value 100 value1000 = value 1000 value10000 = value 10000 encodedValue10 :: LBS.ByteString encodedValue10 = encode value10 encodedValue100 :: LBS.ByteString encodedValue100 = encode value100 encodedValue1000 :: LBS.ByteString encodedValue1000 = encode value1000 encodedValue10000 :: LBS.ByteString encodedValue10000 = encode value10000 ------------------------------------------------------------------------------- -- Helpers ------------------------------------------------------------------------------- decodeHM :: (FromJSON (HM.HashMap k T.Text), Eq k, Hashable k) => Proxy k -> LBS.ByteString -> Maybe (HM.HashMap k T.Text) decodeHM _ = decode decodeMap :: (FromJSON (M.Map k T.Text), Ord k) => Proxy k -> LBS.ByteString -> Maybe (M.Map k T.Text) decodeMap _ = decode proxyText :: Proxy T.Text proxyText = Proxy proxyT1 :: Proxy T1 proxyT1 = Proxy proxyT2 :: Proxy T2 proxyT2 = Proxy proxyT3 :: Proxy T3 proxyT3 = Proxy proxyTagged :: Proxy a -> Proxy (Tagged () a) proxyTagged _ = Proxy ------------------------------------------------------------------------------- -- Main ------------------------------------------------------------------------------- benchDecodeHM :: String -> LBS.ByteString -> Benchmark benchDecodeHM name val = bgroup name [ bench "Text" $ nf (decodeHM proxyText) val , bench "Identity" $ nf (decodeHM proxyT1) val , bench "Coerce" $ nf (decodeHM proxyT2) val , bench "Parser" $ nf (decodeHM proxyT3) val , bench "Tagged Text" $ nf (decodeHM $ proxyTagged proxyText) val , bench "Tagged Identity" $ nf (decodeHM $ proxyTagged proxyT1) val , bench "Tagged Coerce" $ nf (decodeHM $ proxyTagged proxyT2) val , bench "Tagged Parser" $ nf (decodeHM $ proxyTagged proxyT3) val ] benchDecodeMap :: String -> LBS.ByteString -> Benchmark benchDecodeMap name val = bgroup name [ bench "Text" $ nf (decodeMap proxyText) val , bench "Identity" $ nf (decodeMap proxyT1) val , bench "Coerce" $ nf (decodeMap proxyT2) val , bench "Parser" $ nf (decodeMap proxyT3) val ] benchEncodeHM :: String -> HM.HashMap T.Text T.Text -> Benchmark benchEncodeHM name val = bgroup name [ bench "Text" $ nf encode val ] benchEncodeMap :: String -> HM.HashMap T.Text T.Text -> Benchmark benchEncodeMap name val = bgroup name [ bench "Text" $ nf encode val' ] where val' :: M.Map T.Text T.Text val' = M.fromList . HM.toList $ val main :: IO () main = defaultMain [ bgroup "decode" [ bgroup "HashMap" [ benchDecodeHM "10" encodedValue10 , benchDecodeHM "100" encodedValue100 , benchDecodeHM "1000" encodedValue1000 , benchDecodeHM "10000" encodedValue10000 ] , bgroup "Map" [ benchDecodeMap "10" encodedValue10 , benchDecodeMap "100" encodedValue100 , benchDecodeMap "1000" encodedValue1000 , benchDecodeMap "10000" encodedValue10000 ] ] , bgroup "encode" [ bgroup "HashMap" [ benchEncodeHM "100" value100 , benchEncodeHM "1000" value1000 , benchEncodeHM "10000" value10000 ] , bgroup "Map" [ benchEncodeMap "100" value100 , benchEncodeMap "1000" value1000 , benchEncodeMap "10000" value10000 ] ] ] aeson-1.4.2.0/benchmarks/AesonParse.hs0000755000000000000000000000224700000000000015631 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Prelude.Compat import Data.Aeson import Control.Monad import Data.Attoparsec.ByteString (IResult(..), parseWith) import Data.Time.Clock import System.Environment (getArgs) import System.IO import qualified Data.ByteString as B main :: IO () main = do (bs:cnt:args) <- getArgs let count = read cnt :: Int blkSize = read bs forM_ args $ \arg -> withFile arg ReadMode $ \h -> do putStrLn $ arg ++ ":" start <- getCurrentTime let loop !good !bad | good+bad >= count = return (good, bad) | otherwise = do hSeek h AbsoluteSeek 0 let refill = B.hGet h blkSize result <- parseWith refill json =<< refill case result of Done _ _ -> loop (good+1) bad _ -> loop good (bad+1) (good, _) <- loop 0 0 delta <- flip diffUTCTime start `fmap` getCurrentTime putStrLn $ " " ++ show good ++ " good, " ++ show delta let rate = fromIntegral count / realToFrac delta :: Double putStrLn $ " " ++ show (round rate :: Int) ++ " per second" aeson-1.4.2.0/benchmarks/AesonTuples.hs0000755000000000000000000000215500000000000016031 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Main (main) where import Prelude.Compat import Control.DeepSeq (deepseq) import Criterion.Main import Data.Aeson -------------------------------------------------------------------------------- type FJ a = Value -> Result a type T2 = (Int, Int) type T3 = (Int, Int, Int) type T4 = (Int, Int, Int, Int) t2 :: T2 t2 = (1, 2) t3 :: T3 t3 = (1, 2, 3) t4 :: T4 t4 = (1, 2, 3, 4) main :: IO () main = let v2 = toJSON t2 v3 = toJSON t3 v4 = toJSON t4 in t2 `deepseq` t3 `deepseq` t4 `deepseq` v2 `deepseq` v3 `deepseq` v4 `deepseq` defaultMain [ bgroup "t2" [ bench "toJSON" (nf toJSON t2) , bench "fromJSON" (nf (fromJSON :: FJ T2) v2) ] , bgroup "t3" [ bench "toJSON" (nf toJSON t3) , bench "fromJSON" (nf (fromJSON :: FJ T3) v3) ] , bgroup "t4" [ bench "toJSON" (nf toJSON t4) , bench "fromJSON" (nf (fromJSON :: FJ T4) v4) ] ] aeson-1.4.2.0/benchmarks/AutoCompare.hs0000755000000000000000000000372500000000000016012 0ustar0000000000000000{-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} module Main (main) where import Control.DeepSeq import Control.Monad import Criterion.Main import Data.Aeson import qualified Auto.T.D as T import qualified Auto.T.BigRecord as T import qualified Auto.T.BigProduct as T import qualified Auto.T.BigSum as T import qualified Auto.G.D as G import qualified Auto.G.BigRecord as G import qualified Auto.G.BigProduct as G import qualified Auto.G.BigSum as G -------------------------------------------------------------------------------- runBench :: IO () runBench = defaultMain [ compareBench "D" T.d G.d , compareBench "BigRecord" T.bigRecord G.bigRecord , compareBench "BigProduct" T.bigProduct G.bigProduct , compareBench "BigSum" T.bigSum G.bigSum ] group :: String -> Benchmarkable -> Benchmarkable -> Benchmark group n th gen = bgroup n [ bench "th" th , bench "generic" gen ] compareBench :: forall a b . (ToJSON a, FromJSON a, NFData a, ToJSON b, FromJSON b, NFData b) => String -> a -> b -> Benchmark compareBench name a b = v `deepseq` bgroup name [ group "toJSON" (nf toJSON a) (nf toJSON b) , group "encode" (nf encode a) (nf encode b) , group "fromJSON" (nf (fromJSON :: Value -> Result a) v) (nf (fromJSON :: Value -> Result b) v) ] where v = toJSON a -- == toJSON b sanityCheck :: IO () sanityCheck = do check T.d check G.d check T.bigRecord check G.bigRecord check T.bigProduct check G.bigProduct check T.bigSum check G.bigSum check :: (Show a, Eq a, FromJSON a, ToJSON a) => a -> IO () check x = do unless (Success x == (fromJSON . toJSON) x) $ fail $ "toJSON: " ++ show x unless (Success x == (decode_ . encode) x) $ fail $ "encode: " ++ show x where decode_ s = case decode s of Just v -> fromJSON v Nothing -> fail "" main :: IO () main = do sanityCheck runBench aeson-1.4.2.0/benchmarks/Compare.hs0000755000000000000000000000147300000000000015157 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} module Main (main) where import Prelude.Compat import Compare.BufferBuilder () import Criterion.Main import Data.BufferBuilder.Json import Twitter import Twitter.Manual () import Typed.Common import qualified Data.Aeson as Aeson import qualified Compare.JsonBench as JsonBench #ifdef MIN_VERSION_json_builder import Data.Json.Builder import Compare.JsonBuilder () #endif main :: IO () main = defaultMain [ env (load "json-data/twitter100.json") $ \ ~(twtr :: Result) -> bgroup "twitter" [ bench "aeson" $ nf Aeson.encode twtr , bench "buffer-builder" $ nf encodeJson twtr #ifdef MIN_VERSION_json_builder , bench "json-builder" $ nf toJsonLBS twtr #endif ] , JsonBench.benchmarks ] aeson-1.4.2.0/benchmarks/Compare/0000755000000000000000000000000000000000000014613 5ustar0000000000000000aeson-1.4.2.0/benchmarks/Compare/BufferBuilder.hs0000755000000000000000000000357700000000000017706 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Compare.BufferBuilder () where import Prelude.Compat hiding ((<>)) import Data.BufferBuilder.Json import Data.Int (Int64) import Data.Monoid ((<>)) import Twitter import qualified Data.BufferBuilder.Utf8 as UB instance (ToJson a, ToJson b) => ToJson (a,b) where toJson (a,b) = array [toJson a, toJson b] instance ToJson Int64 where toJson a = unsafeValueUtf8Builder $ UB.appendDecimalSignedInt (fromIntegral a) {-# INLINE toJson #-} instance ToJson Metadata where toJson Metadata{..} = toJson $ "result_type" .= result_type instance ToJson Geo where toJson Geo{..} = toJson $ "type_" .= type_ <> "coordinates" .= coordinates instance ToJson Story where toJson Story{..} = toJson $ "from_user_id_str" .= from_user_id_str <> "profile_image_url" .= profile_image_url <> "created_at" .= created_at <> "from_user" .= from_user <> "id_str" .= id_str <> "metadata" .= metadata <> "to_user_id" .= to_user_id <> "text" .= text <> "id" .= id_ <> "from_user_id" .= from_user_id <> "geo" .= geo <> "iso_language_code" .= iso_language_code <> "to_user_id_str" .= to_user_id_str <> "source" .= source instance ToJson Result where toJson Result{..} = toJson $ "results" .= results <> "max_id" .= max_id <> "since_id" .= since_id <> "refresh_url" .= refresh_url <> "next_page" .= next_page <> "results_per_page" .= results_per_page <> "page" .= page <> "completed_in" .= completed_in <> "since_id_str" .= since_id_str <> "max_id_str" .= max_id_str <> "query" .= query aeson-1.4.2.0/benchmarks/Compare/JsonBench.hs0000755000000000000000000002521600000000000017031 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} -- Adapted from a buffer-builder benchmark: -- -- https://github.com/chadaustin/buffer-builder/blob/master/test.json module Compare.JsonBench (benchmarks) where import Prelude.Compat hiding ((<>)) import Control.DeepSeq (NFData(..)) import Criterion import Data.Aeson ((.:)) import Data.Monoid ((<>)) import Data.Text (Text) import Typed.Common (load) import qualified Data.Aeson as Aeson import qualified Data.BufferBuilder.Json as Json #ifdef MIN_VERSION_json_builder import qualified Data.Json.Builder as JB #endif data EyeColor = Green | Blue | Brown deriving (Eq, Show) data Gender = Male | Female deriving (Eq, Show) data Fruit = Apple | Strawberry | Banana deriving (Eq, Show) data Friend = Friend { fId :: !Int , fName :: !Text } deriving (Eq, Show) data User = User { uId :: !Text , uIndex :: !Int , uGuid :: !Text , uIsActive :: !Bool , uBalance :: !Text , uPicture :: !Text , uAge :: !Int , uEyeColor :: !EyeColor , uName :: !Text , uGender :: !Gender , uCompany :: !Text , uEmail :: !Text , uPhone :: !Text , uAddress :: !Text , uAbout :: !Text , uRegistered :: !Text -- UTCTime? , uLatitude :: !Double , uLongitude :: !Double , uTags :: ![Text] , uFriends :: ![Friend] , uGreeting :: !Text , uFavouriteFruit :: !Fruit } deriving (Eq, Show) instance NFData EyeColor where rnf !_ = () instance NFData Gender where rnf !_ = () instance NFData Fruit where rnf !_ = () instance NFData Friend where rnf Friend {..} = rnf fId `seq` rnf fName `seq` () instance NFData User where rnf User {..} = rnf uId `seq` rnf uIndex `seq` rnf uGuid `seq` rnf uIsActive `seq` rnf uBalance `seq` rnf uPicture `seq` rnf uAge `seq` rnf uEyeColor `seq` rnf uName `seq` rnf uGender `seq` rnf uCompany `seq` rnf uEmail `seq` rnf uPhone `seq` rnf uAddress `seq` rnf uAbout `seq` rnf uRegistered `seq` rnf uLatitude `seq` rnf uLongitude `seq` rnf uTags `seq` rnf uFriends `seq` rnf uGreeting `seq` rnf uFavouriteFruit `seq` () eyeColorTable :: [(Text, EyeColor)] eyeColorTable = [("brown", Brown), ("green", Green), ("blue", Blue)] genderTable :: [(Text, Gender)] genderTable = [("male", Male), ("female", Female)] fruitTable :: [(Text, Fruit)] fruitTable = [("apple", Apple), ("strawberry", Strawberry), ("banana", Banana)] enumFromJson :: Monad m => String -> [(Text, enum)] -> (json -> m Text) -> json -> m enum enumFromJson enumName table extract v = do s <- extract v case lookup s table of Just r -> return r Nothing -> fail $ "Bad " ++ enumName ++ ": " ++ show s --- Aeson instances --- instance Aeson.FromJSON EyeColor where parseJSON = enumFromJson "EyeColor" eyeColorTable Aeson.parseJSON instance Aeson.FromJSON Gender where parseJSON = enumFromJson "Gender" genderTable Aeson.parseJSON instance Aeson.FromJSON Fruit where parseJSON = enumFromJson "Fruit" fruitTable Aeson.parseJSON instance Aeson.FromJSON Friend where parseJSON = Aeson.withObject "Friend" $ \o -> do fId <- o .: "id" fName <- o .: "name" return Friend {..} instance Aeson.FromJSON User where parseJSON = Aeson.withObject "User" $ \o -> do uId <- o .: "_id" uIndex <- o .: "index" uGuid <- o .: "guid" uIsActive <- o .: "isActive" uBalance <- o .: "balance" uPicture <- o .: "picture" uAge <- o .: "age" uEyeColor <- o .: "eyeColor" uName <- o .: "name" uGender <- o .: "gender" uCompany <- o .: "company" uEmail <- o .: "email" uPhone <- o .: "phone" uAddress <- o .: "address" uAbout <- o .: "about" uRegistered <- o .: "registered" uLatitude <- o .: "latitude" uLongitude <- o .: "longitude" uTags <- o .: "tags" uFriends <- o .: "friends" uGreeting <- o .: "greeting" uFavouriteFruit <- o .: "favoriteFruit" return User {..} instance Aeson.ToJSON EyeColor where toJSON ec = Aeson.toJSON $ case ec of Green -> "green" :: Text Blue -> "blue" Brown -> "brown" toEncoding ec = Aeson.toEncoding $ case ec of Green -> "green" :: Text Blue -> "blue" Brown -> "brown" instance Aeson.ToJSON Gender where toJSON g = Aeson.toJSON $ case g of Male -> "male" :: Text Female -> "female" toEncoding g = Aeson.toEncoding $ case g of Male -> "male" :: Text Female -> "female" instance Aeson.ToJSON Fruit where toJSON f = Aeson.toJSON $ case f of Apple -> "apple" :: Text Banana -> "banana" Strawberry -> "strawberry" toEncoding f = Aeson.toEncoding $ case f of Apple -> "apple" :: Text Banana -> "banana" Strawberry -> "strawberry" instance Aeson.ToJSON Friend where toJSON Friend {..} = Aeson.object [ "id" Aeson..= fId , "name" Aeson..= fName ] toEncoding Friend {..} = Aeson.pairs $ "id" Aeson..= fId <> "name" Aeson..= fName instance Aeson.ToJSON User where toJSON User{..} = Aeson.object [ "_id" Aeson..= uId , "index" Aeson..= uIndex , "guid" Aeson..= uGuid , "isActive" Aeson..= uIsActive , "balance" Aeson..= uBalance , "picture" Aeson..= uPicture , "age" Aeson..= uAge , "eyeColor" Aeson..= uEyeColor , "name" Aeson..= uName , "gender" Aeson..= uGender , "company" Aeson..= uCompany , "email" Aeson..= uEmail , "phone" Aeson..= uPhone , "address" Aeson..= uAddress , "about" Aeson..= uAbout , "registered" Aeson..= uRegistered , "latitude" Aeson..= uLatitude , "longitude" Aeson..= uLongitude , "tags" Aeson..= uTags , "friends" Aeson..= uFriends , "greeting" Aeson..= uGreeting , "favoriteFruit" Aeson..= uFavouriteFruit ] toEncoding User{..} = Aeson.pairs $ "_id" Aeson..= uId <> "index" Aeson..= uIndex <> "guid" Aeson..= uGuid <> "isActive" Aeson..= uIsActive <> "balance" Aeson..= uBalance <> "picture" Aeson..= uPicture <> "age" Aeson..= uAge <> "eyeColor" Aeson..= uEyeColor <> "name" Aeson..= uName <> "gender" Aeson..= uGender <> "company" Aeson..= uCompany <> "email" Aeson..= uEmail <> "phone" Aeson..= uPhone <> "address" Aeson..= uAddress <> "about" Aeson..= uAbout <> "registered" Aeson..= uRegistered <> "latitude" Aeson..= uLatitude <> "longitude" Aeson..= uLongitude <> "tags" Aeson..= uTags <> "friends" Aeson..= uFriends <> "greeting" Aeson..= uGreeting <> "favoriteFruit" Aeson..= uFavouriteFruit --- BufferBuilder instances --- instance Json.ToJson EyeColor where toJson ec = Json.toJson $ case ec of Green -> "green" :: Text Blue -> "blue" Brown -> "brown" instance Json.ToJson Gender where toJson g = Json.toJson $ case g of Male -> "male" :: Text Female -> "female" instance Json.ToJson Fruit where toJson f = Json.toJson $ case f of Apple -> "apple" :: Text Strawberry -> "strawberry" Banana -> "banana" instance Json.ToJson Friend where toJson Friend{..} = Json.toJson $ "_id" Json..= fId <> "name" Json..= fName instance Json.ToJson User where toJson User{..} = Json.toJson $ "_id"# Json..=# uId <> "index"# Json..=# uIndex <> "guid"# Json..=# uGuid <> "isActive"# Json..=# uIsActive <> "balance"# Json..=# uBalance <> "picture"# Json..=# uPicture <> "age"# Json..=# uAge <> "eyeColor"# Json..=# uEyeColor <> "name"# Json..=# uName <> "gender"# Json..=# uGender <> "company"# Json..=# uCompany <> "email"# Json..=# uEmail <> "phone"# Json..=# uPhone <> "address"# Json..=# uAddress <> "about"# Json..=# uAbout <> "registered"# Json..=# uRegistered <> "latitude"# Json..=# uLatitude <> "longitude"# Json..=# uLongitude <> "tags"# Json..=# uTags <> "friends"# Json..=# uFriends <> "greeting"# Json..=# uGreeting <> "favoriteFruit"# Json..=# uFavouriteFruit #ifdef MIN_VERSION_json_builder ---- json-builder instances ---- instance JB.Value EyeColor where toJson ec = JB.toJson $ case ec of Green -> "green" :: Text Blue -> "blue" Brown -> "brown" instance JB.Value Gender where toJson g = JB.toJson $ case g of Male -> "male" :: Text Female -> "female" instance JB.Value Fruit where toJson f = JB.toJson $ case f of Apple -> "apple" :: Text Strawberry -> "strawberry" Banana -> "banana" instance JB.Value Friend where toJson Friend{..} = JB.toJson $ ("_id" :: Text) `JB.row` fId <> ("name" :: Text) `JB.row` fName instance JB.Value User where toJson User{..} = let t :: Text -> Text t = id in JB.toJson $ t "_id" `JB.row` uId <> t "index" `JB.row` uIndex <> t "guid" `JB.row` uGuid <> t "isActive" `JB.row` uIsActive <> t "balance" `JB.row` uBalance <> t "picture" `JB.row` uPicture <> t "age" `JB.row` uAge <> t "eyeColor" `JB.row` uEyeColor <> t "name" `JB.row` uName <> t "gender" `JB.row` uGender <> t "company" `JB.row` uCompany <> t "email" `JB.row` uEmail <> t "phone" `JB.row` uPhone <> t "address" `JB.row` uAddress <> t "about" `JB.row` uAbout <> t "registered" `JB.row` uRegistered <> t "latitude" `JB.row` uLatitude <> t "longitude" `JB.row` uLongitude <> t "tags" `JB.row` uTags <> t "friends" `JB.row` uFriends <> t "greeting" `JB.row` uGreeting <> t "favoriteFruit" `JB.row` uFavouriteFruit #endif benchmarks :: Benchmark benchmarks = env (load "json-data/buffer-builder.json") $ \ ~(parsedUserList :: [User]) -> bgroup "json-bench" [ bench "aeson" $ nf Aeson.encode parsedUserList , bench "buffer-builder" $ nf Json.encodeJson parsedUserList #ifdef MIN_VERSION_json_builder , bench "json-builder" $ nf JB.toJsonLBS parsedUserList #endif ] aeson-1.4.2.0/benchmarks/Compare/JsonBuilder.hs0000755000000000000000000000342700000000000017400 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Compare.JsonBuilder () where import Prelude.Compat hiding ((<>)) import Data.Json.Builder import Data.Monoid ((<>)) import Twitter instance JsObject Metadata where toObject Metadata{..} = row "result_type" result_type instance Value Metadata where toJson = toJson . toObject instance JsObject Geo where toObject Geo{..} = row "type_" type_ <> row "coordinates" coordinates instance Value Geo where toJson = toJson . toObject instance Value a => Value (Maybe a) where toJson (Just a) = toJson a toJson Nothing = jsNull instance JsObject Story where toObject Story{..} = row "from_user_id_str" from_user_id_str <> row "profile_image_url" profile_image_url <> row "created_at" created_at <> row "from_user" from_user <> row "id_str" id_str <> row "metadata" metadata <> row "to_user_id" to_user_id <> row "text" text <> row "id" id_ <> row "from_user_id" from_user_id <> row "geo" geo <> row "iso_language_code" iso_language_code <> row "to_user_id_str" to_user_id_str <> row "source" source instance Value Story where toJson = toJson . toObject instance JsObject Result where toObject Result{..} = row "results" results <> row "max_id" max_id <> row "since_id" since_id <> row "refresh_url" refresh_url <> row "next_page" next_page <> row "results_per_page" results_per_page <> row "page" page <> row "completed_in" completed_in <> row "since_id_str" since_id_str <> row "max_id_str" max_id_str <> row "query" query instance Value Result where toJson = toJson . toObject aeson-1.4.2.0/benchmarks/CompareWithJSON.hs0000755000000000000000000000635400000000000016510 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Main (main) where import Prelude.Compat import Blaze.ByteString.Builder (toLazyByteString) import Blaze.ByteString.Builder.Char.Utf8 (fromString) import Control.DeepSeq (NFData(rnf)) import Criterion.Main import Data.Maybe (fromMaybe) import qualified Data.Aeson as A import qualified Data.Aeson.Text as A import qualified Data.Aeson.Parser.Internal as I import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as BL import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TLB import qualified Data.Text.Lazy.Encoding as TLE import qualified Text.JSON as J instance (NFData v) => NFData (J.JSObject v) where rnf o = rnf (J.fromJSObject o) instance NFData J.JSValue where rnf J.JSNull = () rnf (J.JSBool b) = rnf b rnf (J.JSRational a b) = rnf a `seq` rnf b `seq` () rnf (J.JSString s) = rnf (J.fromJSString s) rnf (J.JSArray lst) = rnf lst rnf (J.JSObject o) = rnf o decodeJ :: String -> J.JSValue decodeJ s = case J.decodeStrict s of J.Ok v -> v J.Error _ -> error "fail to parse via JSON" decode :: BL.ByteString -> A.Value decode s = fromMaybe (error "fail to parse via Aeson") $ A.decode s decode' :: BL.ByteString -> A.Value decode' s = fromMaybe (error "fail to parse via Aeson") $ A.decode' s decodeS :: BS.ByteString -> A.Value decodeS s = fromMaybe (error "fail to parse via Aeson") $ A.decodeStrict' s decodeIP :: BL.ByteString -> A.Value decodeIP s = fromMaybe (error "fail to parse via Parser.decodeWith") $ I.decodeWith I.jsonEOF A.fromJSON s encodeJ :: J.JSValue -> BL.ByteString encodeJ = toLazyByteString . fromString . J.encode encodeToText :: A.Value -> TL.Text encodeToText = TLB.toLazyText . A.encodeToTextBuilder . A.toJSON encodeViaText :: A.Value -> BL.ByteString encodeViaText = TLE.encodeUtf8 . encodeToText main :: IO () main = do let enFile = "json-data/twitter100.json" jpFile = "json-data/jp100.json" enA <- BL.readFile enFile enS <- BS.readFile enFile enJ <- readFile enFile jpA <- BL.readFile jpFile jpS <- BS.readFile jpFile jpJ <- readFile jpFile defaultMain [ bgroup "decode" [ bgroup "en" [ bench "aeson/lazy" $ nf decode enA , bench "aeson/strict" $ nf decode' enA , bench "aeson/stricter" $ nf decodeS enS , bench "aeson/parser" $ nf decodeIP enA , bench "json" $ nf decodeJ enJ ] , bgroup "jp" [ bench "aeson" $ nf decode jpA , bench "aeson/stricter" $ nf decodeS jpS , bench "json" $ nf decodeJ jpJ ] ] , bgroup "encode" [ bgroup "en" [ bench "aeson-to-bytestring" $ nf A.encode (decode enA) , bench "aeson-via-text-to-bytestring" $ nf encodeViaText (decode enA) , bench "aeson-to-text" $ nf encodeToText (decode enA) , bench "json" $ nf encodeJ (decodeJ enJ) ] , bgroup "jp" [ bench "aeson-to-bytestring" $ nf A.encode (decode jpA) , bench "aeson-via-text-to-bytestring" $ nf encodeViaText (decode jpA) , bench "aeson-to-text" $ nf encodeToText (decode jpA) , bench "json" $ nf encodeJ (decodeJ jpJ) ] ] ] aeson-1.4.2.0/benchmarks/Dates.hs0000755000000000000000000000240300000000000014623 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Main (main) where import Prelude.Compat import Criterion.Main import Data.Aeson (decode, encode) import Data.Time.Clock (UTCTime) import Data.Time.LocalTime (ZonedTime) import qualified Data.ByteString.Lazy as BL utcTime :: BL.ByteString -> Maybe [UTCTime] utcTime = decode zTime :: BL.ByteString -> Maybe [ZonedTime] zTime = decode main :: IO () main = do let file1 = BL.readFile "json-data/dates.json" let file2 = BL.readFile "json-data/dates-fract.json" defaultMain [ bgroup "decode" [ bgroup "UTCTime" [ env file1 $ \bs -> bench "whole" $ nf utcTime bs , env file2 $ \bs -> bench "fractional" $ nf utcTime bs ] , bgroup "ZonedTime" [ env file1 $ \bs -> bench "whole" $ nf zTime bs , env file2 $ \bs -> bench "fractional" $ nf zTime bs ] ] , bgroup "encode" [ bgroup "UTCTime" [ env (utcTime <$> file1) $ \ts -> bench "whole" $ nf encode ts , env (utcTime <$> file2) $ \ts -> bench "fractional" $ nf encode ts ] , bgroup "ZonedTime" [ env (zTime <$> file1) $ \ts -> bench "whole" $ nf encode ts , env (zTime <$> file2) $ \ts -> bench "fractional" $ nf encode ts ] ] ] aeson-1.4.2.0/benchmarks/Escape.hs0000755000000000000000000000155100000000000014766 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} module Main (main) where import Prelude.Compat import Criterion.Main import qualified Data.Aeson.Parser.UnescapeFFI as FFI import qualified Data.Aeson.Parser.UnescapePure as Pure import qualified Data.ByteString.Char8 as BS import System.Environment (getArgs, withArgs) main :: IO () main = do args_ <- getArgs let (args, p, n) = case args_ of "--pattern" : p : args_ -> k p args_ _ -> k "\\\"" args_ k p args_ = case args_ of "--repeat" : n : args_ -> (args_, p, read n) args_ -> (args_, p, 10000) input = BS.concat $ replicate n $ BS.pack p withArgs args $ defaultMain [ bench "ffi" $ whnf FFI.unescapeText input , bench "pure" $ whnf Pure.unescapeText input ] aeson-1.4.2.0/benchmarks/Issue673.hs0000755000000000000000000001105100000000000015112 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Main ( main, input17, input32, input64, input128, input256, input2048, input4096, input8192, input16384, ) where import Criterion.Main import Prelude.Compat import Data.Int (Int64) import Data.Scientific (Scientific) import Data.Aeson.Parser (scientific) import qualified Data.Attoparsec.ByteString.Lazy as AttoL import qualified Data.Attoparsec.ByteString.Char8 as Atto8 import qualified Data.Aeson as A import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as LBS import qualified Data.ByteString.Lazy.Char8 as LBS8 decodeInt :: LBS.ByteString -> Maybe Int decodeInt = A.decode decodeString :: LBS.ByteString -> Maybe String decodeString = A.decode decodeScientific :: LBS.ByteString -> Maybe Scientific decodeScientific = A.decode decodeViaRead :: LBS.ByteString -> Integer decodeViaRead = read . LBS8.unpack decodeAtto :: LBS.ByteString -> Maybe Scientific decodeAtto = parseOnly (scientific <* AttoL.endOfInput) where parseOnly p lbs = case AttoL.parse p lbs of AttoL.Done _ r -> Just r AttoL.Fail {} -> Nothing decodeAtto8 :: LBS.ByteString -> Maybe Scientific decodeAtto8 = parseOnly (Atto8.scientific <* AttoL.endOfInput) where parseOnly p lbs = case AttoL.parse p lbs of AttoL.Done _ r -> Just r AttoL.Fail {} -> Nothing generate :: Int64 -> LBS.ByteString generate n = LBS8.replicate n '1' input17 :: LBS.ByteString input17 = generate 17 input32 :: LBS.ByteString input32 = generate 32 input64 :: LBS.ByteString input64 = generate 64 input128 :: LBS.ByteString input128 = generate 128 input256 :: LBS.ByteString input256 = generate 256 input2048 :: LBS.ByteString input2048 = generate 2048 input4096 :: LBS.ByteString input4096 = generate 4096 input8192 :: LBS.ByteString input8192 = generate 8192 input16384 :: LBS.ByteString input16384 = generate 16384 main :: IO () main = defaultMain -- works on 64bit [ benchPair "17" input17 -- , benchPair "32" input32 -- , benchPair "64" input64 -- , benchPair "128" input128 -- , benchPair "256" input256 , benchPair "2048" input2048 , benchPair "4096" input4096 , benchPair "8192" input8192 , benchPair "16384" input16384 ] where benchPair name input = bgroup name [ bench "Int" $ whnf decodeInt input , bench "Simple" $ whnf bsToIntegerSimple (LBS.toStrict input) , bench "Optim" $ whnf bsToInteger (LBS.toStrict input) , bench "Read" $ whnf decodeViaRead input , bench "Scientific" $ whnf decodeScientific input , bench "parserA" $ whnf decodeAtto input , bench "parserS" $ whnf decodeAtto8 input , bench "String" $ whnf decodeString $ "\"" <> input <> "\"" ] ------------------------------------------------------------------------------- -- better fromInteger ------------------------------------------------------------------------------- bsToInteger :: BS.ByteString -> Integer bsToInteger bs | l > 40 = valInteger 10 l [ fromIntegral (w - 48) | w <- BS.unpack bs ] | otherwise = bsToIntegerSimple bs where l = BS.length bs bsToIntegerSimple :: BS.ByteString -> Integer bsToIntegerSimple = BS.foldl' step 0 where step a b = a * 10 + fromIntegral (b - 48) -- 48 = '0' -- A sub-quadratic algorithm for Integer. Pairs of adjacent radix b -- digits are combined into a single radix b^2 digit. This process is -- repeated until we are left with a single digit. This algorithm -- performs well only on large inputs, so we use the simple algorithm -- for smaller inputs. valInteger :: Integer -> Int -> [Integer] -> Integer valInteger = go where go :: Integer -> Int -> [Integer] -> Integer go _ _ [] = 0 go _ _ [d] = d go b l ds | l > 40 = b' `seq` go b' l' (combine b ds') | otherwise = valSimple b ds where -- ensure that we have an even number of digits -- before we call combine: ds' = if even l then ds else 0 : ds b' = b * b l' = (l + 1) `quot` 2 combine b (d1 : d2 : ds) = d `seq` (d : combine b ds) where d = d1 * b + d2 combine _ [] = [] combine _ [_] = errorWithoutStackTrace "this should not happen" -- The following algorithm is only linear for types whose Num operations -- are in constant time. valSimple :: Integer -> [Integer] -> Integer valSimple base = go 0 where go r [] = r go r (d : ds) = r' `seq` go r' ds where r' = r * base + fromIntegral d aeson-1.4.2.0/benchmarks/JsonParse.hs0000755000000000000000000000211400000000000015466 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Main (main) where import Prelude.Compat import Control.DeepSeq import Control.Monad import Data.Time.Clock import System.Environment (getArgs) import Text.JSON instance NFData JSValue where rnf JSNull = () rnf (JSBool b) = rnf b rnf (JSRational b r) = rnf b `seq` rnf r `seq` () rnf (JSString s) = rnf (fromJSString s) rnf (JSArray vs) = rnf vs rnf (JSObject kvs) = rnf (fromJSObject kvs) main :: IO () main = do (cnt:args) <- getArgs let count = read cnt :: Int forM_ args $ \arg -> do putStrLn $ arg ++ ":" start <- getCurrentTime let loop !good !bad | good+bad >= count = return (good, bad) | otherwise = do s <- readFile arg case decodeStrict s of Ok (_::JSValue) -> loop (good+1) 0 _ -> loop 0 (bad+1) (good, _) <- loop 0 0 end <- getCurrentTime putStrLn $ " " ++ show good ++ " good, " ++ show (diffUTCTime end start) aeson-1.4.2.0/benchmarks/Makefile0000755000000000000000000000047300000000000014674 0ustar0000000000000000ghc := ghc ghcflags := -O binaries := AesonParse AesonEncode JsonParse AesonCompareAutoInstances all: $(binaries) $(binaries:%=%_p) %_p: %.hs $(ghc) $(ghcflags) -prof -auto-all -rtsopts --make -o $@ $^ %: %.hs $(ghc) $(ghcflags) --make -rtsopts -o $@ $^ clean: -rm -f *.o *.hi $(binaries) $(binaries:%=%_p) aeson-1.4.2.0/benchmarks/Micro.hs0000755000000000000000000000116400000000000014637 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Main (main) where import Prelude.Compat import Criterion.Main -- Encoding is a newtype wrapper around Builder import Data.Aeson.Encoding (text, string, encodingToLazyByteString) import qualified Data.Text as T main :: IO () main = do let txt = "append (append b (primBounded w1 x1)) (primBounded w2 x2)" defaultMain [ bgroup "string" [ bench "text" $ nf (encodingToLazyByteString . text) (T.pack txt) , bench "string direct" $ nf (encodingToLazyByteString . string) txt , bench "string via text" $ nf (encodingToLazyByteString . text . T.pack) txt ] ] aeson-1.4.2.0/benchmarks/Options.hs0000755000000000000000000000022200000000000015213 0ustar0000000000000000module Options (opts) where import Data.Aeson.Types opts :: Options opts = defaultOptions { sumEncoding = ObjectWithSingleField } aeson-1.4.2.0/benchmarks/ReadFile.hs0000755000000000000000000000161000000000000015235 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Prelude.Compat import Control.DeepSeq import Control.Exception import Control.Monad import Data.Aeson import Data.Aeson.Parser import Data.Attoparsec import Data.Time.Clock import System.Environment (getArgs) import System.IO import qualified Data.ByteString as B main = do (cnt:args) <- getArgs let count = read cnt :: Int forM_ args $ \arg -> withFile arg ReadMode $ \h -> do putStrLn $ arg ++ ":" start <- getCurrentTime let loop !n | n >= count = return () | otherwise = do let go = do s <- B.hGet h 16384 if B.null s then loop (n+1) else go go loop 0 end <- getCurrentTime putStrLn $ " " ++ show (diffUTCTime end start) aeson-1.4.2.0/benchmarks/Typed.hs0000755000000000000000000000062500000000000014654 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Main (main) where import Prelude.Compat import Criterion.Main import qualified Typed.Generic as Generic import qualified Typed.Manual as Manual import qualified Typed.TH as TH main :: IO () main = defaultMain [ Generic.benchmarks , Manual.benchmarks , TH.benchmarks , Generic.decodeBenchmarks , Manual.decodeBenchmarks , TH.decodeBenchmarks ] aeson-1.4.2.0/benchmarks/Typed/0000755000000000000000000000000000000000000014312 5ustar0000000000000000aeson-1.4.2.0/benchmarks/Typed/Common.hs0000755000000000000000000000077100000000000016106 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} module Typed.Common (load) where import Prelude.Compat import Data.ByteString.Lazy as L import System.Exit import System.IO import Data.Aeson hiding (Result) load :: FromJSON a => FilePath -> IO a load fileName = do mv <- eitherDecode' <$> L.readFile fileName case mv of Right v -> return v Left err -> do hPutStrLn stderr $ fileName ++ ": JSON decode failed - " ++ err exitWith (ExitFailure 1) aeson-1.4.2.0/benchmarks/Typed/Generic.hs0000755000000000000000000000234500000000000016231 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Typed.Generic (benchmarks, decodeBenchmarks) where import Prelude.Compat import Data.Aeson hiding (Result) import Criterion import Data.ByteString.Lazy as L import Twitter.Generic import Typed.Common encodeDirect :: Result -> L.ByteString encodeDirect = encode encodeViaValue :: Result -> L.ByteString encodeViaValue = encode . toJSON benchmarks :: Benchmark benchmarks = env ((,) <$> load "json-data/twitter100.json" <*> load "json-data/jp100.json") $ \ ~(twitter100, jp100) -> bgroup "encodeGeneric" [ bgroup "direct" [ bench "twitter100" $ nf encodeDirect twitter100 , bench "jp100" $ nf encodeDirect jp100 ] , bgroup "viaValue" [ bench "twitter100" $ nf encodeViaValue twitter100 , bench "jp100" $ nf encodeViaValue jp100 ] ] decodeDirect :: L.ByteString -> Maybe Result decodeDirect = decode decodeBenchmarks :: Benchmark decodeBenchmarks = env ((,) <$> L.readFile "json-data/twitter100.json" <*> L.readFile "json-data/jp100.json") $ \ ~(twitter100, jp100) -> bgroup "decodeGeneric" [ bgroup "direct" [ bench "twitter100" $ nf decodeDirect twitter100 , bench "jp100" $ nf decodeDirect jp100 ] ] aeson-1.4.2.0/benchmarks/Typed/Manual.hs0000755000000000000000000000234100000000000016066 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Typed.Manual (benchmarks, decodeBenchmarks) where import Prelude.Compat import Data.Aeson hiding (Result) import Criterion import Data.ByteString.Lazy as L import Twitter.Manual import Typed.Common encodeDirect :: Result -> L.ByteString encodeDirect = encode encodeViaValue :: Result -> L.ByteString encodeViaValue = encode . toJSON benchmarks :: Benchmark benchmarks = env ((,) <$> load "json-data/twitter100.json" <*> load "json-data/jp100.json") $ \ ~(twitter100, jp100) -> bgroup "encodeManual" [ bgroup "direct" [ bench "twitter100" $ nf encodeDirect twitter100 , bench "jp100" $ nf encodeDirect jp100 ] , bgroup "viaValue" [ bench "twitter100" $ nf encodeViaValue twitter100 , bench "jp100" $ nf encodeViaValue jp100 ] ] decodeDirect :: L.ByteString -> Maybe Result decodeDirect = decode decodeBenchmarks :: Benchmark decodeBenchmarks = env ((,) <$> L.readFile "json-data/twitter100.json" <*> L.readFile "json-data/jp100.json") $ \ ~(twitter100, jp100) -> bgroup "decodeManual" [ bgroup "direct" [ bench "twitter100" $ nf decodeDirect twitter100 , bench "jp100" $ nf decodeDirect jp100 ] ] aeson-1.4.2.0/benchmarks/Typed/TH.hs0000755000000000000000000000232100000000000015162 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Typed.TH (benchmarks, decodeBenchmarks) where import Prelude.Compat import Data.Aeson hiding (Result) import Criterion import Data.ByteString.Lazy as L import Twitter.TH import Typed.Common encodeDirect :: Result -> L.ByteString encodeDirect = encode encodeViaValue :: Result -> L.ByteString encodeViaValue = encode . toJSON benchmarks :: Benchmark benchmarks = env ((,) <$> load "json-data/twitter100.json" <*> load "json-data/jp100.json") $ \ ~(twitter100, jp100) -> bgroup "encodeTH" [ bgroup "direct" [ bench "twitter100" $ nf encodeDirect twitter100 , bench "jp100" $ nf encodeDirect jp100 ] , bgroup "viaValue" [ bench "twitter100" $ nf encodeViaValue twitter100 , bench "jp100" $ nf encodeViaValue jp100 ] ] decodeDirect :: L.ByteString -> Maybe Result decodeDirect = decode decodeBenchmarks :: Benchmark decodeBenchmarks = env ((,) <$> L.readFile "json-data/twitter100.json" <*> L.readFile "json-data/jp100.json") $ \ ~(twitter100, jp100) -> bgroup "decodeTH" [ bgroup "direct" [ bench "twitter100" $ nf decodeDirect twitter100 , bench "jp100" $ nf decodeDirect jp100 ] ] aeson-1.4.2.0/benchmarks/aeson-benchmarks.cabal0000755000000000000000000001633400000000000017443 0ustar0000000000000000name: aeson-benchmarks version: 0 build-type: Simple cabal-version: >=1.10 flag bytestring-builder description: Depend on the bytestring-builder package for backwards compatibility. default: False manual: False flag local-aeson description: Build the local version of aeson, to avoid rebuilding aeson's reverse dependencies for benchmarking (statistics, criterion). default: True manual: True library default-language: Haskell2010 if flag(bytestring-builder) build-depends: bytestring >= 0.9 && < 0.10.4, bytestring-builder >= 0.10.4 && < 1 else build-depends: bytestring >= 0.10.4 if flag(local-aeson) hs-source-dirs: .. ../ffi ../pure ../attoparsec-iso8601 c-sources: ../cbits/unescape_string.c build-depends: attoparsec >= 0.13.0.1, base == 4.*, base-compat >= 0.9.1 && <0.11, time-locale-compat >=0.1.1 && <0.2, containers, deepseq, dlist >= 0.2, fail == 4.9.*, ghc-prim >= 0.2, hashable >= 1.1.2.0, mtl, primitive >= 0.6.1, scientific >= 0.3.4.7 && < 0.4, syb, tagged >=0.8.3 && <0.9, template-haskell >= 2.4, text >= 1.2.3, th-abstraction >= 0.2.2 && < 0.3, time, transformers, unordered-containers >= 0.2.3.0, uuid-types >= 1.0.3 && <1.1, vector >= 0.7.1 if !impl(ghc >= 7.10) -- `Numeric.Natural` is available in base only since GHC 7.10 / base 4.8 build-depends: nats >= 1 && < 1.2 if impl(ghc >=7.8) cpp-options: -DHAS_COERCIBLE if !impl(ghc >= 8.0) -- `Data.Semigroup` is available in base only since GHC 8.0 / base 4.9 build-depends: semigroups >= 0.18.2 && < 0.19 if !impl(ghc >= 8.6) build-depends: contravariant >=1.4.1 && <1.6 include-dirs: ../include ghc-options: -O2 -Wall cpp-options: -DGENERICS exposed-modules: Data.Aeson Data.Aeson.Compat Data.Aeson.Encoding Data.Aeson.Encoding.Builder Data.Aeson.Encoding.Internal Data.Aeson.Internal Data.Aeson.Internal.Functions Data.Aeson.Internal.Time Data.Aeson.Parser Data.Aeson.Parser.Internal Data.Aeson.Parser.Time Data.Aeson.Parser.Unescape Data.Aeson.Parser.UnescapeFFI Data.Aeson.Parser.UnescapePure Data.Aeson.TH Data.Aeson.Text Data.Aeson.Types Data.Aeson.Types.Class Data.Aeson.Types.FromJSON Data.Aeson.Types.Generic Data.Aeson.Types.Internal Data.Aeson.Types.ToJSON Data.Attoparsec.Time Data.Attoparsec.Time.Internal else build-depends: aeson reexported-modules: Data.Aeson, Data.Aeson.Encoding, Data.Aeson.Parser.Internal, Data.Aeson.Text, Data.Aeson.TH, Data.Aeson.Types executable aeson-benchmark-auto-compare default-language: Haskell2010 main-is: AutoCompare.hs hs-source-dirs: . ghc-options: -Wall -O2 -rtsopts other-modules: Auto.T.D Auto.T.BigRecord Auto.T.BigProduct Auto.T.BigSum Auto.G.D Auto.G.BigRecord Auto.G.BigProduct Auto.G.BigSum Options build-depends: aeson-benchmarks, base, criterion, deepseq, template-haskell executable aeson-benchmark-escape default-language: Haskell2010 main-is: Escape.hs hs-source-dirs: ../examples . ghc-options: -Wall -O2 -rtsopts if flag(local-aeson) build-depends: aeson-benchmarks, base, base-compat, bytestring, criterion >= 1.0, deepseq, ghc-prim, text else -- Disabled because of inaccessible internals buildable: False executable aeson-benchmark-compare default-language: Haskell2010 main-is: Compare.hs hs-source-dirs: ../examples . ghc-options: -Wall -O2 -rtsopts other-modules: Compare.BufferBuilder Compare.JsonBench Twitter Twitter.Manual Typed.Common build-depends: aeson-benchmarks, base, base-compat, buffer-builder, bytestring, criterion >= 1.0, deepseq, ghc-prim, text if impl(ghc < 8.4) other-modules: Compare.JsonBuilder build-depends: json-builder executable aeson-benchmark-micro default-language: Haskell2010 main-is: Micro.hs hs-source-dirs: ../examples . ghc-options: -Wall -O2 -rtsopts build-depends: aeson-benchmarks, base, base-compat, bytestring, criterion >= 1.0, deepseq, ghc-prim, text executable aeson-benchmark-typed default-language: Haskell2010 main-is: Typed.hs hs-source-dirs: ../examples . ghc-options: -Wall -O2 -rtsopts other-modules: Twitter Twitter.Generic Twitter.Manual Twitter.Options Twitter.TH Typed.Common Typed.Generic Typed.Manual Typed.TH build-depends: aeson-benchmarks, base, base-compat, criterion >= 1.0, deepseq, ghc-prim, text, time if flag(bytestring-builder) build-depends: bytestring >= 0.9 && < 0.10.4, bytestring-builder >= 0.10.4 && < 1 else build-depends: bytestring >= 0.10.4 executable aeson-benchmark-compare-with-json default-language: Haskell2010 main-is: CompareWithJSON.hs ghc-options: -Wall -O2 -rtsopts build-depends: aeson-benchmarks, base, base-compat, blaze-builder, bytestring, criterion, deepseq, json, text executable aeson-benchmark-aeson-encode default-language: Haskell2010 main-is: AesonEncode.hs ghc-options: -Wall -O2 -rtsopts build-depends: aeson-benchmarks, attoparsec, base, base-compat, bytestring, deepseq, time executable aeson-benchmark-aeson-parse default-language: Haskell2010 main-is: AesonParse.hs ghc-options: -Wall -O2 -rtsopts build-depends: aeson-benchmarks, attoparsec, base, base-compat, bytestring, time executable aeson-benchmark-json-parse default-language: Haskell2010 main-is: JsonParse.hs ghc-options: -Wall -O2 -rtsopts build-depends: base, base-compat, deepseq, json, time executable aeson-benchmark-dates default-language: Haskell2010 main-is: Dates.hs ghc-options: -Wall -O2 -rtsopts build-depends: base, base-compat, bytestring, criterion, deepseq, aeson-benchmarks, text, time if impl(ghc >= 8.2) ghc-options: -Wno-simplifiable-class-constraints executable aeson-benchmark-map default-language: Haskell2010 main-is: AesonMap.hs ghc-options: -Wall -O2 -rtsopts build-depends: aeson-benchmarks, base, base-compat, criterion >= 1.0, bytestring, containers, deepseq, hashable, tagged, text, unordered-containers executable aeson-benchmark-foldable default-language: Haskell2010 main-is: AesonFoldable.hs ghc-options: -Wall -O2 -rtsopts build-depends: aeson-benchmarks, base, base-compat, criterion >= 1.0, bytestring, containers, deepseq, hashable, tagged, text, unordered-containers, vector executable aeson-issue-673 default-language: Haskell2010 main-is: Issue673.hs ghc-options: -Wall -O1 -rtsopts build-depends: aeson-benchmarks, attoparsec, base, bytestring, scientific, base-compat, criterion >= 1.0 aeson-1.4.2.0/benchmarks/bench-parse.py0000755000000000000000000000343600000000000015777 0ustar0000000000000000#!/usr/bin/env python import os, re, subprocess, sys result_re = re.compile(r'^\s*(\d+) good, (\d+\.\d+)s$', re.M) if len(sys.argv) > 1: parser_exe = sys.argv[1] else: parser_exe = ('dist/build/aeson-benchmark-aeson-parse/' + 'aeson-benchmark-aeson-parse') def run(count, filename): print ' %s :: %s times' % (filename, count) p = subprocess.Popen([parser_exe, '65536', str(count), filename], stdout=subprocess.PIPE) output = p.stdout.read() p.wait() m = result_re.search(output) if not m: print >> sys.stderr, 'run gave confusing output!?' sys.stderr.write(output) return else: #sys.stdout.write(output) pass good, elapsed = m.groups() good, elapsed = int(good), float(elapsed) st = os.stat(filename) parses_per_second = good / elapsed mb_per_second = st.st_size * parses_per_second / 1048576 print (' %.3f seconds, %d parses/sec, %.3f MB/sec' % (elapsed, parses_per_second, mb_per_second)) return parses_per_second, mb_per_second, st.st_size, elapsed def runtimes(count, filename, times=1): for i in xrange(times): yield run(count, filename) info = ''' json-data/twitter1.json 60000 json-data/twitter10.json 13000 json-data/twitter20.json 7500 json-data/twitter50.json 2500 json-data/twitter100.json 1000 json-data/jp10.json 4000 json-data/jp50.json 1200 json-data/jp100.json 700 ''' for i in info.strip().splitlines(): name, count = i.split() best = sorted(runtimes(int(count), name, times=3), reverse=True)[0] parses_per_second, mb_per_second, size, elapsed = best print ('%.1f KB: %d msg\\/sec (%.1f MB\\/sec)' % (size / 1024.0, int(round(parses_per_second)), mb_per_second)) aeson-1.4.2.0/benchmarks/encode.py0000755000000000000000000000073200000000000015041 0ustar0000000000000000#!/usr/bin/env python import json, sys, time def isint(x): try: int(x) return True except: return False if len(sys.argv) > 2 and isint(sys.argv[1]) and isint(sys.argv[2]): sys.argv.pop(1) count = int(sys.argv[1]) for n in sys.argv[2:]: print '%s:' % n obj = json.load(open(n)) start = time.time() for i in xrange(count): json.dumps(obj) end = time.time() print ' %d good, %gs' % (count, end - start) aeson-1.4.2.0/benchmarks/json-data/0000755000000000000000000000000000000000000015105 5ustar0000000000000000aeson-1.4.2.0/benchmarks/json-data/buffer-builder.json0000755000000000000000000040540600000000000020711 0ustar0000000000000000[ { "_id": "54727a90e43524efe8abfdac", "index": 0, "guid": "aaa926e8-8359-4afe-adb0-dca0401de765", "isActive": true, "balance": "$1,114.73", "picture": "http://placehold.it/32x32", "age": 20, "eyeColor": "green", "name": "Dillon Valenzuela", "gender": "male", "company": "GEOFORM", "email": "dillonvalenzuela@geoform.com", "phone": "+1 (817) 536-3796", "address": "309 Desmond Court, Zarephath, Montana, 6156", "about": "Dolore laboris excepteur sunt velit velit nostrud non esse qui laboris nostrud Lorem. Amet anim occaecat et ipsum. Ad proident nostrud elit adipisicing anim labore consectetur ut amet elit. Tempor aliqua in ea eiusmod elit Lorem cillum est laboris. Nisi Lorem amet amet Lorem. Nostrud sunt incididunt magna nostrud amet enim. Laboris ad et fugiat dolor ad proident aliquip nisi do ea eiusmod enim proident.\r\n", "registered": "2014-08-17T07:29:03 +07:00", "latitude": -17.423462, "longitude": 121.069662, "tags": [ "sunt", "ex", "irure", "cillum", "velit", "duis", "sit" ], "friends": [ { "id": 0, "name": "Joyce Jordan" }, { "id": 1, "name": "Ophelia Rosales" }, { "id": 2, "name": "Florine Stark" } ], "greeting": "Hello, Dillon Valenzuela! You have 9 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90f520a07ff2498a69", "index": 1, "guid": "8f78cc18-a7ef-498b-9adf-60f008a48c02", "isActive": false, "balance": "$1,324.52", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "blue", "name": "Donovan Weiss", "gender": "male", "company": "TELPOD", "email": "donovanweiss@telpod.com", "phone": "+1 (962) 417-2408", "address": "511 Grant Avenue, Westmoreland, Hawaii, 5092", "about": "Laborum excepteur exercitation sint veniam dolor. Dolor aliqua esse do aliqua adipisicing. Ea magna minim veniam tempor ipsum. Incididunt anim reprehenderit occaecat proident eiusmod anim Lorem aliquip dolore incididunt. Consequat occaecat qui minim commodo est velit ex.\r\n", "registered": "2014-09-30T23:49:41 +07:00", "latitude": -18.034963, "longitude": 70.821705, "tags": [ "cupidatat", "excepteur", "id", "consectetur", "ea", "enim", "et" ], "friends": [ { "id": 0, "name": "Cummings Irwin" }, { "id": 1, "name": "Conley Lester" }, { "id": 2, "name": "Katy Holt" } ], "greeting": "Hello, Donovan Weiss! You have 2 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90fbb3f49ea6d40dde", "index": 2, "guid": "69a4c6d7-6189-4a90-ae00-7b64ab1d5a2d", "isActive": false, "balance": "$2,739.87", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "brown", "name": "Renee Calderon", "gender": "female", "company": "TALKOLA", "email": "reneecalderon@talkola.com", "phone": "+1 (910) 523-3382", "address": "323 Montauk Avenue, Greenwich, South Dakota, 8034", "about": "Reprehenderit deserunt et do proident Lorem Lorem dolor labore ullamco eu nulla laborum voluptate. Consectetur sint magna enim commodo dolore ullamco in. Nulla id proident esse veniam proident esse velit exercitation do. Qui nulla magna anim Lorem dolor culpa id. Nostrud cupidatat officia culpa sit irure voluptate exercitation voluptate nostrud elit. Duis occaecat velit fugiat exercitation anim aute laborum irure.\r\n", "registered": "2014-09-11T20:48:20 +07:00", "latitude": 15.654081, "longitude": 84.156609, "tags": [ "dolor", "et", "in", "veniam", "non", "est", "enim" ], "friends": [ { "id": 0, "name": "Gilda Murray" }, { "id": 1, "name": "Marguerite West" }, { "id": 2, "name": "Chrystal Rojas" } ], "greeting": "Hello, Renee Calderon! You have 1 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90c5ea2a48502a0640", "index": 3, "guid": "689a64d7-16b0-41dc-947d-035b40a29ed4", "isActive": false, "balance": "$3,805.39", "picture": "http://placehold.it/32x32", "age": 32, "eyeColor": "blue", "name": "Aguirre Garrett", "gender": "male", "company": "ZOSIS", "email": "aguirregarrett@zosis.com", "phone": "+1 (811) 471-3145", "address": "198 Baycliff Terrace, Clarence, District Of Columbia, 1528", "about": "Deserunt minim aliquip magna ut fugiat quis. Quis consequat culpa reprehenderit minim do eiusmod adipisicing nostrud aute. Lorem nostrud laborum quis dolore tempor tempor magna aute eu pariatur dolor est. Reprehenderit ex consectetur adipisicing Lorem nostrud fugiat aute non quis anim laborum aute proident amet. Sunt consectetur eu ut eu mollit ipsum.\r\n", "registered": "2014-02-14T04:27:27 +08:00", "latitude": 25.922024, "longitude": 107.428199, "tags": [ "esse", "officia", "commodo", "esse", "cupidatat", "amet", "ad" ], "friends": [ { "id": 0, "name": "Penelope Humphrey" }, { "id": 1, "name": "Church Byers" }, { "id": 2, "name": "Hazel Stafford" } ], "greeting": "Hello, Aguirre Garrett! You have 4 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a9096bcf2d2f4b4aeff", "index": 4, "guid": "77392422-81ad-48c8-9cfc-37d142a814d5", "isActive": false, "balance": "$1,956.06", "picture": "http://placehold.it/32x32", "age": 26, "eyeColor": "brown", "name": "Griffin Mclaughlin", "gender": "male", "company": "COMTOUR", "email": "griffinmclaughlin@comtour.com", "phone": "+1 (950) 494-2956", "address": "549 Robert Street, Libertytown, North Carolina, 4377", "about": "Exercitation culpa ad id deserunt sit ullamco anim anim ad aute officia ut tempor. Ullamco dolor pariatur enim exercitation commodo consectetur fugiat velit nulla mollit pariatur occaecat. Amet voluptate qui labore mollit ipsum consequat. Esse pariatur proident ad pariatur aliquip labore quis voluptate quis ut culpa tempor. Reprehenderit sint id officia deserunt quis laboris. Velit ipsum dolore anim consectetur.\r\n", "registered": "2014-06-23T04:48:12 +07:00", "latitude": 8.808284, "longitude": 20.539814, "tags": [ "consequat", "proident", "eiusmod", "dolore", "in", "laborum", "non" ], "friends": [ { "id": 0, "name": "Hinton Santiago" }, { "id": 1, "name": "Talley Dyer" }, { "id": 2, "name": "Karen Logan" } ], "greeting": "Hello, Griffin Mclaughlin! You have 3 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a9010e5c5ac55919561", "index": 5, "guid": "7e6fca4d-0329-47ab-b3e7-f4d6a6ee4dd2", "isActive": true, "balance": "$3,767.46", "picture": "http://placehold.it/32x32", "age": 36, "eyeColor": "brown", "name": "Rachel Mcclure", "gender": "female", "company": "ESCENTA", "email": "rachelmcclure@escenta.com", "phone": "+1 (857) 518-3454", "address": "901 Harwood Place, Rossmore, Tennessee, 3213", "about": "Nisi enim deserunt ut ex mollit fugiat. Magna nostrud culpa irure nulla mollit nisi. Sit ea incididunt amet culpa veniam voluptate Lorem sunt dolore amet. Exercitation tempor eiusmod exercitation officia dolor. Ut ea sint veniam cupidatat et. Sunt nostrud ad ipsum non elit elit esse ut dolor. Et officia et minim ipsum amet sint eu ut nostrud adipisicing cillum ullamco.\r\n", "registered": "2014-05-29T20:42:11 +07:00", "latitude": 8.132878, "longitude": -99.198755, "tags": [ "est", "Lorem", "ullamco", "nisi", "reprehenderit", "nisi", "cupidatat" ], "friends": [ { "id": 0, "name": "Michael Martin" }, { "id": 1, "name": "Gayle Heath" }, { "id": 2, "name": "Slater Bender" } ], "greeting": "Hello, Rachel Mcclure! You have 2 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90a76a5ba627b180c9", "index": 6, "guid": "fbf59485-142c-4eb6-a98e-8952cbb19942", "isActive": true, "balance": "$2,139.12", "picture": "http://placehold.it/32x32", "age": 28, "eyeColor": "blue", "name": "Megan Morrow", "gender": "female", "company": "PETICULAR", "email": "meganmorrow@peticular.com", "phone": "+1 (825) 572-2854", "address": "151 Jardine Place, Boonville, Idaho, 160", "about": "Magna reprehenderit aliqua quis eiusmod eu minim ut. Consectetur non veniam est et aliqua mollit. Aliqua eiusmod sit fugiat qui quis nisi mollit officia do. Enim quis quis occaecat ullamco anim reprehenderit exercitation. Ad id id laborum ipsum ipsum cillum ipsum occaecat irure. Commodo voluptate ullamco excepteur ea laboris adipisicing veniam cillum commodo velit anim. Occaecat magna laborum non ex anim consequat dolor cillum excepteur velit duis commodo officia veniam.\r\n", "registered": "2014-04-16T08:56:52 +07:00", "latitude": 57.771446, "longitude": -146.885322, "tags": [ "veniam", "officia", "magna", "ipsum", "nulla", "ea", "mollit" ], "friends": [ { "id": 0, "name": "Marina Wise" }, { "id": 1, "name": "Ann Mercado" }, { "id": 2, "name": "Glenn Duran" } ], "greeting": "Hello, Megan Morrow! You have 7 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90776f7328f4df750f", "index": 7, "guid": "ef99cc91-061c-49c5-9901-3ac22a75bc92", "isActive": true, "balance": "$3,161.69", "picture": "http://placehold.it/32x32", "age": 37, "eyeColor": "blue", "name": "Lawson Kirby", "gender": "male", "company": "PLASMOSIS", "email": "lawsonkirby@plasmosis.com", "phone": "+1 (853) 583-2577", "address": "122 Linden Boulevard, Edneyville, Palau, 6050", "about": "Elit ullamco reprehenderit eiusmod in duis minim exercitation incididunt reprehenderit eiusmod nulla. Cupidatat ea anim incididunt esse ea eu esse laboris velit. Culpa sunt exercitation officia amet voluptate enim duis ipsum ex anim quis nisi. Dolor officia irure do veniam do amet ullamco eu.\r\n", "registered": "2014-08-13T02:14:13 +07:00", "latitude": -16.166232, "longitude": 12.254111, "tags": [ "et", "aliqua", "aute", "voluptate", "officia", "est", "quis" ], "friends": [ { "id": 0, "name": "Marquita Hutchinson" }, { "id": 1, "name": "Karla Conner" }, { "id": 2, "name": "Mattie Page" } ], "greeting": "Hello, Lawson Kirby! You have 3 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90b8e9fff0ed297a59", "index": 8, "guid": "9bb8d813-704c-4714-929f-1321576a2701", "isActive": false, "balance": "$1,275.37", "picture": "http://placehold.it/32x32", "age": 23, "eyeColor": "brown", "name": "Pat Medina", "gender": "female", "company": "PLEXIA", "email": "patmedina@plexia.com", "phone": "+1 (933) 557-3028", "address": "623 Sunnyside Court, Edinburg, Minnesota, 2620", "about": "Est aliqua sint adipisicing labore magna sunt laboris non eu. Aute deserunt commodo Lorem amet sunt amet qui qui incididunt anim Lorem culpa. Ea exercitation officia dolor aute incididunt ea enim. Nulla aliqua ut ullamco sunt velit cillum esse minim incididunt ut mollit aute. Fugiat eiusmod anim laborum duis aliquip aute reprehenderit qui dolor officia amet labore id. Enim officia reprehenderit incididunt sit. Nisi ullamco nisi adipisicing esse eiusmod dolore veniam cupidatat consequat sunt.\r\n", "registered": "2014-10-22T20:29:14 +07:00", "latitude": -9.032987, "longitude": 71.98971, "tags": [ "laborum", "dolore", "aliqua", "tempor", "eu", "elit", "voluptate" ], "friends": [ { "id": 0, "name": "Elnora Moses" }, { "id": 1, "name": "Alexandra Carter" }, { "id": 2, "name": "Beth Pacheco" } ], "greeting": "Hello, Pat Medina! You have 5 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a908c17a619571cfd39", "index": 9, "guid": "0a5de094-eadc-4120-8941-964f27fbc898", "isActive": true, "balance": "$1,939.34", "picture": "http://placehold.it/32x32", "age": 35, "eyeColor": "brown", "name": "Gibbs Butler", "gender": "male", "company": "OPTIQUE", "email": "gibbsbutler@optique.com", "phone": "+1 (956) 574-3434", "address": "552 Columbia Street, Richmond, Illinois, 903", "about": "Laboris eu ut magna exercitation non laboris sint. Mollit velit est exercitation enim exercitation reprehenderit culpa eiusmod laboris fugiat veniam adipisicing. Voluptate enim id do eu officia duis in incididunt. Esse do laboris pariatur cupidatat elit.\r\n", "registered": "2014-02-24T15:46:23 +08:00", "latitude": -68.874573, "longitude": -6.876165, "tags": [ "excepteur", "deserunt", "ea", "labore", "aliqua", "deserunt", "labore" ], "friends": [ { "id": 0, "name": "Chen Langley" }, { "id": 1, "name": "Latonya Vaughan" }, { "id": 2, "name": "Simone Sutton" } ], "greeting": "Hello, Gibbs Butler! You have 2 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a9049447027a378812c", "index": 10, "guid": "406ae437-820d-4e0f-b8dc-1da0ddcc561c", "isActive": false, "balance": "$1,348.37", "picture": "http://placehold.it/32x32", "age": 39, "eyeColor": "brown", "name": "Bond Peck", "gender": "male", "company": "DANCERITY", "email": "bondpeck@dancerity.com", "phone": "+1 (918) 554-2856", "address": "361 Cortelyou Road, Hollins, Missouri, 131", "about": "Nisi ut ea ut deserunt. Consequat pariatur dolor consequat sunt. Ullamco aute proident excepteur fugiat id consequat eu nisi occaecat.\r\n", "registered": "2014-05-15T02:12:14 +07:00", "latitude": -79.266187, "longitude": 92.89454, "tags": [ "ex", "est", "sit", "irure", "qui", "veniam", "exercitation" ], "friends": [ { "id": 0, "name": "Nettie Pope" }, { "id": 1, "name": "Alyssa Hensley" }, { "id": 2, "name": "Puckett Kinney" } ], "greeting": "Hello, Bond Peck! You have 7 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a9062a82eff9506c4d7", "index": 11, "guid": "b7400b79-2b71-46cd-9260-13e0767b437e", "isActive": true, "balance": "$1,757.66", "picture": "http://placehold.it/32x32", "age": 20, "eyeColor": "blue", "name": "Garrison Warner", "gender": "male", "company": "NAMEBOX", "email": "garrisonwarner@namebox.com", "phone": "+1 (874) 417-2183", "address": "927 Knapp Street, Shaft, Connecticut, 2188", "about": "Sint commodo ipsum commodo id magna labore in. Pariatur nostrud reprehenderit adipisicing amet enim ut quis laboris culpa exercitation deserunt cillum. Adipisicing excepteur sunt do labore anim exercitation non excepteur. Minim consectetur sit dolore occaecat et aliquip aliquip excepteur aliquip ut do eiusmod ea nulla. Nostrud sunt dolore ea sunt est enim occaecat culpa minim. Sit elit mollit mollit aliquip eu ex. Tempor nulla voluptate dolore ex.\r\n", "registered": "2014-06-18T03:58:19 +07:00", "latitude": -87.629414, "longitude": 96.653639, "tags": [ "eu", "deserunt", "dolore", "nisi", "culpa", "ullamco", "ipsum" ], "friends": [ { "id": 0, "name": "Gutierrez Sears" }, { "id": 1, "name": "Holly Jacobson" }, { "id": 2, "name": "Henry Delgado" } ], "greeting": "Hello, Garrison Warner! You have 4 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a904638f48ca7f9e85e", "index": 12, "guid": "4cd59615-46b7-4733-a439-dc59c0ca0118", "isActive": true, "balance": "$3,897.06", "picture": "http://placehold.it/32x32", "age": 24, "eyeColor": "blue", "name": "Consuelo Bray", "gender": "female", "company": "COMTEST", "email": "consuelobray@comtest.com", "phone": "+1 (945) 432-2620", "address": "433 Clinton Street, Clarktown, Maine, 6916", "about": "Do occaecat consectetur tempor Lorem ullamco commodo exercitation veniam reprehenderit nulla officia. Nisi irure sunt cupidatat amet et excepteur quis et do. Et commodo nulla occaecat do sint quis mollit reprehenderit do laboris magna. Dolore ea sit aute esse consequat fugiat Lorem occaecat adipisicing adipisicing qui aute elit. Amet veniam anim ipsum aute officia. Fugiat nisi magna anim pariatur minim magna exercitation duis officia.\r\n", "registered": "2014-03-19T07:39:44 +07:00", "latitude": 7.760448, "longitude": -92.399314, "tags": [ "irure", "veniam", "ex", "ullamco", "anim", "do", "enim" ], "friends": [ { "id": 0, "name": "Ellen Bullock" }, { "id": 1, "name": "Davis Vaughn" }, { "id": 2, "name": "Robert Mendoza" } ], "greeting": "Hello, Consuelo Bray! You have 8 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90fd85a45d33d54cf7", "index": 13, "guid": "53868eb7-df5c-445d-ad62-6124db081b6c", "isActive": false, "balance": "$2,988.04", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "green", "name": "Clark Skinner", "gender": "male", "company": "OVOLO", "email": "clarkskinner@ovolo.com", "phone": "+1 (834) 587-2391", "address": "967 Dewey Place, Gibsonia, Puerto Rico, 6398", "about": "Duis irure exercitation ullamco amet aliquip minim sit consequat officia laborum id ad. Lorem duis velit consequat non irure nulla elit elit velit dolor ullamco qui fugiat. Quis ad velit ea consectetur veniam Lorem incididunt quis magna eiusmod. Et nostrud irure tempor nostrud esse.\r\n", "registered": "2014-10-11T06:48:59 +07:00", "latitude": -62.633073, "longitude": -121.03338, "tags": [ "ut", "deserunt", "adipisicing", "enim", "amet", "proident", "officia" ], "friends": [ { "id": 0, "name": "Francine Petersen" }, { "id": 1, "name": "Lena Robles" }, { "id": 2, "name": "Mcintyre Gardner" } ], "greeting": "Hello, Clark Skinner! You have 6 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a908789850c55818269", "index": 14, "guid": "84cc7d0b-0544-40f8-900a-825429b0ee87", "isActive": true, "balance": "$3,012.07", "picture": "http://placehold.it/32x32", "age": 32, "eyeColor": "blue", "name": "Katie Allen", "gender": "female", "company": "SYBIXTEX", "email": "katieallen@sybixtex.com", "phone": "+1 (959) 504-2563", "address": "543 Heath Place, Bartonsville, New Mexico, 4882", "about": "Nisi ullamco anim in culpa in non nostrud ex aliqua ex. Nisi occaecat exercitation sint ad magna Lorem amet anim pariatur quis. Dolore consequat quis dolor ea. Aliquip sunt ex cillum tempor fugiat laboris ipsum mollit aliqua reprehenderit nulla fugiat exercitation ad.\r\n", "registered": "2014-03-17T05:45:50 +07:00", "latitude": -79.18988, "longitude": -95.023826, "tags": [ "commodo", "incididunt", "voluptate", "sit", "mollit", "veniam", "et" ], "friends": [ { "id": 0, "name": "Hampton Jimenez" }, { "id": 1, "name": "Lara Cline" }, { "id": 2, "name": "Jennings Cantu" } ], "greeting": "Hello, Katie Allen! You have 3 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90787015f61850162f", "index": 15, "guid": "d848ac32-1d24-471a-ad7e-d272f52cb5fc", "isActive": true, "balance": "$1,416.33", "picture": "http://placehold.it/32x32", "age": 38, "eyeColor": "brown", "name": "Pratt Watson", "gender": "male", "company": "HARMONEY", "email": "prattwatson@harmoney.com", "phone": "+1 (905) 557-3197", "address": "867 Campus Road, Lindisfarne, Northern Mariana Islands, 8349", "about": "Nisi mollit eu reprehenderit qui ut eu cillum cupidatat do. Et ex qui minim proident. Quis aliquip aliquip exercitation exercitation dolor aute nostrud fugiat ea. Id ullamco occaecat reprehenderit mollit occaecat ea ipsum cupidatat ea consequat fugiat.\r\n", "registered": "2014-11-15T05:07:03 +08:00", "latitude": -66.117872, "longitude": 52.197654, "tags": [ "ullamco", "sunt", "ea", "veniam", "elit", "sint", "id" ], "friends": [ { "id": 0, "name": "Dale Ray" }, { "id": 1, "name": "Beryl Hayes" }, { "id": 2, "name": "Millie Good" } ], "greeting": "Hello, Pratt Watson! You have 2 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90c4106283f0c1eed9", "index": 16, "guid": "6839b0af-5c69-45e2-b83b-381ff05034e6", "isActive": false, "balance": "$2,720.67", "picture": "http://placehold.it/32x32", "age": 31, "eyeColor": "blue", "name": "Shari Mendez", "gender": "female", "company": "INDEXIA", "email": "sharimendez@indexia.com", "phone": "+1 (895) 589-3754", "address": "533 Conduit Boulevard, Forestburg, Mississippi, 6873", "about": "Ex excepteur elit id laborum veniam dolore duis ea eiusmod minim. Consequat reprehenderit magna elit tempor voluptate esse officia minim reprehenderit consequat fugiat qui eiusmod. Et Lorem nisi voluptate tempor nulla cillum reprehenderit pariatur elit dolore occaecat laboris sunt. Anim cupidatat do veniam pariatur nostrud anim eu aliqua veniam ad cillum quis.\r\n", "registered": "2014-05-04T10:15:37 +07:00", "latitude": 31.931465, "longitude": 155.732674, "tags": [ "enim", "sint", "est", "aliqua", "elit", "laboris", "occaecat" ], "friends": [ { "id": 0, "name": "Desiree Norris" }, { "id": 1, "name": "Abigail Crosby" }, { "id": 2, "name": "Anderson Alston" } ], "greeting": "Hello, Shari Mendez! You have 6 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90474ecbf0a9c34382", "index": 17, "guid": "079bb238-0556-4ede-8243-2eaadabb3050", "isActive": false, "balance": "$2,629.01", "picture": "http://placehold.it/32x32", "age": 26, "eyeColor": "green", "name": "Hancock Rowland", "gender": "male", "company": "SOFTMICRO", "email": "hancockrowland@softmicro.com", "phone": "+1 (983) 565-2302", "address": "168 Dooley Street, Driftwood, North Dakota, 3607", "about": "Eu voluptate velit incididunt ipsum amet veniam. Lorem aliquip adipisicing incididunt laborum aliqua elit consectetur aute velit voluptate ea. Mollit irure duis consequat veniam sint nostrud est dolore sunt anim laboris fugiat. Dolor officia elit esse elit dolore. Minim non est duis culpa ullamco veniam excepteur. Veniam ullamco amet ullamco esse voluptate laboris velit.\r\n", "registered": "2014-09-06T04:32:40 +07:00", "latitude": -68.853851, "longitude": 135.592762, "tags": [ "nulla", "ut", "magna", "adipisicing", "officia", "nulla", "cillum" ], "friends": [ { "id": 0, "name": "Shannon Burch" }, { "id": 1, "name": "Marisol Nixon" }, { "id": 2, "name": "Poole Wolfe" } ], "greeting": "Hello, Hancock Rowland! You have 4 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90cf708eccc9032fd0", "index": 18, "guid": "8930775e-9271-400e-b662-77ee520b3369", "isActive": false, "balance": "$1,026.68", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "blue", "name": "Luna Rice", "gender": "male", "company": "GEEKULAR", "email": "lunarice@geekular.com", "phone": "+1 (840) 541-2996", "address": "417 Varick Avenue, Martell, Vermont, 2749", "about": "Aliqua enim ullamco do eiusmod. Ipsum incididunt minim esse veniam nisi velit. Ipsum reprehenderit velit eiusmod nisi magna dolore consectetur reprehenderit magna culpa. Commodo excepteur labore proident adipisicing in velit sit occaecat reprehenderit id.\r\n", "registered": "2014-10-15T05:13:55 +07:00", "latitude": -57.335675, "longitude": -173.387514, "tags": [ "fugiat", "enim", "exercitation", "aliquip", "Lorem", "laboris", "deserunt" ], "friends": [ { "id": 0, "name": "Mclaughlin Schmidt" }, { "id": 1, "name": "Munoz Key" }, { "id": 2, "name": "Candace Stephenson" } ], "greeting": "Hello, Luna Rice! You have 2 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90a0fd17c9e4f5d33f", "index": 19, "guid": "570f0e20-085f-4c40-9e84-b555cc4e79c8", "isActive": true, "balance": "$3,333.73", "picture": "http://placehold.it/32x32", "age": 39, "eyeColor": "green", "name": "Beverly Newton", "gender": "female", "company": "ECLIPSENT", "email": "beverlynewton@eclipsent.com", "phone": "+1 (902) 595-3072", "address": "903 Knight Court, Gardiner, Rhode Island, 3327", "about": "Labore culpa tempor nisi commodo dolore exercitation est eu. Aute exercitation duis proident deserunt culpa ullamco. Irure cillum elit ea sint dolore ipsum adipisicing anim sit. Amet incididunt labore ex fugiat mollit quis reprehenderit nisi ut excepteur proident ullamco laboris. Reprehenderit voluptate aliqua labore culpa in non magna velit nostrud amet. Minim nulla ea culpa irure. Minim ea ex nisi proident ex ex quis ipsum culpa.\r\n", "registered": "2014-09-23T10:25:17 +07:00", "latitude": 23.973865, "longitude": -71.604537, "tags": [ "ullamco", "anim", "id", "pariatur", "est", "cupidatat", "qui" ], "friends": [ { "id": 0, "name": "James Garner" }, { "id": 1, "name": "Goff Reese" }, { "id": 2, "name": "Casey Bradford" } ], "greeting": "Hello, Beverly Newton! You have 2 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90fd0cafc2fa513aea", "index": 20, "guid": "c0e243a3-bf20-4112-8dab-0b0aed785060", "isActive": true, "balance": "$2,290.97", "picture": "http://placehold.it/32x32", "age": 28, "eyeColor": "blue", "name": "Stokes Dodson", "gender": "male", "company": "SLAMBDA", "email": "stokesdodson@slambda.com", "phone": "+1 (994) 443-2829", "address": "232 Kosciusko Street, Manitou, Michigan, 2638", "about": "Nostrud minim cillum elit reprehenderit ut do eu. Quis deserunt enim nisi do proident quis quis voluptate elit. Sit nostrud et amet nostrud pariatur exercitation cillum ullamco laborum ullamco do id. Tempor incididunt dolore consequat ut amet in reprehenderit magna anim laboris reprehenderit tempor adipisicing.\r\n", "registered": "2014-05-21T16:30:03 +07:00", "latitude": -86.112825, "longitude": 56.089279, "tags": [ "ea", "dolor", "dolor", "consequat", "nulla", "cillum", "voluptate" ], "friends": [ { "id": 0, "name": "Jodi Camacho" }, { "id": 1, "name": "Michele Miles" }, { "id": 2, "name": "Rene Mitchell" } ], "greeting": "Hello, Stokes Dodson! You have 9 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a908be67242a33d9597", "index": 21, "guid": "8ad92a47-ac1d-46ad-9dc3-d1f96526bf1d", "isActive": true, "balance": "$1,134.78", "picture": "http://placehold.it/32x32", "age": 20, "eyeColor": "green", "name": "Jody Stewart", "gender": "female", "company": "EARGO", "email": "jodystewart@eargo.com", "phone": "+1 (925) 470-3426", "address": "271 Norwood Avenue, Sperryville, Oklahoma, 9504", "about": "Ut cillum ea pariatur Lorem ad veniam ex ullamco. Exercitation culpa sit occaecat aliquip eu quis magna exercitation quis reprehenderit nostrud consequat. Exercitation magna duis culpa nulla id proident. Adipisicing sunt consequat laborum consequat id dolore aute qui. Consectetur magna irure minim ut consectetur elit qui elit voluptate sint excepteur officia.\r\n", "registered": "2014-04-29T09:04:08 +07:00", "latitude": -51.736959, "longitude": -37.406481, "tags": [ "officia", "ullamco", "velit", "nulla", "ipsum", "eiusmod", "mollit" ], "friends": [ { "id": 0, "name": "Jodie Browning" }, { "id": 1, "name": "Collins Gamble" }, { "id": 2, "name": "Emerson Mccullough" } ], "greeting": "Hello, Jody Stewart! You have 4 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a905956037e359d6786", "index": 22, "guid": "730467a3-9f5d-4d41-9503-09f30222dffa", "isActive": false, "balance": "$1,821.23", "picture": "http://placehold.it/32x32", "age": 24, "eyeColor": "brown", "name": "Wall Moss", "gender": "male", "company": "BOILICON", "email": "wallmoss@boilicon.com", "phone": "+1 (865) 518-2689", "address": "902 Fleet Street, Cornfields, West Virginia, 9088", "about": "Consectetur voluptate enim est elit dolor adipisicing reprehenderit ut in proident sunt. Fugiat cillum anim ullamco qui laborum sit. Dolore qui mollit ut irure proident consequat est veniam. Qui incididunt quis duis enim quis cupidatat do nostrud dolore labore consectetur laboris consectetur. Adipisicing veniam amet officia mollit incididunt non veniam ea laboris. Enim adipisicing velit in dolore proident Lorem esse et sunt.\r\n", "registered": "2014-01-21T18:36:59 +08:00", "latitude": -70.265889, "longitude": -148.213176, "tags": [ "ea", "cillum", "ea", "enim", "aliqua", "nostrud", "do" ], "friends": [ { "id": 0, "name": "Margaret Chavez" }, { "id": 1, "name": "Mendez Garrison" }, { "id": 2, "name": "Howard Ortiz" } ], "greeting": "Hello, Wall Moss! You have 9 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9062feb6c7bfa8710d", "index": 23, "guid": "1b428a55-1b50-4bcf-b2d9-06c2e8950768", "isActive": true, "balance": "$1,045.36", "picture": "http://placehold.it/32x32", "age": 25, "eyeColor": "blue", "name": "Adele Santana", "gender": "female", "company": "EBIDCO", "email": "adelesantana@ebidco.com", "phone": "+1 (981) 528-2138", "address": "117 Kent Avenue, Chamizal, Iowa, 4289", "about": "Culpa eu nostrud mollit voluptate consequat pariatur. Qui ex laboris velit cupidatat enim. Reprehenderit commodo eu excepteur ex elit amet dolore enim. Nisi dolor pariatur enim laborum voluptate Lorem magna ipsum enim aute do sunt. Ad consectetur velit laborum magna labore Lorem occaecat quis. Exercitation ipsum velit nostrud cupidatat consequat ex non velit deserunt pariatur officia. Magna occaecat Lorem qui aliqua id aliquip laborum.\r\n", "registered": "2014-10-01T21:15:54 +07:00", "latitude": 24.339451, "longitude": -38.920718, "tags": [ "ullamco", "labore", "magna", "fugiat", "consectetur", "nostrud", "veniam" ], "friends": [ { "id": 0, "name": "Sharpe Haley" }, { "id": 1, "name": "Patrice Horne" }, { "id": 2, "name": "Melanie Sosa" } ], "greeting": "Hello, Adele Santana! You have 10 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a900e0eec7c0c194713", "index": 24, "guid": "cc7114a5-89ce-4fb6-9ad8-b5886360ab42", "isActive": true, "balance": "$2,505.31", "picture": "http://placehold.it/32x32", "age": 36, "eyeColor": "blue", "name": "Lindsey Colon", "gender": "male", "company": "XYLAR", "email": "lindseycolon@xylar.com", "phone": "+1 (952) 532-3896", "address": "144 Poly Place, Detroit, Federated States Of Micronesia, 2004", "about": "Ullamco nostrud Lorem duis duis aute sunt commodo Lorem. Esse cupidatat aliqua et laborum officia et. Ea magna est eiusmod id sit ea esse consectetur qui.\r\n", "registered": "2014-04-05T02:52:07 +07:00", "latitude": -55.350071, "longitude": -20.446672, "tags": [ "id", "sit", "cillum", "id", "exercitation", "reprehenderit", "deserunt" ], "friends": [ { "id": 0, "name": "Kathleen Berger" }, { "id": 1, "name": "Morales Tran" }, { "id": 2, "name": "Dionne Hunter" } ], "greeting": "Hello, Lindsey Colon! You have 3 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90a20ec5bce57f2f55", "index": 25, "guid": "c1d3f95b-25dd-4b48-8fe8-9af5f62895e2", "isActive": true, "balance": "$1,609.28", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "green", "name": "Langley Moore", "gender": "male", "company": "ZYTRAX", "email": "langleymoore@zytrax.com", "phone": "+1 (912) 580-3688", "address": "747 Abbey Court, Odessa, Kentucky, 4688", "about": "Eiusmod adipisicing aliquip quis voluptate qui. Enim esse culpa elit id eu dolor culpa eiusmod. Deserunt ut ea ipsum ipsum non culpa ullamco non ipsum sunt cupidatat.\r\n", "registered": "2014-06-28T08:29:15 +07:00", "latitude": 65.464748, "longitude": -129.638837, "tags": [ "deserunt", "cillum", "sint", "proident", "ad", "adipisicing", "mollit" ], "friends": [ { "id": 0, "name": "Mcguire Vance" }, { "id": 1, "name": "Norma Buck" }, { "id": 2, "name": "Janelle Bailey" } ], "greeting": "Hello, Langley Moore! You have 8 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a903c9a63ef7fccce96", "index": 26, "guid": "88c32c0f-a2c6-49c2-8261-bc323895067f", "isActive": false, "balance": "$3,748.41", "picture": "http://placehold.it/32x32", "age": 26, "eyeColor": "blue", "name": "Duran Bryan", "gender": "male", "company": "BULLZONE", "email": "duranbryan@bullzone.com", "phone": "+1 (911) 598-2827", "address": "903 Village Road, Cressey, New Jersey, 9174", "about": "Do in fugiat est deserunt in sit Lorem quis reprehenderit est ut tempor. Ullamco in veniam non quis cillum consectetur id. Elit exercitation reprehenderit et amet voluptate magna voluptate minim veniam enim exercitation aute aute esse. Exercitation magna voluptate laborum ipsum cupidatat exercitation ad eu aute deserunt et. Voluptate qui aute ut elit amet excepteur nostrud officia irure do.\r\n", "registered": "2014-01-29T12:32:05 +08:00", "latitude": -51.269785, "longitude": 79.015891, "tags": [ "consequat", "id", "exercitation", "incididunt", "adipisicing", "laboris", "laboris" ], "friends": [ { "id": 0, "name": "Jenny Allison" }, { "id": 1, "name": "Della Hobbs" }, { "id": 2, "name": "Bradshaw Owens" } ], "greeting": "Hello, Duran Bryan! You have 5 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a907a2f07fbb3efec0f", "index": 27, "guid": "df997a84-5ec1-4f63-acb7-140b9fed981d", "isActive": true, "balance": "$1,249.61", "picture": "http://placehold.it/32x32", "age": 28, "eyeColor": "blue", "name": "Juarez House", "gender": "male", "company": "ZUVY", "email": "juarezhouse@zuvy.com", "phone": "+1 (841) 533-3140", "address": "494 Atlantic Avenue, Shasta, Nevada, 8475", "about": "Proident eu nostrud laboris adipisicing pariatur sint ipsum exercitation velit non incididunt. Qui cupidatat reprehenderit nostrud magna sunt aute nulla aliquip velit culpa commodo fugiat laborum. Dolore consectetur esse labore magna anim exercitation dolor velit qui sunt Lorem reprehenderit amet.\r\n", "registered": "2014-03-16T19:21:13 +07:00", "latitude": 57.96486, "longitude": 130.460435, "tags": [ "incididunt", "reprehenderit", "consequat", "duis", "veniam", "nulla", "dolor" ], "friends": [ { "id": 0, "name": "Keri Lara" }, { "id": 1, "name": "Celina Pace" }, { "id": 2, "name": "Bush Haynes" } ], "greeting": "Hello, Juarez House! You have 7 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a903021f42c063be598", "index": 28, "guid": "1dc6349d-4354-42a9-9f73-7bc12d5ac9c2", "isActive": false, "balance": "$1,991.33", "picture": "http://placehold.it/32x32", "age": 26, "eyeColor": "blue", "name": "Sonja Horton", "gender": "female", "company": "VIDTO", "email": "sonjahorton@vidto.com", "phone": "+1 (990) 504-2432", "address": "612 River Street, Carrizo, California, 5778", "about": "Nisi reprehenderit occaecat anim ut minim aliqua aliquip velit veniam eiusmod reprehenderit laboris ad. Duis aliqua labore cillum proident est amet. Adipisicing nostrud proident labore laborum. Elit est sint ex veniam reprehenderit. Veniam ut dolor nulla tempor voluptate sit excepteur sit ut quis.\r\n", "registered": "2014-10-30T05:07:28 +07:00", "latitude": 85.37031, "longitude": -122.082636, "tags": [ "tempor", "ex", "nostrud", "ullamco", "ullamco", "nisi", "cillum" ], "friends": [ { "id": 0, "name": "Phillips Henry" }, { "id": 1, "name": "Leanne Sexton" }, { "id": 2, "name": "Alisha Chang" } ], "greeting": "Hello, Sonja Horton! You have 1 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a903a33ff6bb03e049a", "index": 29, "guid": "4ef3a65d-5407-400b-aace-62bbb8a83c6a", "isActive": true, "balance": "$2,823.03", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "blue", "name": "Lidia Hewitt", "gender": "female", "company": "PROWASTE", "email": "lidiahewitt@prowaste.com", "phone": "+1 (909) 562-3312", "address": "625 Ralph Avenue, Kiskimere, Maryland, 2033", "about": "Eu adipisicing eiusmod laboris veniam sunt id ad eiusmod consectetur nisi. Esse nulla ipsum Lorem nisi consequat laborum. Veniam ea exercitation ullamco pariatur consectetur. Cupidatat velit excepteur ex eu sunt id. In velit reprehenderit pariatur velit. Voluptate nostrud deserunt qui mollit et tempor nostrud eiusmod adipisicing ad est laborum. Fugiat nisi sit nulla eu ad.\r\n", "registered": "2014-01-15T00:05:42 +08:00", "latitude": -50.566931, "longitude": -149.036259, "tags": [ "in", "ipsum", "tempor", "magna", "aliqua", "duis", "incididunt" ], "friends": [ { "id": 0, "name": "Allie Baker" }, { "id": 1, "name": "Valdez Giles" }, { "id": 2, "name": "Knox Vargas" } ], "greeting": "Hello, Lidia Hewitt! You have 3 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90ce7ef56e53f98790", "index": 30, "guid": "9ae34b38-098b-4de6-aa0f-90359571ddf2", "isActive": false, "balance": "$3,152.82", "picture": "http://placehold.it/32x32", "age": 38, "eyeColor": "brown", "name": "Nieves Ewing", "gender": "male", "company": "QNEKT", "email": "nievesewing@qnekt.com", "phone": "+1 (888) 460-2384", "address": "425 Highland Place, Hampstead, Washington, 7019", "about": "Ipsum aliquip ullamco labore aliquip et. Eu pariatur exercitation ex fugiat fugiat. Nulla voluptate et cupidatat deserunt mollit et incididunt. Deserunt anim qui cupidatat veniam et et dolore qui sunt tempor ipsum. In et voluptate excepteur incididunt dolore cupidatat exercitation ullamco dolore Lorem nostrud sunt nostrud. Occaecat amet ut laborum laborum aliqua est incididunt ea excepteur commodo. Ipsum et elit nisi duis pariatur occaecat.\r\n", "registered": "2014-06-15T18:44:29 +07:00", "latitude": 8.010315, "longitude": 69.049129, "tags": [ "exercitation", "eiusmod", "voluptate", "ullamco", "consectetur", "reprehenderit", "enim" ], "friends": [ { "id": 0, "name": "Maggie Rodriguez" }, { "id": 1, "name": "Evans Roach" }, { "id": 2, "name": "Greer Mccoy" } ], "greeting": "Hello, Nieves Ewing! You have 7 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a9049aa4bbedefd311d", "index": 31, "guid": "471d52a6-da38-4015-8d7a-6fe215a032d3", "isActive": false, "balance": "$1,456.93", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "green", "name": "Reyna Clay", "gender": "female", "company": "KINETICA", "email": "reynaclay@kinetica.com", "phone": "+1 (865) 425-3747", "address": "480 Dakota Place, Kimmell, Utah, 6677", "about": "Tempor esse ex amet aliqua incididunt incididunt qui commodo laborum incididunt deserunt elit id consequat. Proident duis ut ullamco non ea magna fugiat fugiat Lorem minim. Incididunt tempor nostrud proident irure laboris consectetur elit labore adipisicing fugiat nulla quis ipsum consequat. Tempor mollit pariatur irure in nisi minim magna excepteur. Aliquip et laborum cillum adipisicing consequat.\r\n", "registered": "2014-10-30T08:53:04 +07:00", "latitude": 38.437675, "longitude": 42.847793, "tags": [ "incididunt", "est", "mollit", "nulla", "ipsum", "ea", "ea" ], "friends": [ { "id": 0, "name": "Glenna Macdonald" }, { "id": 1, "name": "Bertha Meadows" }, { "id": 2, "name": "Oneill Barnes" } ], "greeting": "Hello, Reyna Clay! You have 6 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a900238319b9b407aa0", "index": 32, "guid": "fa5c52e1-9a9d-44d4-8e6b-5a65221ab142", "isActive": true, "balance": "$3,113.15", "picture": "http://placehold.it/32x32", "age": 24, "eyeColor": "blue", "name": "Felicia Harris", "gender": "female", "company": "FITCORE", "email": "feliciaharris@fitcore.com", "phone": "+1 (814) 449-2730", "address": "641 Hazel Court, Bawcomville, Wisconsin, 4111", "about": "Magna in elit aute ipsum anim dolore et exercitation sunt occaecat velit. Sint tempor nulla sit laborum dolor ex irure nisi nulla veniam in labore laborum. Nulla magna excepteur exercitation aute occaecat consequat laborum Lorem velit occaecat aliqua qui. Id in aliqua dolore fugiat duis elit laborum commodo cillum ex aute minim eu.\r\n", "registered": "2014-04-15T21:31:39 +07:00", "latitude": -58.891583, "longitude": -162.554134, "tags": [ "eiusmod", "dolor", "enim", "cupidatat", "labore", "sunt", "consectetur" ], "friends": [ { "id": 0, "name": "Rich Lott" }, { "id": 1, "name": "Rebecca Cardenas" }, { "id": 2, "name": "Jarvis Barron" } ], "greeting": "Hello, Felicia Harris! You have 7 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90f03941c94fe50d08", "index": 33, "guid": "49070cf3-b2f3-445e-86ec-3ae9cddc474d", "isActive": false, "balance": "$1,105.05", "picture": "http://placehold.it/32x32", "age": 35, "eyeColor": "green", "name": "Josefina Holland", "gender": "female", "company": "GOGOL", "email": "josefinaholland@gogol.com", "phone": "+1 (809) 411-2991", "address": "778 McKibben Street, Whitehaven, Louisiana, 2079", "about": "Cillum ipsum cupidatat et dolor minim aliqua. Laborum culpa magna ullamco nulla ut labore deserunt amet sunt est esse do. Consequat aliquip eiusmod ipsum tempor. Voluptate exercitation nisi nulla dolor esse ullamco occaecat. Sint minim reprehenderit anim tempor deserunt sit exercitation. Qui proident cillum eu voluptate adipisicing velit tempor sunt sunt ipsum. Enim anim ea ea eu excepteur excepteur laboris eu.\r\n", "registered": "2014-09-13T12:46:51 +07:00", "latitude": 81.172596, "longitude": -151.851605, "tags": [ "velit", "ad", "tempor", "tempor", "adipisicing", "nulla", "minim" ], "friends": [ { "id": 0, "name": "Lester Woods" }, { "id": 1, "name": "Audra Shepherd" }, { "id": 2, "name": "Chandler Church" } ], "greeting": "Hello, Josefina Holland! You have 5 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9008a3955509cf065f", "index": 34, "guid": "4c838bee-e8b1-4c22-b8ad-e0e5d0822334", "isActive": false, "balance": "$3,032.13", "picture": "http://placehold.it/32x32", "age": 32, "eyeColor": "green", "name": "Susie Cash", "gender": "female", "company": "DOGSPA", "email": "susiecash@dogspa.com", "phone": "+1 (991) 447-2298", "address": "361 Quincy Street, Duryea, Florida, 7538", "about": "Officia eu non proident ad ea quis eu ea amet irure aliqua qui. Ea in laborum do sit. Dolor proident voluptate excepteur sit. Tempor nulla anim ex proident ipsum laboris laboris cupidatat esse dolore ex fugiat proident. Excepteur exercitation pariatur ex velit. In adipisicing eu eiusmod elit dolore ullamco nulla sit ut ut anim aliquip. Et eu eu aliquip ex aute aliquip veniam sint pariatur non incididunt in aliqua sit.\r\n", "registered": "2014-09-14T22:55:19 +07:00", "latitude": 8.46119, "longitude": -1.171475, "tags": [ "voluptate", "irure", "ex", "proident", "nulla", "in", "esse" ], "friends": [ { "id": 0, "name": "Cassie Whitley" }, { "id": 1, "name": "Shawna Todd" }, { "id": 2, "name": "Antoinette Brooks" } ], "greeting": "Hello, Susie Cash! You have 1 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9079c5bce30e9c0a68", "index": 35, "guid": "7a70e0df-c23b-435d-8d19-864cc1bd09e6", "isActive": false, "balance": "$2,523.44", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "brown", "name": "Marquez Hartman", "gender": "male", "company": "BUZZMAKER", "email": "marquezhartman@buzzmaker.com", "phone": "+1 (880) 574-2420", "address": "326 Church Avenue, Yardville, Indiana, 6743", "about": "Ullamco reprehenderit pariatur veniam enim est nulla laboris ullamco eiusmod eu Lorem amet in amet. Incididunt consectetur reprehenderit tempor Lorem aute eiusmod laborum sunt mollit excepteur qui ea enim. Consectetur enim excepteur proident incididunt adipisicing duis est amet quis proident laboris. Consectetur Lorem consequat incididunt eiusmod mollit id amet velit quis ipsum labore. Cupidatat id minim cillum qui consequat quis non quis irure dolor voluptate ea eu.\r\n", "registered": "2014-06-16T07:23:30 +07:00", "latitude": -88.970617, "longitude": -28.068887, "tags": [ "nostrud", "adipisicing", "quis", "voluptate", "dolore", "dolore", "reprehenderit" ], "friends": [ { "id": 0, "name": "Florence David" }, { "id": 1, "name": "Lynn Mcleod" }, { "id": 2, "name": "Catherine Abbott" } ], "greeting": "Hello, Marquez Hartman! You have 10 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a902bf5baf83c4fafcd", "index": 36, "guid": "56ac4022-1ed3-4298-9b70-c6060c69b13c", "isActive": false, "balance": "$1,162.32", "picture": "http://placehold.it/32x32", "age": 35, "eyeColor": "green", "name": "Bishop Gibbs", "gender": "male", "company": "MICROLUXE", "email": "bishopgibbs@microluxe.com", "phone": "+1 (808) 584-2587", "address": "801 Exeter Street, Trucksville, New Hampshire, 4871", "about": "Incididunt sit eu sunt cupidatat aute do eu eu culpa. Laborum adipisicing sit anim sit dolor labore commodo minim proident ullamco laboris sit irure. Duis dolore cupidatat ullamco anim reprehenderit aliquip incididunt sunt eu id non proident non.\r\n", "registered": "2014-09-10T02:39:14 +07:00", "latitude": -3.268064, "longitude": 149.311591, "tags": [ "enim", "aute", "commodo", "consectetur", "Lorem", "est", "cillum" ], "friends": [ { "id": 0, "name": "Head Pickett" }, { "id": 1, "name": "Thornton Russo" }, { "id": 2, "name": "Hooper Rivera" } ], "greeting": "Hello, Bishop Gibbs! You have 9 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90a4406555b5bdab8f", "index": 37, "guid": "0f052dd2-283e-441e-86d7-b7f7b47224f1", "isActive": true, "balance": "$3,306.81", "picture": "http://placehold.it/32x32", "age": 34, "eyeColor": "brown", "name": "Carr Strickland", "gender": "male", "company": "EXERTA", "email": "carrstrickland@exerta.com", "phone": "+1 (862) 455-3845", "address": "730 Aberdeen Street, Klondike, Kansas, 4412", "about": "Pariatur velit qui Lorem cillum labore veniam minim. Nisi reprehenderit commodo consectetur commodo velit. Ipsum dolor ea mollit excepteur minim do excepteur. Aliquip cillum quis nostrud cillum duis eu laborum reprehenderit adipisicing adipisicing do exercitation. Laborum Lorem sunt voluptate qui quis officia nisi et elit sint veniam. Lorem velit ad do amet labore veniam consectetur.\r\n", "registered": "2014-01-19T10:53:58 +08:00", "latitude": -45.243563, "longitude": -17.8448, "tags": [ "mollit", "ex", "qui", "fugiat", "consequat", "consectetur", "do" ], "friends": [ { "id": 0, "name": "Rosario Gomez" }, { "id": 1, "name": "Robinson Robinson" }, { "id": 2, "name": "Vicki Moreno" } ], "greeting": "Hello, Carr Strickland! You have 2 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9097f6a585321fe001", "index": 38, "guid": "eee159c2-73ac-44b7-9054-d72295d3178a", "isActive": true, "balance": "$3,336.97", "picture": "http://placehold.it/32x32", "age": 30, "eyeColor": "brown", "name": "Stephens Harper", "gender": "male", "company": "KIDSTOCK", "email": "stephensharper@kidstock.com", "phone": "+1 (989) 464-3887", "address": "315 Hewes Street, Cuylerville, Pennsylvania, 7331", "about": "Et ea Lorem labore consequat laboris. Aliqua irure elit aliqua ad fugiat. Commodo cupidatat incididunt ut nostrud consequat elit ad esse magna nisi nostrud dolore eu. Minim incididunt esse ullamco esse ullamco deserunt reprehenderit commodo ut. Quis sint cupidatat excepteur et laboris incididunt id esse irure nostrud sint nostrud ut pariatur. Pariatur officia aute ullamco laboris nisi elit quis labore Lorem minim ad. Ea esse anim commodo fugiat exercitation voluptate eiusmod aliquip amet enim nulla mollit excepteur nisi.\r\n", "registered": "2014-03-02T06:45:25 +08:00", "latitude": -88.39292, "longitude": -121.170605, "tags": [ "ullamco", "est", "mollit", "id", "commodo", "Lorem", "nostrud" ], "friends": [ { "id": 0, "name": "Castaneda Dillon" }, { "id": 1, "name": "Morin Hodge" }, { "id": 2, "name": "Vincent Lamb" } ], "greeting": "Hello, Stephens Harper! You have 2 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90357d07212fdefd7a", "index": 39, "guid": "160a80a4-8e5d-483a-93ed-0a37ee359f04", "isActive": true, "balance": "$1,588.64", "picture": "http://placehold.it/32x32", "age": 32, "eyeColor": "green", "name": "Espinoza May", "gender": "male", "company": "ZIDOX", "email": "espinozamay@zidox.com", "phone": "+1 (955) 420-2244", "address": "614 Alice Court, Vienna, Delaware, 5018", "about": "Pariatur voluptate culpa enim enim sunt dolor laborum consequat officia est nostrud. Ad pariatur labore reprehenderit cillum dolor consequat quis eu fugiat. Ut fugiat do dolor minim voluptate incididunt laboris magna deserunt. Culpa incididunt fugiat nostrud qui incididunt velit laboris deserunt exercitation velit.\r\n", "registered": "2014-09-16T06:10:45 +07:00", "latitude": -28.413217, "longitude": -76.45198, "tags": [ "ullamco", "ut", "nulla", "consequat", "ea", "in", "commodo" ], "friends": [ { "id": 0, "name": "Virginia Obrien" }, { "id": 1, "name": "Snider Hopper" }, { "id": 2, "name": "Fannie Harrell" } ], "greeting": "Hello, Espinoza May! You have 3 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a901e753e41d1232a42", "index": 40, "guid": "7f3923e7-2fad-4210-b051-bd805e505d06", "isActive": false, "balance": "$2,512.14", "picture": "http://placehold.it/32x32", "age": 28, "eyeColor": "green", "name": "Morrison Guerrero", "gender": "male", "company": "MARQET", "email": "morrisonguerrero@marqet.com", "phone": "+1 (881) 456-3335", "address": "157 Huntington Street, Topaz, Georgia, 6068", "about": "Velit cupidatat eiusmod elit ut adipisicing. Proident pariatur consequat ullamco velit dolore do esse adipisicing non est ea. Velit non amet nisi aliqua est veniam dolor. Cillum id labore qui ut aute pariatur exercitation ut incididunt velit aute.\r\n", "registered": "2014-11-12T21:01:15 +08:00", "latitude": -43.420946, "longitude": 23.215515, "tags": [ "sit", "dolore", "aliqua", "esse", "et", "cillum", "mollit" ], "friends": [ { "id": 0, "name": "Pamela Stanton" }, { "id": 1, "name": "Spence Banks" }, { "id": 2, "name": "Newton Cooley" } ], "greeting": "Hello, Morrison Guerrero! You have 4 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a9098c06d55fa03398f", "index": 41, "guid": "c17e4f56-ca2b-48fd-bbc4-aea053062ebd", "isActive": false, "balance": "$3,405.25", "picture": "http://placehold.it/32x32", "age": 26, "eyeColor": "brown", "name": "Janna Porter", "gender": "female", "company": "NIMON", "email": "jannaporter@nimon.com", "phone": "+1 (974) 475-2497", "address": "231 Wythe Place, Stonybrook, Alaska, 6291", "about": "Veniam aute dolor Lorem dolore enim eiusmod veniam esse pariatur duis nisi. Eu sit sunt in exercitation amet veniam reprehenderit voluptate proident officia. Dolore aliquip laboris veniam cupidatat non cupidatat ipsum esse labore Lorem reprehenderit ex. Amet magna do officia proident laborum laboris enim. Ea sunt quis officia minim ea in id cillum. Aute ipsum aliquip fugiat tempor proident sit pariatur duis fugiat fugiat esse cillum eiusmod laboris.\r\n", "registered": "2014-08-21T22:08:24 +07:00", "latitude": -43.52587, "longitude": 143.40506, "tags": [ "ipsum", "consequat", "labore", "tempor", "ipsum", "exercitation", "sint" ], "friends": [ { "id": 0, "name": "Bray Francis" }, { "id": 1, "name": "Whitley Guthrie" }, { "id": 2, "name": "Christa Short" } ], "greeting": "Hello, Janna Porter! You have 1 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90ddf3f9e967357339", "index": 42, "guid": "5b194b7d-c5ca-4cdd-9239-6aa6f9b28e2f", "isActive": false, "balance": "$1,601.96", "picture": "http://placehold.it/32x32", "age": 31, "eyeColor": "green", "name": "Sandoval Melton", "gender": "male", "company": "GENMEX", "email": "sandovalmelton@genmex.com", "phone": "+1 (826) 536-3504", "address": "726 Lester Court, Gracey, Colorado, 4092", "about": "Fugiat pariatur elit Lorem amet fugiat tempor. Quis sint fugiat officia deserunt voluptate fugiat aliquip reprehenderit est laborum. Ut id ullamco Lorem esse occaecat eu officia veniam velit. Aliquip nisi voluptate id aliquip qui tempor commodo occaecat velit adipisicing nisi cillum id adipisicing.\r\n", "registered": "2014-09-05T08:54:55 +07:00", "latitude": -66.159672, "longitude": -135.605108, "tags": [ "deserunt", "minim", "nulla", "ea", "tempor", "reprehenderit", "nulla" ], "friends": [ { "id": 0, "name": "Veronica Goodwin" }, { "id": 1, "name": "Heather Pena" }, { "id": 2, "name": "Lynch Crane" } ], "greeting": "Hello, Sandoval Melton! You have 2 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a904d114bb57f0826af", "index": 43, "guid": "57e4715d-f7e7-4843-9844-638648315628", "isActive": false, "balance": "$1,820.21", "picture": "http://placehold.it/32x32", "age": 34, "eyeColor": "blue", "name": "Flynn Fitzgerald", "gender": "male", "company": "ORBEAN", "email": "flynnfitzgerald@orbean.com", "phone": "+1 (931) 578-2443", "address": "662 Degraw Street, Morgandale, Alabama, 5945", "about": "Nulla anim qui duis ea do consectetur eiusmod commodo. Minim sunt aliqua velit ullamco velit dolor in amet. Eiusmod Lorem sint ea ea nisi ullamco ut officia magna id adipisicing. Ut eu minim pariatur incididunt non nisi in nostrud culpa magna anim. Veniam dolor consequat cillum sunt elit.\r\n", "registered": "2014-06-21T08:11:23 +07:00", "latitude": 17.108863, "longitude": -21.608292, "tags": [ "officia", "quis", "sint", "ipsum", "esse", "commodo", "aute" ], "friends": [ { "id": 0, "name": "Browning Mcdonald" }, { "id": 1, "name": "Austin Lane" }, { "id": 2, "name": "Blankenship Ferrell" } ], "greeting": "Hello, Flynn Fitzgerald! You have 6 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a903a4a0629f547f5ab", "index": 44, "guid": "1e128e33-65bf-4420-ae93-f228d030401c", "isActive": false, "balance": "$3,158.96", "picture": "http://placehold.it/32x32", "age": 25, "eyeColor": "brown", "name": "Holden Golden", "gender": "male", "company": "QABOOS", "email": "holdengolden@qaboos.com", "phone": "+1 (825) 535-2422", "address": "892 Vandervoort Place, Hessville, Guam, 3942", "about": "Non sunt cupidatat ipsum nostrud qui ad ex nostrud fugiat laboris minim. Aliquip dolore est proident aliquip in non culpa. Minim ut laboris duis proident commodo occaecat duis duis cupidatat incididunt aliqua. Ad qui anim non occaecat excepteur labore consequat Lorem.\r\n", "registered": "2014-09-11T00:33:16 +07:00", "latitude": -3.274271, "longitude": -151.539207, "tags": [ "nostrud", "non", "sint", "laborum", "deserunt", "velit", "sit" ], "friends": [ { "id": 0, "name": "Barbara Sharpe" }, { "id": 1, "name": "Jerri Martinez" }, { "id": 2, "name": "Ronda Montoya" } ], "greeting": "Hello, Holden Golden! You have 3 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a9079e20c148518a60a", "index": 45, "guid": "90fa284f-6cba-42d4-8484-6edb1ffc260b", "isActive": false, "balance": "$1,739.35", "picture": "http://placehold.it/32x32", "age": 27, "eyeColor": "blue", "name": "Maxwell Hodges", "gender": "male", "company": "DOGTOWN", "email": "maxwellhodges@dogtown.com", "phone": "+1 (962) 527-3585", "address": "696 Baughman Place, Cucumber, South Carolina, 5454", "about": "Officia ea in non veniam ipsum ea magna enim velit. Enim mollit duis consectetur magna fugiat nostrud cillum duis. Voluptate qui nostrud amet ea eiusmod consectetur cupidatat fugiat in eiusmod amet esse excepteur aute. Magna qui duis ex qui irure esse amet. Quis amet ex esse aliquip mollit. Deserunt consectetur eiusmod culpa reprehenderit. Duis quis excepteur non in consectetur commodo.\r\n", "registered": "2014-03-20T11:37:19 +07:00", "latitude": 19.760315, "longitude": -26.731699, "tags": [ "magna", "aute", "consectetur", "labore", "sunt", "pariatur", "excepteur" ], "friends": [ { "id": 0, "name": "Violet Vincent" }, { "id": 1, "name": "West Dorsey" }, { "id": 2, "name": "Concepcion Hull" } ], "greeting": "Hello, Maxwell Hodges! You have 3 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a903c504d648884f367", "index": 46, "guid": "7fd30275-a097-41e0-8924-252f0a14d6ba", "isActive": false, "balance": "$1,153.05", "picture": "http://placehold.it/32x32", "age": 22, "eyeColor": "brown", "name": "Chasity Day", "gender": "female", "company": "EQUITAX", "email": "chasityday@equitax.com", "phone": "+1 (900) 484-3047", "address": "858 Gelston Avenue, Succasunna, Arkansas, 3818", "about": "Est ullamco deserunt cillum enim velit velit magna qui nisi eiusmod enim officia sit voluptate. Laboris laborum elit nostrud sit in elit labore occaecat mollit Lorem. Aliquip ipsum dolore cupidatat ad anim sint non. Commodo ut fugiat ut dolor irure id velit enim in Lorem.\r\n", "registered": "2014-01-05T08:26:01 +08:00", "latitude": -34.705083, "longitude": -77.213981, "tags": [ "consectetur", "velit", "enim", "excepteur", "ipsum", "non", "adipisicing" ], "friends": [ { "id": 0, "name": "Judy Trevino" }, { "id": 1, "name": "Rosie Cervantes" }, { "id": 2, "name": "Stella Cortez" } ], "greeting": "Hello, Chasity Day! You have 1 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90ac6406c3b9606052", "index": 47, "guid": "9bcd39b8-10db-40cc-a9f0-73e8179f181b", "isActive": true, "balance": "$1,755.70", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "green", "name": "Richards Mcfadden", "gender": "male", "company": "ZILLACOM", "email": "richardsmcfadden@zillacom.com", "phone": "+1 (883) 447-2941", "address": "241 Turnbull Avenue, Chesterfield, Ohio, 7594", "about": "Fugiat ut qui qui et Lorem ipsum do anim veniam. Sunt ex Lorem et nostrud consectetur esse nostrud qui minim ut veniam commodo. Cillum enim laboris aliquip sunt quis ut et adipisicing deserunt. Est aute amet elit non duis deserunt nisi quis excepteur do velit. Nostrud laboris ullamco sunt occaecat Lorem nostrud laboris.\r\n", "registered": "2014-07-04T03:08:44 +07:00", "latitude": -66.813737, "longitude": 75.337073, "tags": [ "elit", "consequat", "excepteur", "qui", "deserunt", "sint", "ipsum" ], "friends": [ { "id": 0, "name": "Mercado Quinn" }, { "id": 1, "name": "Lucia Roberts" }, { "id": 2, "name": "Essie Cohen" } ], "greeting": "Hello, Richards Mcfadden! You have 5 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9033409e09e42cf3f1", "index": 48, "guid": "6ea51613-14f0-42b7-97c6-eb7a5cc32226", "isActive": true, "balance": "$3,907.64", "picture": "http://placehold.it/32x32", "age": 31, "eyeColor": "blue", "name": "Sargent Harrington", "gender": "male", "company": "DIGINETIC", "email": "sargentharrington@diginetic.com", "phone": "+1 (974) 427-2742", "address": "883 Kermit Place, Rehrersburg, Virgin Islands, 4044", "about": "Officia eiusmod do ut ipsum voluptate aute mollit minim ea incididunt ipsum commodo. Qui aute commodo dolor id pariatur ullamco adipisicing duis irure reprehenderit aliquip ullamco consequat. Sunt ad non deserunt velit consectetur ipsum. Sit voluptate aliquip nisi ea pariatur proident ut eu cillum. Irure sunt ad aliqua et enim. Deserunt deserunt incididunt Lorem commodo aliqua.\r\n", "registered": "2014-06-16T00:32:02 +07:00", "latitude": -88.301682, "longitude": -16.268399, "tags": [ "Lorem", "reprehenderit", "consequat", "officia", "velit", "ad", "ex" ], "friends": [ { "id": 0, "name": "Dolly Swanson" }, { "id": 1, "name": "Jeannette Underwood" }, { "id": 2, "name": "Ayers Wheeler" } ], "greeting": "Hello, Sargent Harrington! You have 3 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a9083fe43074bb5b9c8", "index": 49, "guid": "d5835fea-0882-4e20-b86e-6dd8b9534b49", "isActive": false, "balance": "$2,481.41", "picture": "http://placehold.it/32x32", "age": 22, "eyeColor": "green", "name": "Kristin Perez", "gender": "female", "company": "JAMNATION", "email": "kristinperez@jamnation.com", "phone": "+1 (917) 575-2693", "address": "737 Schroeders Avenue, Chemung, Nebraska, 8601", "about": "Voluptate id id mollit in aliquip aliquip duis cupidatat elit voluptate proident sit sunt voluptate. Irure ipsum esse duis culpa esse et do officia consequat velit commodo Lorem. Dolore incididunt proident proident officia aliqua mollit nisi exercitation consectetur. Est dolore consectetur aliqua occaecat est. Labore nostrud ipsum aliquip labore elit aliquip magna ex esse do consequat minim id. Sit sint ea ad irure voluptate occaecat duis magna. Sint ex minim irure anim sint do cillum.\r\n", "registered": "2014-08-12T23:35:39 +07:00", "latitude": 75.002428, "longitude": 12.266159, "tags": [ "anim", "exercitation", "excepteur", "amet", "aute", "mollit", "aliquip" ], "friends": [ { "id": 0, "name": "Gilliam Steele" }, { "id": 1, "name": "Loretta Brennan" }, { "id": 2, "name": "Ratliff Norton" } ], "greeting": "Hello, Kristin Perez! You have 9 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90f594e03626363339", "index": 50, "guid": "bdb8284c-7b55-4791-90c0-d9e4abecd91f", "isActive": true, "balance": "$1,906.85", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "green", "name": "Petra Scott", "gender": "female", "company": "BRAINCLIP", "email": "petrascott@brainclip.com", "phone": "+1 (942) 449-2471", "address": "759 Coleridge Street, Tuskahoma, Virginia, 9943", "about": "Consectetur magna consequat ea est. Minim veniam culpa deserunt aliqua in dolor ex aliqua occaecat reprehenderit. Proident in mollit ad est excepteur anim quis aliquip non consequat minim cillum deserunt. Occaecat sint ad et irure sit ad ad sit sint quis sunt nisi.\r\n", "registered": "2014-11-12T20:54:05 +08:00", "latitude": -64.192199, "longitude": -144.535209, "tags": [ "cillum", "id", "aliqua", "reprehenderit", "officia", "aliquip", "in" ], "friends": [ { "id": 0, "name": "Holmes Rasmussen" }, { "id": 1, "name": "Leach Hickman" }, { "id": 2, "name": "Noelle Battle" } ], "greeting": "Hello, Petra Scott! You have 9 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a902f79c4cdada83391", "index": 51, "guid": "c79aaabd-212b-4dc8-b1b5-de14362b550c", "isActive": true, "balance": "$2,845.25", "picture": "http://placehold.it/32x32", "age": 32, "eyeColor": "brown", "name": "Kelli Gates", "gender": "female", "company": "MUSANPOLY", "email": "kelligates@musanpoly.com", "phone": "+1 (899) 414-3276", "address": "888 Elm Place, Grayhawk, Wyoming, 8032", "about": "Nisi excepteur laboris duis magna dolore occaecat dolor cupidatat. Ut commodo proident incididunt ea anim enim deserunt laboris occaecat anim cillum. In amet exercitation officia mollit officia quis exercitation aliqua culpa ullamco consequat excepteur aute mollit. Aliqua tempor consequat ullamco consequat qui duis tempor ex est aliqua id nulla Lorem occaecat. Et laborum culpa pariatur et ad minim. Nulla ad eiusmod pariatur velit aliquip magna duis duis tempor. Nisi ea reprehenderit aliquip magna esse occaecat consectetur ullamco esse.\r\n", "registered": "2014-03-01T15:11:58 +08:00", "latitude": 30.679655, "longitude": -175.200369, "tags": [ "laborum", "non", "pariatur", "ea", "non", "proident", "culpa" ], "friends": [ { "id": 0, "name": "Coleman Mejia" }, { "id": 1, "name": "Meyers Sellers" }, { "id": 2, "name": "Stuart Carney" } ], "greeting": "Hello, Kelli Gates! You have 1 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a9040ef999266e0142c", "index": 52, "guid": "cb9bc903-5e95-4918-91ed-8485d75489fa", "isActive": true, "balance": "$1,352.24", "picture": "http://placehold.it/32x32", "age": 29, "eyeColor": "green", "name": "Maricela Conrad", "gender": "female", "company": "QUIZKA", "email": "maricelaconrad@quizka.com", "phone": "+1 (924) 592-2199", "address": "339 Virginia Place, Lutsen, Marshall Islands, 1479", "about": "Quis commodo cupidatat mollit et deserunt id ut anim nostrud nisi mollit esse commodo laborum. Cillum exercitation anim cillum esse quis consequat. Dolor laboris exercitation irure ullamco excepteur ipsum deserunt. Anim veniam dolore labore exercitation et consectetur eiusmod eu. Aliquip velit consectetur nostrud dolore.\r\n", "registered": "2014-06-15T22:10:22 +07:00", "latitude": -0.554318, "longitude": -65.103334, "tags": [ "adipisicing", "irure", "deserunt", "culpa", "cupidatat", "do", "occaecat" ], "friends": [ { "id": 0, "name": "Gentry Holden" }, { "id": 1, "name": "Dillard Herrera" }, { "id": 2, "name": "Guzman Patton" } ], "greeting": "Hello, Maricela Conrad! You have 1 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a905369b0bb27f85607", "index": 53, "guid": "fa3a125f-2d10-4015-a0fd-68d7e2401a31", "isActive": false, "balance": "$2,858.28", "picture": "http://placehold.it/32x32", "age": 34, "eyeColor": "green", "name": "Simpson Cleveland", "gender": "male", "company": "ZAPPIX", "email": "simpsoncleveland@zappix.com", "phone": "+1 (808) 572-3724", "address": "202 Georgia Avenue, Jamestown, Texas, 6347", "about": "Reprehenderit elit in duis sunt quis consequat mollit ut consequat amet. Incididunt non sint culpa non mollit incididunt elit irure sint excepteur esse sit ut fugiat. Ullamco esse culpa excepteur magna laborum sunt magna ut reprehenderit aute laboris ullamco Lorem ea. Culpa ut sit amet dolor adipisicing veniam non occaecat ex ad ea. Quis nostrud sit mollit aliqua adipisicing.\r\n", "registered": "2014-10-27T07:51:50 +07:00", "latitude": -34.024135, "longitude": 66.799767, "tags": [ "anim", "pariatur", "fugiat", "reprehenderit", "ullamco", "labore", "fugiat" ], "friends": [ { "id": 0, "name": "Hester Howell" }, { "id": 1, "name": "Deena King" }, { "id": 2, "name": "Wilkerson Fox" } ], "greeting": "Hello, Simpson Cleveland! You have 10 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a900271aa8695bc5cdf", "index": 54, "guid": "501e7876-6b3f-4f2e-bbaf-914e6ff23845", "isActive": false, "balance": "$2,015.78", "picture": "http://placehold.it/32x32", "age": 23, "eyeColor": "brown", "name": "Queen Mckay", "gender": "female", "company": "PROXSOFT", "email": "queenmckay@proxsoft.com", "phone": "+1 (954) 439-2402", "address": "749 Wakeman Place, Sidman, Massachusetts, 3345", "about": "Culpa irure velit cupidatat voluptate ad non anim sit sunt in esse adipisicing. Officia amet Lorem et id eiusmod non commodo deserunt irure tempor aute fugiat est cupidatat. Ut amet ad consequat nulla in in deserunt minim ipsum adipisicing eu adipisicing nisi nulla. Qui culpa sunt aute amet est consequat excepteur occaecat voluptate in do. In labore aute sit duis enim sunt qui ullamco est tempor labore aute aliquip. Sunt eu veniam in amet cillum nisi tempor quis in fugiat culpa exercitation sunt. Exercitation enim dolore sit exercitation in mollit culpa magna amet et amet.\r\n", "registered": "2014-05-02T07:58:52 +07:00", "latitude": -24.836277, "longitude": -108.207588, "tags": [ "aliquip", "dolor", "velit", "non", "sint", "deserunt", "ut" ], "friends": [ { "id": 0, "name": "Maynard Shannon" }, { "id": 1, "name": "Ernestine Sullivan" }, { "id": 2, "name": "Sullivan Juarez" } ], "greeting": "Hello, Queen Mckay! You have 8 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a902c9d0c4f7379c125", "index": 55, "guid": "c13147c1-9aab-432b-9eaa-eda127454f06", "isActive": false, "balance": "$1,498.79", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "green", "name": "Madeline Rhodes", "gender": "female", "company": "LOCAZONE", "email": "madelinerhodes@locazone.com", "phone": "+1 (817) 404-2650", "address": "648 Rochester Avenue, Tetherow, Arizona, 751", "about": "Sit velit ea enim mollit ad fugiat anim commodo minim qui sit dolor aliqua. Amet nostrud aliquip qui velit et ea reprehenderit sint ipsum quis. Ut amet aute enim proident. Et officia nostrud voluptate non tempor quis aliquip ullamco commodo consequat fugiat ut. Eiusmod sit excepteur non nostrud esse consequat nulla sunt deserunt aliqua. Commodo laborum voluptate ea eu non excepteur pariatur.\r\n", "registered": "2014-03-14T19:50:42 +07:00", "latitude": -31.489199, "longitude": 124.798218, "tags": [ "tempor", "culpa", "pariatur", "irure", "nisi", "proident", "quis" ], "friends": [ { "id": 0, "name": "Hebert Kline" }, { "id": 1, "name": "Daisy Cochran" }, { "id": 2, "name": "Russell Gilmore" } ], "greeting": "Hello, Madeline Rhodes! You have 10 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90b6d8621dab6c9126", "index": 56, "guid": "2ebcecc1-180e-46b7-bdca-9d9a6babc687", "isActive": false, "balance": "$3,190.82", "picture": "http://placehold.it/32x32", "age": 27, "eyeColor": "blue", "name": "Rasmussen Knapp", "gender": "male", "company": "BIOSPAN", "email": "rasmussenknapp@biospan.com", "phone": "+1 (860) 461-3219", "address": "214 Williams Court, Brady, Oregon, 5174", "about": "Tempor ullamco officia laborum irure cillum est culpa tempor pariatur aliqua officia incididunt tempor. Laboris adipisicing nostrud Lorem veniam enim consequat mollit nisi. Minim nulla culpa dolor esse dolore deserunt reprehenderit adipisicing aliquip.\r\n", "registered": "2014-08-11T17:15:51 +07:00", "latitude": -25.850361, "longitude": -36.01581, "tags": [ "enim", "laboris", "dolore", "amet", "nisi", "in", "aliqua" ], "friends": [ { "id": 0, "name": "Letha Peters" }, { "id": 1, "name": "Lavonne Mccarthy" }, { "id": 2, "name": "Hensley Kim" } ], "greeting": "Hello, Rasmussen Knapp! You have 5 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a902e4d6731ddf406bf", "index": 57, "guid": "7a13b0b9-7cc4-477a-944f-a27eb7e74ae6", "isActive": false, "balance": "$1,711.06", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "brown", "name": "Maryellen Russell", "gender": "female", "company": "MAXEMIA", "email": "maryellenrussell@maxemia.com", "phone": "+1 (839) 590-2573", "address": "514 Roosevelt Court, Sugartown, American Samoa, 6602", "about": "Pariatur laborum nostrud aliqua nisi cillum sunt laborum cillum minim pariatur et consectetur minim adipisicing. Exercitation non dolor id voluptate aute sint sunt. Nostrud cupidatat officia dolor cupidatat ex irure non. Fugiat laboris quis id aliqua sunt consectetur est ea. Eiusmod mollit enim Lorem cupidatat consectetur anim nostrud enim eu irure. Et eiusmod velit esse fugiat elit laboris labore voluptate ipsum. Excepteur consequat proident quis voluptate excepteur nulla in.\r\n", "registered": "2014-05-17T21:19:21 +07:00", "latitude": -15.634102, "longitude": -81.860909, "tags": [ "ea", "ipsum", "esse", "veniam", "reprehenderit", "adipisicing", "do" ], "friends": [ { "id": 0, "name": "Virgie Whitaker" }, { "id": 1, "name": "Earlene Ruiz" }, { "id": 2, "name": "Rosa Estrada" } ], "greeting": "Hello, Maryellen Russell! You have 5 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a906ea1b53a8de569dd", "index": 58, "guid": "0e91224f-af4a-4cb0-a51e-5874ad140b32", "isActive": false, "balance": "$1,226.26", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "blue", "name": "Wright Morris", "gender": "male", "company": "APPLICA", "email": "wrightmorris@applica.com", "phone": "+1 (968) 550-2677", "address": "630 Hornell Loop, Sparkill, Montana, 7355", "about": "Veniam commodo nostrud nostrud ullamco do aliquip quis dolore laboris culpa minim do est. In sunt consequat irure veniam minim duis ex commodo duis. Ullamco eu reprehenderit dolore eiusmod est exercitation nisi tempor.\r\n", "registered": "2014-02-05T10:33:53 +08:00", "latitude": -16.050009, "longitude": -149.883606, "tags": [ "Lorem", "in", "est", "consequat", "cillum", "adipisicing", "commodo" ], "friends": [ { "id": 0, "name": "Washington Carson" }, { "id": 1, "name": "Hines Bean" }, { "id": 2, "name": "Cox Powell" } ], "greeting": "Hello, Wright Morris! You have 7 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9047deb3b6b5122221", "index": 59, "guid": "f85bae2d-b72a-4f81-b596-b5338ec41578", "isActive": true, "balance": "$1,928.94", "picture": "http://placehold.it/32x32", "age": 26, "eyeColor": "brown", "name": "Agnes Guzman", "gender": "female", "company": "PEARLESSA", "email": "agnesguzman@pearlessa.com", "phone": "+1 (859) 451-3816", "address": "874 Duffield Street, Benson, Hawaii, 1388", "about": "Ad voluptate incididunt ullamco ullamco velit adipisicing culpa aute minim adipisicing non. Consectetur elit ullamco mollit ipsum aliqua in enim Lorem eiusmod nisi fugiat exercitation. Do amet pariatur deserunt ex labore exercitation non ad commodo aliquip. Nostrud magna ipsum reprehenderit qui consectetur cillum irure nostrud do quis excepteur cillum.\r\n", "registered": "2014-07-28T12:22:31 +07:00", "latitude": -89.041016, "longitude": -4.513498, "tags": [ "eiusmod", "deserunt", "deserunt", "eiusmod", "minim", "nisi", "magna" ], "friends": [ { "id": 0, "name": "Kari Trujillo" }, { "id": 1, "name": "Kaye Sloan" }, { "id": 2, "name": "Aguilar Fields" } ], "greeting": "Hello, Agnes Guzman! You have 9 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a905ad56237e1e3ae99", "index": 60, "guid": "3244774e-3c8d-4c84-8ae6-d04486ce05d7", "isActive": false, "balance": "$3,045.23", "picture": "http://placehold.it/32x32", "age": 27, "eyeColor": "green", "name": "Jill Evans", "gender": "female", "company": "GOLISTIC", "email": "jillevans@golistic.com", "phone": "+1 (871) 577-2459", "address": "738 Putnam Avenue, Ona, South Dakota, 4749", "about": "Irure exercitation esse quis commodo sunt laborum esse id anim. Ut ut ad quis qui id labore ut tempor labore velit laborum pariatur. Dolore ipsum ea tempor excepteur esse cillum sit non eu sit irure adipisicing mollit. Nulla ut proident velit consequat officia magna ex duis proident aliqua amet exercitation do commodo. Nulla Lorem ad reprehenderit mollit deserunt veniam qui duis enim enim consectetur do.\r\n", "registered": "2014-05-05T11:50:14 +07:00", "latitude": -56.941561, "longitude": -169.158104, "tags": [ "consequat", "minim", "minim", "laborum", "aute", "nisi", "aliqua" ], "friends": [ { "id": 0, "name": "Compton Becker" }, { "id": 1, "name": "Conner Wall" }, { "id": 2, "name": "Bright Harvey" } ], "greeting": "Hello, Jill Evans! You have 2 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90f530d8bc9e6faf86", "index": 61, "guid": "a983ed9d-fb1b-48ee-94b7-54b33634ccbc", "isActive": false, "balance": "$3,091.12", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "brown", "name": "Susana Berry", "gender": "female", "company": "POWERNET", "email": "susanaberry@powernet.com", "phone": "+1 (879) 454-3173", "address": "141 Cambridge Place, Florence, District Of Columbia, 6760", "about": "Magna occaecat laborum voluptate excepteur. Proident esse voluptate enim est exercitation elit voluptate minim ex. Velit officia cupidatat sit quis reprehenderit minim voluptate et nulla cupidatat duis mollit. Aute incididunt id magna nostrud cupidatat qui sit. Enim anim enim excepteur est sunt non enim proident sit non deserunt et veniam culpa. Ullamco irure ullamco id esse exercitation anim et fugiat labore. Do enim exercitation deserunt sint consectetur occaecat commodo commodo elit.\r\n", "registered": "2014-06-08T14:24:28 +07:00", "latitude": 75.590221, "longitude": -127.23641, "tags": [ "esse", "anim", "est", "anim", "esse", "adipisicing", "mollit" ], "friends": [ { "id": 0, "name": "Helene Holcomb" }, { "id": 1, "name": "Kramer Gregory" }, { "id": 2, "name": "Fitzgerald Graves" } ], "greeting": "Hello, Susana Berry! You have 1 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90e6f9c07f205357ec", "index": 62, "guid": "26cecce2-1202-4703-8bf5-8ff431336b37", "isActive": false, "balance": "$3,437.96", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "blue", "name": "Weeks Wallace", "gender": "male", "company": "SUREMAX", "email": "weekswallace@suremax.com", "phone": "+1 (946) 528-2733", "address": "219 Dekalb Avenue, Hasty, North Carolina, 7278", "about": "Magna dolor ex dolor eiusmod sint laboris consequat non magna ipsum. Nostrud qui aute ut consectetur in amet deserunt aliqua voluptate. In velit nisi voluptate amet consequat. Tempor deserunt velit ut aliqua duis cupidatat laboris amet in ipsum aliquip adipisicing. Quis anim cillum labore ipsum commodo deserunt mollit tempor tempor pariatur dolore. Irure aute ipsum do occaecat laborum eiusmod ad proident exercitation elit cillum do.\r\n", "registered": "2014-07-17T22:33:55 +07:00", "latitude": -22.986103, "longitude": -110.848014, "tags": [ "ut", "irure", "elit", "quis", "ut", "fugiat", "sunt" ], "friends": [ { "id": 0, "name": "Colon Tyler" }, { "id": 1, "name": "Dianne Lucas" }, { "id": 2, "name": "Mathews Acosta" } ], "greeting": "Hello, Weeks Wallace! You have 8 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9034039bde61fe5fdb", "index": 63, "guid": "cad69671-eb0a-4128-8024-9a0f469cf1f8", "isActive": true, "balance": "$2,503.03", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "green", "name": "Watson Tucker", "gender": "male", "company": "IMKAN", "email": "watsontucker@imkan.com", "phone": "+1 (841) 499-3837", "address": "297 Falmouth Street, Woodlands, Tennessee, 2227", "about": "Do aliquip laboris voluptate aliqua duis duis qui. Lorem officia consectetur et in nulla do aliquip occaecat labore officia sunt ipsum ad consequat. Culpa voluptate adipisicing dolore do velit ea.\r\n", "registered": "2014-09-16T17:39:32 +07:00", "latitude": 76.336221, "longitude": -154.036452, "tags": [ "veniam", "non", "aliquip", "ex", "esse", "sint", "voluptate" ], "friends": [ { "id": 0, "name": "Lolita Finch" }, { "id": 1, "name": "Gilmore Solis" }, { "id": 2, "name": "Faith Gallegos" } ], "greeting": "Hello, Watson Tucker! You have 9 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90780b195513995278", "index": 64, "guid": "625810dc-6353-4387-862c-e71ed6115966", "isActive": false, "balance": "$2,428.28", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "green", "name": "Levy Ortega", "gender": "male", "company": "FIBEROX", "email": "levyortega@fiberox.com", "phone": "+1 (819) 514-2393", "address": "485 Dunne Place, Sena, Idaho, 1583", "about": "Exercitation reprehenderit voluptate aliqua laborum dolore consequat pariatur ipsum occaecat culpa et dolore voluptate. Laborum ut adipisicing exercitation irure ipsum ea. Occaecat aute officia et qui id elit adipisicing consectetur. Laborum ullamco pariatur eiusmod dolore aliqua ea nostrud. Occaecat ullamco nostrud deserunt ea officia. Deserunt incididunt et laboris veniam laboris adipisicing culpa laborum occaecat culpa sit labore. Irure in ipsum exercitation ea laboris culpa.\r\n", "registered": "2014-06-19T01:29:28 +07:00", "latitude": -66.489978, "longitude": 35.142253, "tags": [ "consequat", "ut", "ipsum", "ullamco", "anim", "irure", "consectetur" ], "friends": [ { "id": 0, "name": "Nellie Webb" }, { "id": 1, "name": "Sheri Roy" }, { "id": 2, "name": "Elizabeth Cooke" } ], "greeting": "Hello, Levy Ortega! You have 3 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a901df67d5f687df4ab", "index": 65, "guid": "73d49a86-1caa-4ef5-b637-aef68b215e96", "isActive": true, "balance": "$3,990.52", "picture": "http://placehold.it/32x32", "age": 24, "eyeColor": "blue", "name": "Webster Conway", "gender": "male", "company": "PRISMATIC", "email": "websterconway@prismatic.com", "phone": "+1 (857) 462-3648", "address": "557 Dekoven Court, Sandston, Palau, 8537", "about": "Fugiat non velit fugiat sint minim magna occaecat deserunt enim adipisicing excepteur amet. Esse incididunt mollit nisi ut id consectetur qui laborum consequat et occaecat. Tempor cupidatat enim sunt cillum. Laborum consequat Lorem enim fugiat id voluptate incididunt aliquip eu esse dolor duis ad. Officia dolore duis nisi veniam ut ut dolore fugiat deserunt aute consectetur. Excepteur voluptate mollit velit duis ullamco voluptate ullamco.\r\n", "registered": "2014-04-30T14:39:28 +07:00", "latitude": -67.082095, "longitude": 38.979656, "tags": [ "amet", "aliquip", "ea", "culpa", "incididunt", "dolor", "fugiat" ], "friends": [ { "id": 0, "name": "Sharp Ramirez" }, { "id": 1, "name": "Leona Campbell" }, { "id": 2, "name": "Hyde Reyes" } ], "greeting": "Hello, Webster Conway! You have 3 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90f7b820f93d4df443", "index": 66, "guid": "1a306b16-3a38-426c-9254-22dd7264c108", "isActive": true, "balance": "$2,194.31", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "brown", "name": "Hill Lancaster", "gender": "male", "company": "UNIWORLD", "email": "hilllancaster@uniworld.com", "phone": "+1 (836) 462-3865", "address": "786 Dictum Court, Roulette, Minnesota, 3625", "about": "Adipisicing ea commodo et nulla ullamco fugiat do magna occaecat consectetur cupidatat nisi fugiat consequat. Velit veniam eu cupidatat adipisicing culpa non non velit amet labore. Dolore dolor enim eiusmod ipsum excepteur non sint ullamco irure laboris nulla id.\r\n", "registered": "2014-03-09T12:51:14 +07:00", "latitude": -65.924237, "longitude": 161.521943, "tags": [ "amet", "id", "aliquip", "aliquip", "exercitation", "excepteur", "cupidatat" ], "friends": [ { "id": 0, "name": "Morrow Mullen" }, { "id": 1, "name": "Calderon Campos" }, { "id": 2, "name": "Janis Ramsey" } ], "greeting": "Hello, Hill Lancaster! You have 10 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a906c7f0305536c965c", "index": 67, "guid": "d1dadd20-7ced-447d-ba72-61e886f4195e", "isActive": true, "balance": "$3,014.64", "picture": "http://placehold.it/32x32", "age": 25, "eyeColor": "brown", "name": "Fletcher Pearson", "gender": "male", "company": "QOT", "email": "fletcherpearson@qot.com", "phone": "+1 (930) 439-2213", "address": "779 Middagh Street, Crayne, Illinois, 2229", "about": "Nulla sit officia velit dolore eiusmod veniam anim laborum Lorem anim et enim irure. Quis labore ad proident occaecat dolore tempor occaecat dolor dolore aliqua laboris esse enim. Dolore tempor cupidatat aute labore aliqua nulla non est.\r\n", "registered": "2014-04-25T09:09:10 +07:00", "latitude": -2.329892, "longitude": 135.411164, "tags": [ "magna", "ipsum", "tempor", "velit", "esse", "magna", "nisi" ], "friends": [ { "id": 0, "name": "Tonya Ashley" }, { "id": 1, "name": "Latisha Burris" }, { "id": 2, "name": "Tracey Rowe" } ], "greeting": "Hello, Fletcher Pearson! You have 9 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9057e5269ab81d8e18", "index": 68, "guid": "4723bd56-76cb-4a30-bdf5-8b4c4c9805aa", "isActive": false, "balance": "$3,114.82", "picture": "http://placehold.it/32x32", "age": 23, "eyeColor": "blue", "name": "Odessa Lawson", "gender": "female", "company": "JOVIOLD", "email": "odessalawson@joviold.com", "phone": "+1 (921) 400-3177", "address": "443 Ryder Avenue, Camino, Missouri, 487", "about": "Labore aliquip nulla est eiusmod amet Lorem duis fugiat duis do excepteur voluptate in non. Consequat nisi reprehenderit ullamco eu sit id consectetur commodo culpa consequat dolore aliqua. Amet nulla ut in laboris dolor do ad laboris eu commodo qui dolore pariatur. Et qui cillum anim dolore ipsum excepteur id laboris minim dolor.\r\n", "registered": "2014-03-26T22:07:14 +07:00", "latitude": 18.291259, "longitude": -86.22914, "tags": [ "nisi", "ut", "dolore", "ullamco", "cupidatat", "nulla", "laborum" ], "friends": [ { "id": 0, "name": "Vonda Cote" }, { "id": 1, "name": "Lewis Gonzales" }, { "id": 2, "name": "Jacqueline Richmond" } ], "greeting": "Hello, Odessa Lawson! You have 4 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90f748a6195f1c2b42", "index": 69, "guid": "697c2775-d924-436d-ba9f-e21bd4fa0f73", "isActive": false, "balance": "$1,269.09", "picture": "http://placehold.it/32x32", "age": 40, "eyeColor": "green", "name": "Selena Nieves", "gender": "female", "company": "INTRAWEAR", "email": "selenanieves@intrawear.com", "phone": "+1 (862) 476-3196", "address": "101 Harkness Avenue, Worton, Connecticut, 400", "about": "Sunt aliquip exercitation dolor dolore nostrud anim enim anim est officia. Minim ea Lorem ullamco reprehenderit officia reprehenderit ex ex reprehenderit. Qui nulla ullamco consequat minim exercitation. Veniam id eu pariatur ut veniam dolore aliquip qui aliqua incididunt ut.\r\n", "registered": "2014-03-07T15:11:53 +08:00", "latitude": -43.588256, "longitude": 43.731157, "tags": [ "duis", "duis", "reprehenderit", "ad", "magna", "excepteur", "officia" ], "friends": [ { "id": 0, "name": "Rutledge Hines" }, { "id": 1, "name": "Carrillo Johnson" }, { "id": 2, "name": "Morgan Parks" } ], "greeting": "Hello, Selena Nieves! You have 9 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90628ac7e339a407a5", "index": 70, "guid": "6ddd302b-fd62-47f9-aa8a-9fb2c35172c5", "isActive": true, "balance": "$2,185.43", "picture": "http://placehold.it/32x32", "age": 34, "eyeColor": "blue", "name": "Georgia Moran", "gender": "female", "company": "EARTHMARK", "email": "georgiamoran@earthmark.com", "phone": "+1 (970) 439-3884", "address": "848 Fay Court, Hayes, Maine, 7603", "about": "Ea do et excepteur dolor cupidatat nisi. Quis deserunt cupidatat duis enim eu deserunt anim enim. Cillum consectetur occaecat exercitation occaecat duis dolor voluptate officia exercitation irure. Occaecat magna proident enim exercitation veniam. Est commodo ullamco minim esse enim commodo ea commodo nulla et voluptate aliqua anim. Quis magna commodo nulla quis sit duis id et ex id ea dolore anim.\r\n", "registered": "2014-04-22T10:10:46 +07:00", "latitude": -78.673083, "longitude": 167.271688, "tags": [ "non", "labore", "adipisicing", "cupidatat", "cupidatat", "quis", "aliquip" ], "friends": [ { "id": 0, "name": "Andrews Love" }, { "id": 1, "name": "Brianna Yates" }, { "id": 2, "name": "Jennifer Bass" } ], "greeting": "Hello, Georgia Moran! You have 10 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a901ec4ee748cbbc125", "index": 71, "guid": "0e5fc95f-e605-4baa-bc36-b2f795c42e03", "isActive": false, "balance": "$2,256.63", "picture": "http://placehold.it/32x32", "age": 22, "eyeColor": "blue", "name": "House Sargent", "gender": "male", "company": "FANFARE", "email": "housesargent@fanfare.com", "phone": "+1 (877) 416-3590", "address": "961 Olive Street, Sultana, Puerto Rico, 3764", "about": "Cillum minim aliquip sit nulla aute commodo pariatur reprehenderit aliqua laboris in sint velit. Qui irure ut nostrud elit aliqua reprehenderit tempor quis laboris. Voluptate enim eiusmod laborum est excepteur enim est. Veniam non magna ea proident deserunt ipsum Lorem adipisicing velit eiusmod. Culpa id ea non ex ad.\r\n", "registered": "2014-04-27T09:04:21 +07:00", "latitude": -54.902834, "longitude": 147.773359, "tags": [ "cupidatat", "voluptate", "dolor", "excepteur", "exercitation", "id", "in" ], "friends": [ { "id": 0, "name": "Francis Alford" }, { "id": 1, "name": "Berta Sparks" }, { "id": 2, "name": "Laura Hahn" } ], "greeting": "Hello, House Sargent! You have 9 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90b51db1c7d287288e", "index": 72, "guid": "574450df-adad-4071-b642-0971f5f7928e", "isActive": true, "balance": "$2,263.30", "picture": "http://placehold.it/32x32", "age": 38, "eyeColor": "green", "name": "Roseann Lambert", "gender": "female", "company": "ROUGHIES", "email": "roseannlambert@roughies.com", "phone": "+1 (908) 551-2196", "address": "142 Girard Street, Levant, New Mexico, 2920", "about": "Aliquip ea elit anim aliqua in ea. Ex nisi nulla veniam amet. Occaecat pariatur qui consectetur consectetur anim ut anim cillum consectetur adipisicing pariatur. Cillum quis aliquip ad do in fugiat minim et ad labore sit ut aliqua cillum. Elit enim laboris incididunt laboris. Est in ullamco laboris deserunt aliqua veniam. Aute cillum culpa do dolore.\r\n", "registered": "2014-04-29T13:57:00 +07:00", "latitude": 0.812689, "longitude": 127.517728, "tags": [ "veniam", "quis", "do", "aliqua", "deserunt", "id", "ut" ], "friends": [ { "id": 0, "name": "Amelia Dunlap" }, { "id": 1, "name": "Benson Huff" }, { "id": 2, "name": "Aimee Fisher" } ], "greeting": "Hello, Roseann Lambert! You have 6 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90285dfadf5a8ab1db", "index": 73, "guid": "cf2c0b72-e90e-43d1-a5ee-ff85e28272ec", "isActive": false, "balance": "$3,053.88", "picture": "http://placehold.it/32x32", "age": 20, "eyeColor": "brown", "name": "Althea Burgess", "gender": "female", "company": "RODEMCO", "email": "altheaburgess@rodemco.com", "phone": "+1 (946) 406-2326", "address": "127 Fleet Place, Northridge, Northern Mariana Islands, 2106", "about": "Ea aliquip mollit consectetur non sunt. Deserunt adipisicing sint non excepteur veniam. Sunt eu ad Lorem qui laborum labore. Dolor ut esse veniam dolor officia. Minim occaecat labore voluptate exercitation fugiat eu labore non dolor ipsum do magna qui incididunt.\r\n", "registered": "2014-03-16T23:19:14 +07:00", "latitude": -63.483213, "longitude": 118.593144, "tags": [ "amet", "veniam", "consequat", "deserunt", "magna", "ea", "aliqua" ], "friends": [ { "id": 0, "name": "Delacruz Pollard" }, { "id": 1, "name": "Kelly Washington" }, { "id": 2, "name": "Irma Freeman" } ], "greeting": "Hello, Althea Burgess! You have 10 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a902435e7e0219ce954", "index": 74, "guid": "e3079855-52fe-494a-bb64-cf88934d1f84", "isActive": false, "balance": "$1,615.23", "picture": "http://placehold.it/32x32", "age": 28, "eyeColor": "brown", "name": "Ursula French", "gender": "female", "company": "KLUGGER", "email": "ursulafrench@klugger.com", "phone": "+1 (803) 454-3759", "address": "768 Bancroft Place, Layhill, Mississippi, 3591", "about": "Anim proident aliquip non amet. Dolore occaecat non irure cillum excepteur eu officia irure ea enim incididunt. Adipisicing ad esse voluptate duis dolor irure. Non sunt cillum est exercitation labore cillum minim consequat occaecat est aliqua. Ex adipisicing consequat aliqua pariatur est elit deserunt. Proident fugiat aliquip culpa magna ut deserunt incididunt eu enim esse fugiat eu consequat amet. Ad sit do Lorem aliquip enim ea magna.\r\n", "registered": "2014-08-01T00:12:36 +07:00", "latitude": -31.044528, "longitude": -131.432956, "tags": [ "consequat", "enim", "nisi", "cupidatat", "est", "sint", "nostrud" ], "friends": [ { "id": 0, "name": "Mai Hudson" }, { "id": 1, "name": "Erickson Perkins" }, { "id": 2, "name": "Cleveland Armstrong" } ], "greeting": "Hello, Ursula French! You have 8 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a906ae58205e4d302e3", "index": 75, "guid": "f8b68baa-b922-4a5f-9d4a-fa7d9eee543c", "isActive": true, "balance": "$1,500.61", "picture": "http://placehold.it/32x32", "age": 29, "eyeColor": "blue", "name": "Lee Kelley", "gender": "male", "company": "INQUALA", "email": "leekelley@inquala.com", "phone": "+1 (947) 551-3499", "address": "973 Bayard Street, Orovada, North Dakota, 8499", "about": "Ullamco labore fugiat in minim duis duis reprehenderit deserunt eiusmod nostrud cillum laborum. Incididunt occaecat duis esse consectetur voluptate velit pariatur. Pariatur et qui sint anim sunt fugiat ut proident nulla fugiat. Nostrud ea sunt occaecat nulla qui id cupidatat proident ut.\r\n", "registered": "2014-11-01T01:18:21 +07:00", "latitude": -59.393379, "longitude": -110.276914, "tags": [ "sit", "magna", "in", "consequat", "excepteur", "consequat", "Lorem" ], "friends": [ { "id": 0, "name": "Walton Daniels" }, { "id": 1, "name": "Hammond Robbins" }, { "id": 2, "name": "Evangelina Chaney" } ], "greeting": "Hello, Lee Kelley! You have 8 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a902a956e2130c70b9c", "index": 76, "guid": "3f62418d-23f0-4ed2-a76f-51645437223b", "isActive": false, "balance": "$2,477.19", "picture": "http://placehold.it/32x32", "age": 28, "eyeColor": "green", "name": "Miles Poole", "gender": "male", "company": "YOGASM", "email": "milespoole@yogasm.com", "phone": "+1 (866) 412-2294", "address": "744 Sutton Street, Richford, Vermont, 7668", "about": "Nostrud reprehenderit officia officia ex proident sint nulla sint quis duis laborum duis. Anim adipisicing officia officia anim aliquip incididunt culpa duis sint do ullamco ex consectetur. Commodo et tempor eu consequat laboris tempor ipsum magna elit labore consectetur excepteur.\r\n", "registered": "2014-07-20T11:37:28 +07:00", "latitude": 23.618997, "longitude": -80.142779, "tags": [ "magna", "exercitation", "Lorem", "nostrud", "pariatur", "ut", "laborum" ], "friends": [ { "id": 0, "name": "Claudine Gill" }, { "id": 1, "name": "Huff Kramer" }, { "id": 2, "name": "Bryan Doyle" } ], "greeting": "Hello, Miles Poole! You have 10 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90357b2420c0dc0895", "index": 77, "guid": "ef7aa63d-53b9-4e85-ac36-4cfb1afd214a", "isActive": true, "balance": "$1,105.70", "picture": "http://placehold.it/32x32", "age": 39, "eyeColor": "green", "name": "Cohen Clemons", "gender": "male", "company": "EARBANG", "email": "cohenclemons@earbang.com", "phone": "+1 (936) 599-3992", "address": "952 Paerdegat Avenue, Frizzleburg, Rhode Island, 7905", "about": "Consequat exercitation fugiat ut labore. Ad magna sunt dolore magna nulla. Laborum deserunt magna eu incididunt magna occaecat ut sit aliqua nisi culpa dolor ullamco esse. Enim adipisicing proident proident enim qui est ad non. Ex proident sit irure cillum in nostrud veniam amet excepteur voluptate commodo eu eiusmod ullamco.\r\n", "registered": "2014-06-15T00:23:03 +07:00", "latitude": 78.28454, "longitude": 64.170517, "tags": [ "non", "ex", "sit", "ipsum", "esse", "enim", "minim" ], "friends": [ { "id": 0, "name": "Sanchez Wolf" }, { "id": 1, "name": "Trudy Melendez" }, { "id": 2, "name": "Magdalena Hatfield" } ], "greeting": "Hello, Cohen Clemons! You have 3 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90ae5beac7dec2ba78", "index": 78, "guid": "1bccbb43-2801-4c99-a646-001622f3653c", "isActive": false, "balance": "$1,246.07", "picture": "http://placehold.it/32x32", "age": 35, "eyeColor": "blue", "name": "Evelyn Combs", "gender": "female", "company": "BITENDREX", "email": "evelyncombs@bitendrex.com", "phone": "+1 (937) 463-3648", "address": "498 Beayer Place, Caln, Michigan, 637", "about": "Laboris ipsum ea est nisi exercitation adipisicing commodo ea ipsum tempor. Laboris duis sit aliquip reprehenderit id cillum officia. Tempor velit reprehenderit adipisicing dolor ut qui id magna consequat. Fugiat proident sunt sit reprehenderit duis. Eu ipsum adipisicing eu magna cupidatat mollit esse.\r\n", "registered": "2014-06-14T20:28:41 +07:00", "latitude": 13.771679, "longitude": 58.844141, "tags": [ "ex", "irure", "quis", "velit", "deserunt", "mollit", "irure" ], "friends": [ { "id": 0, "name": "Melton Wright" }, { "id": 1, "name": "Letitia Osborn" }, { "id": 2, "name": "Delgado Hebert" } ], "greeting": "Hello, Evelyn Combs! You have 7 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90a58e6a9e15665417", "index": 79, "guid": "6c039c25-e902-4121-9319-aa5e25f09b90", "isActive": true, "balance": "$1,839.17", "picture": "http://placehold.it/32x32", "age": 27, "eyeColor": "blue", "name": "Lakeisha Glover", "gender": "female", "company": "REALMO", "email": "lakeishaglover@realmo.com", "phone": "+1 (962) 444-3749", "address": "259 Homecrest Court, Villarreal, Oklahoma, 5463", "about": "Lorem cupidatat non elit mollit commodo tempor dolore sint qui officia fugiat mollit ex. Ea commodo minim labore commodo commodo sint occaecat eu aute est excepteur labore eiusmod ut. Fugiat voluptate laborum mollit aliqua ea. Ut fugiat culpa do velit non nisi voluptate exercitation. Duis elit velit adipisicing esse.\r\n", "registered": "2014-10-07T01:42:52 +07:00", "latitude": 7.777536, "longitude": -148.148716, "tags": [ "officia", "Lorem", "eu", "eiusmod", "mollit", "duis", "exercitation" ], "friends": [ { "id": 0, "name": "Hodge Snider" }, { "id": 1, "name": "Maritza Gilliam" }, { "id": 2, "name": "Barbra Harding" } ], "greeting": "Hello, Lakeisha Glover! You have 5 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a904e60ffa71e64c330", "index": 80, "guid": "764804ce-2ded-4ab7-aef7-cc638d74a1f6", "isActive": true, "balance": "$3,096.79", "picture": "http://placehold.it/32x32", "age": 36, "eyeColor": "green", "name": "Hall Woodard", "gender": "male", "company": "HOTCAKES", "email": "hallwoodard@hotcakes.com", "phone": "+1 (923) 579-2251", "address": "678 Johnson Avenue, Nescatunga, West Virginia, 5718", "about": "Nulla Lorem proident incididunt nulla amet. Consectetur ea fugiat est adipisicing nisi exercitation ea irure. Id nisi anim culpa incididunt ea laborum. Non est aute anim deserunt ad cupidatat.\r\n", "registered": "2014-07-25T16:17:12 +07:00", "latitude": -72.300952, "longitude": 149.908938, "tags": [ "magna", "fugiat", "laboris", "nulla", "tempor", "consequat", "officia" ], "friends": [ { "id": 0, "name": "Tessa Mccray" }, { "id": 1, "name": "Hendricks Larson" }, { "id": 2, "name": "Cecilia Mooney" } ], "greeting": "Hello, Hall Woodard! You have 1 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a9095c0ba3039bba2a0", "index": 81, "guid": "477bf131-1833-4ceb-a02d-367662e8a0ad", "isActive": true, "balance": "$3,975.04", "picture": "http://placehold.it/32x32", "age": 20, "eyeColor": "brown", "name": "Mccray Holman", "gender": "male", "company": "NETROPIC", "email": "mccrayholman@netropic.com", "phone": "+1 (888) 582-2650", "address": "930 Alton Place, Stouchsburg, Iowa, 8307", "about": "Officia laboris laboris ea magna nulla exercitation ullamco est magna proident cupidatat dolor. Et dolore fugiat nostrud elit in Lorem cillum eu incididunt ullamco irure eiusmod voluptate aliqua. Sint velit veniam nisi in amet incididunt ex et voluptate. Amet laborum sint fugiat nulla dolor adipisicing eiusmod ea. Labore amet nisi et pariatur duis non aliquip ea pariatur sit. Est eu dolore consequat ex quis qui adipisicing minim ea. Proident eiusmod enim irure cillum eu do laborum do voluptate occaecat id consectetur irure dolor.\r\n", "registered": "2014-07-15T14:32:20 +07:00", "latitude": 69.28999, "longitude": 20.24303, "tags": [ "deserunt", "labore", "voluptate", "sint", "occaecat", "non", "sunt" ], "friends": [ { "id": 0, "name": "Ashley Mcintosh" }, { "id": 1, "name": "Augusta Barr" }, { "id": 2, "name": "Page Wiley" } ], "greeting": "Hello, Mccray Holman! You have 8 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a908bfd72d2f3594530", "index": 82, "guid": "e7128ea4-81e3-4888-ba11-4f3670e473ea", "isActive": false, "balance": "$3,306.06", "picture": "http://placehold.it/32x32", "age": 22, "eyeColor": "green", "name": "Sherri Villarreal", "gender": "female", "company": "TERRAGEN", "email": "sherrivillarreal@terragen.com", "phone": "+1 (881) 513-2832", "address": "922 Surf Avenue, Oberlin, Federated States Of Micronesia, 8301", "about": "Occaecat Lorem nostrud sint esse ullamco voluptate cillum sit aliquip sint nostrud. Velit aliqua cupidatat eu adipisicing sunt aute dolore cillum. Voluptate laboris exercitation magna non elit. Excepteur eiusmod enim amet fugiat quis. Anim cillum aute sit magna fugiat ut aliquip incididunt enim.\r\n", "registered": "2014-01-29T03:48:07 +08:00", "latitude": 70.685812, "longitude": -159.885272, "tags": [ "adipisicing", "officia", "laborum", "ipsum", "voluptate", "sint", "cupidatat" ], "friends": [ { "id": 0, "name": "Vinson Berg" }, { "id": 1, "name": "Emily Strong" }, { "id": 2, "name": "Lori Gonzalez" } ], "greeting": "Hello, Sherri Villarreal! You have 1 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90ed7615708c5d1f8e", "index": 83, "guid": "cb7d9a4c-9739-43c8-b75e-0d3cdf462e89", "isActive": false, "balance": "$3,087.41", "picture": "http://placehold.it/32x32", "age": 28, "eyeColor": "brown", "name": "Little Nielsen", "gender": "male", "company": "LUDAK", "email": "littlenielsen@ludak.com", "phone": "+1 (826) 557-2684", "address": "842 Banner Avenue, Gadsden, Kentucky, 3196", "about": "Officia nostrud anim aliqua veniam ut. Non culpa et dolore nostrud elit esse sint mollit anim pariatur id velit irure culpa. Officia irure adipisicing velit velit culpa sunt proident occaecat irure voluptate ullamco. Labore mollit pariatur minim in cillum deserunt. Sint irure ex laborum et minim id ea fugiat excepteur velit veniam velit consequat sint. Culpa anim velit elit officia irure exercitation ex labore est amet. Do do eiusmod ipsum officia veniam laboris irure sint eiusmod non cillum eiusmod.\r\n", "registered": "2014-09-19T15:02:29 +07:00", "latitude": 26.743234, "longitude": -53.174043, "tags": [ "et", "sint", "culpa", "dolore", "ea", "irure", "excepteur" ], "friends": [ { "id": 0, "name": "Gillespie Branch" }, { "id": 1, "name": "Cantu Kent" }, { "id": 2, "name": "Nell Meyer" } ], "greeting": "Hello, Little Nielsen! You have 5 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a909137471ca6b126c8", "index": 84, "guid": "169b0cbf-781c-4b46-8285-e18b3aa6bc0e", "isActive": true, "balance": "$2,853.96", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "green", "name": "Kristi Marquez", "gender": "female", "company": "RONELON", "email": "kristimarquez@ronelon.com", "phone": "+1 (838) 414-3765", "address": "566 Love Lane, Fresno, New Jersey, 5219", "about": "Proident enim commodo ut nisi minim esse eiusmod nisi irure consequat proident voluptate. Culpa ut sunt incididunt sint minim duis excepteur nulla cupidatat ullamco proident nisi ex enim. Qui culpa ex velit do pariatur Lorem dolor ad labore adipisicing magna sunt voluptate dolore. Lorem minim commodo non amet. Nulla reprehenderit consectetur ad nisi voluptate. Ea consectetur deserunt dolore ut. Esse duis consequat reprehenderit cillum commodo consequat ex consectetur do sint velit non deserunt.\r\n", "registered": "2014-02-21T07:19:48 +08:00", "latitude": 38.750345, "longitude": -111.349096, "tags": [ "minim", "minim", "occaecat", "tempor", "dolore", "fugiat", "laborum" ], "friends": [ { "id": 0, "name": "Eddie Soto" }, { "id": 1, "name": "Valencia Serrano" }, { "id": 2, "name": "Sears Richards" } ], "greeting": "Hello, Kristi Marquez! You have 3 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90deb8bb21d9c88b7a", "index": 85, "guid": "58c6180e-8bc6-4ae0-9988-52df23beedac", "isActive": false, "balance": "$2,028.59", "picture": "http://placehold.it/32x32", "age": 39, "eyeColor": "blue", "name": "Callie Sweeney", "gender": "female", "company": "POLARIA", "email": "calliesweeney@polaria.com", "phone": "+1 (999) 576-3446", "address": "278 Gunnison Court, Wakulla, Nevada, 3605", "about": "Minim non eu sint culpa. Non irure ea eiusmod est dolore id culpa laborum ex aliquip et eu. Laborum occaecat labore incididunt et ipsum adipisicing cupidatat eu consectetur reprehenderit quis dolor.\r\n", "registered": "2014-11-06T17:55:38 +08:00", "latitude": 22.578553, "longitude": 70.713617, "tags": [ "veniam", "ad", "aliqua", "id", "quis", "esse", "est" ], "friends": [ { "id": 0, "name": "Cochran Raymond" }, { "id": 1, "name": "Perry Pugh" }, { "id": 2, "name": "Walsh Cummings" } ], "greeting": "Hello, Callie Sweeney! You have 8 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a9092b4caeee42e4083", "index": 86, "guid": "b37a99a1-89ea-4257-bd5c-f8070c6e5d72", "isActive": false, "balance": "$2,333.35", "picture": "http://placehold.it/32x32", "age": 27, "eyeColor": "brown", "name": "Henson Parrish", "gender": "male", "company": "MANTRO", "email": "hensonparrish@mantro.com", "phone": "+1 (983) 409-3702", "address": "749 Malbone Street, Century, California, 6571", "about": "Pariatur nisi magna laboris ipsum ad sint. Exercitation sit id reprehenderit fugiat ea dolor. Duis exercitation voluptate nulla duis enim culpa eiusmod nulla mollit et occaecat eu Lorem.\r\n", "registered": "2014-06-21T02:15:00 +07:00", "latitude": 42.27087, "longitude": 88.230275, "tags": [ "sunt", "excepteur", "veniam", "cillum", "sunt", "consequat", "ullamco" ], "friends": [ { "id": 0, "name": "Dunn Cantrell" }, { "id": 1, "name": "Mendoza Keller" }, { "id": 2, "name": "Josefa Green" } ], "greeting": "Hello, Henson Parrish! You have 7 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a9001009b488b9deadf", "index": 87, "guid": "4a8e033a-6160-44a0-b6f6-e07f11455db9", "isActive": false, "balance": "$2,886.19", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "blue", "name": "Mcgowan Hogan", "gender": "male", "company": "MAGNEMO", "email": "mcgowanhogan@magnemo.com", "phone": "+1 (816) 507-2353", "address": "979 Reed Street, Roberts, Maryland, 9773", "about": "Sunt sint labore aliqua nisi ipsum mollit. Lorem aliquip nisi Lorem eu velit. Laborum reprehenderit minim cillum culpa cupidatat commodo do aute dolore. Sunt ullamco consectetur ex officia anim fugiat quis fugiat laboris est quis officia aliqua pariatur. Adipisicing nulla culpa officia ut reprehenderit ea cupidatat.\r\n", "registered": "2014-05-26T12:57:18 +07:00", "latitude": -24.348796, "longitude": 25.886101, "tags": [ "ex", "ullamco", "non", "ea", "enim", "quis", "ipsum" ], "friends": [ { "id": 0, "name": "Terry Burton" }, { "id": 1, "name": "Cara Estes" }, { "id": 2, "name": "Johanna Dillard" } ], "greeting": "Hello, Mcgowan Hogan! You have 1 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a9021cae47006152c91", "index": 88, "guid": "ebae8f41-1ba7-4f91-8d61-1a1a0d6b515f", "isActive": false, "balance": "$2,168.49", "picture": "http://placehold.it/32x32", "age": 25, "eyeColor": "brown", "name": "Riddle Alvarado", "gender": "male", "company": "INTERLOO", "email": "riddlealvarado@interloo.com", "phone": "+1 (892) 530-2012", "address": "488 Loring Avenue, Homeworth, Washington, 8337", "about": "Officia labore commodo eu consectetur. Consectetur consequat voluptate minim dolor do anim magna deserunt ullamco. Mollit laborum eiusmod veniam velit officia dolore dolore in ex veniam officia eu elit fugiat. Labore non in Lorem nulla irure ea id cupidatat eu consectetur. Tempor non quis eu nulla aliquip proident elit commodo duis laboris laborum eu amet occaecat.\r\n", "registered": "2014-11-13T11:12:08 +08:00", "latitude": 21.377099, "longitude": 128.211659, "tags": [ "ex", "excepteur", "magna", "enim", "magna", "et", "incididunt" ], "friends": [ { "id": 0, "name": "Elisa Vinson" }, { "id": 1, "name": "Peterson Reynolds" }, { "id": 2, "name": "Mason Odonnell" } ], "greeting": "Hello, Riddle Alvarado! You have 1 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a901459251e4d519953", "index": 89, "guid": "6fe0652a-7055-47d0-8b6a-8bc3b3f6a7d0", "isActive": true, "balance": "$1,638.04", "picture": "http://placehold.it/32x32", "age": 29, "eyeColor": "blue", "name": "Stone Maynard", "gender": "male", "company": "CONJURICA", "email": "stonemaynard@conjurica.com", "phone": "+1 (827) 532-2021", "address": "631 Orient Avenue, Homestead, Utah, 8151", "about": "In voluptate voluptate veniam reprehenderit dolor est ut est voluptate dolore occaecat voluptate. Laboris cillum ex aliquip quis dolor qui qui fugiat sit. Veniam magna dolor mollit sint laborum duis id duis aliqua dolore reprehenderit qui et. Irure cupidatat ea sunt anim amet mollit adipisicing id sint deserunt veniam irure. Reprehenderit elit mollit do ex reprehenderit ipsum aliqua qui. Ea non eiusmod officia laboris dolor tempor deserunt elit velit ex aliqua. Duis reprehenderit duis duis elit irure elit dolore dolore.\r\n", "registered": "2014-05-26T12:55:16 +07:00", "latitude": -20.476755, "longitude": 76.876321, "tags": [ "fugiat", "dolore", "consequat", "do", "esse", "consectetur", "anim" ], "friends": [ { "id": 0, "name": "Mckenzie Bartlett" }, { "id": 1, "name": "Villarreal Welch" }, { "id": 2, "name": "Amparo Kelly" } ], "greeting": "Hello, Stone Maynard! You have 5 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a9015625be6710ded3e", "index": 90, "guid": "d079e795-b71e-446b-91f8-6347ca0e2e57", "isActive": false, "balance": "$1,156.54", "picture": "http://placehold.it/32x32", "age": 28, "eyeColor": "blue", "name": "Baird Jones", "gender": "male", "company": "KNEEDLES", "email": "bairdjones@kneedles.com", "phone": "+1 (898) 574-3748", "address": "890 Lancaster Avenue, Falconaire, Wisconsin, 9406", "about": "Officia veniam sunt minim ex tempor labore consequat laborum adipisicing officia. Incididunt enim excepteur anim et do cupidatat magna excepteur culpa. Dolore enim ea excepteur non commodo aliqua nostrud commodo exercitation dolor duis. Consectetur consequat ullamco in esse fugiat pariatur anim mollit aliqua aliquip qui. Voluptate cupidatat ipsum labore aliquip fugiat cillum amet sunt voluptate occaecat occaecat nostrud.\r\n", "registered": "2014-01-22T19:38:09 +08:00", "latitude": -30.096555, "longitude": -119.933566, "tags": [ "occaecat", "qui", "enim", "in", "pariatur", "irure", "officia" ], "friends": [ { "id": 0, "name": "Gail Flynn" }, { "id": 1, "name": "Sanford Harmon" }, { "id": 2, "name": "Noble Chambers" } ], "greeting": "Hello, Baird Jones! You have 3 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a90b147f5343b9ce16b", "index": 91, "guid": "af036dfd-72dd-451e-b93d-6dceea4796c4", "isActive": false, "balance": "$3,703.12", "picture": "http://placehold.it/32x32", "age": 33, "eyeColor": "blue", "name": "Leila Gay", "gender": "female", "company": "ZOXY", "email": "leilagay@zoxy.com", "phone": "+1 (845) 467-2535", "address": "800 Little Street, Troy, Louisiana, 233", "about": "Ea aliqua excepteur duis est velit eiusmod irure est eiusmod non elit. Consequat nostrud elit ullamco minim labore deserunt commodo. Mollit amet duis laboris mollit est ex aliquip. Minim et veniam reprehenderit voluptate aliqua id officia excepteur consequat fugiat non ex eu. Fugiat officia cupidatat pariatur voluptate excepteur in.\r\n", "registered": "2014-08-02T18:50:58 +07:00", "latitude": 59.481938, "longitude": 141.038749, "tags": [ "ipsum", "commodo", "velit", "sit", "aliquip", "ullamco", "nisi" ], "friends": [ { "id": 0, "name": "Conway Summers" }, { "id": 1, "name": "Deirdre Moody" }, { "id": 2, "name": "Curtis Dickerson" } ], "greeting": "Hello, Leila Gay! You have 10 unread messages.", "favoriteFruit": "apple" }, { "_id": "54727a90ffed9e529a6fa6b2", "index": 92, "guid": "7deb0cd2-5374-40c4-a38d-060ef674b2df", "isActive": true, "balance": "$2,980.94", "picture": "http://placehold.it/32x32", "age": 20, "eyeColor": "brown", "name": "Alma England", "gender": "female", "company": "SOLAREN", "email": "almaengland@solaren.com", "phone": "+1 (941) 595-3246", "address": "727 Covert Street, Nutrioso, Florida, 9152", "about": "Commodo quis occaecat voluptate tempor commodo non ipsum quis tempor pariatur elit. Ea fugiat velit dolor ea et occaecat eu ad aute ipsum. In sunt ad reprehenderit duis. Qui deserunt voluptate proident eu officia laborum pariatur incididunt id nisi. Eiusmod adipisicing do pariatur et incididunt aliquip consectetur.\r\n", "registered": "2014-08-08T20:51:29 +07:00", "latitude": 70.990007, "longitude": -119.193428, "tags": [ "irure", "cillum", "incididunt", "nisi", "magna", "ullamco", "ex" ], "friends": [ { "id": 0, "name": "Downs Keith" }, { "id": 1, "name": "Dawn Velazquez" }, { "id": 2, "name": "Deanna Simpson" } ], "greeting": "Hello, Alma England! You have 9 unread messages.", "favoriteFruit": "strawberry" }, { "_id": "54727a9075e4734b622a166a", "index": 93, "guid": "c0adc5f1-039a-4b52-a8cf-0196f3c23129", "isActive": true, "balance": "$2,658.69", "picture": "http://placehold.it/32x32", "age": 21, "eyeColor": "brown", "name": "Lou Rose", "gender": "female", "company": "INFOTRIPS", "email": "lourose@infotrips.com", "phone": "+1 (845) 564-3943", "address": "343 Krier Place, Evergreen, Indiana, 5249", "about": "Tempor ullamco id reprehenderit sunt veniam incididunt laboris. Ea ut officia do velit dolor officia Lorem consectetur nisi velit nisi. Aliquip dolore minim sint deserunt deserunt est.\r\n", "registered": "2014-04-22T07:46:26 +07:00", "latitude": 12.216368, "longitude": 8.875707, "tags": [ "velit", "consectetur", "Lorem", "est", "adipisicing", "ad", "ullamco" ], "friends": [ { "id": 0, "name": "Coleen Foley" }, { "id": 1, "name": "Boone Fitzpatrick" }, { "id": 2, "name": "Elise Osborne" } ], "greeting": "Hello, Lou Rose! You have 5 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a90512b4f65287789e9", "index": 94, "guid": "26d470db-29c3-4c14-894b-5654462385a5", "isActive": false, "balance": "$2,751.47", "picture": "http://placehold.it/32x32", "age": 23, "eyeColor": "blue", "name": "Velez Wong", "gender": "male", "company": "FRANSCENE", "email": "velezwong@franscene.com", "phone": "+1 (821) 577-3492", "address": "197 Huron Street, Hilltop, New Hampshire, 6969", "about": "Minim id ullamco ullamco do proident Lorem commodo tempor ea. Est ut id non proident eiusmod. Deserunt fugiat enim culpa veniam sint.\r\n", "registered": "2014-07-21T05:23:01 +07:00", "latitude": -37.262537, "longitude": 132.661281, "tags": [ "culpa", "non", "elit", "nulla", "laboris", "elit", "ex" ], "friends": [ { "id": 0, "name": "Charmaine Curry" }, { "id": 1, "name": "Clara Randall" }, { "id": 2, "name": "Lauren Jacobs" } ], "greeting": "Hello, Velez Wong! You have 4 unread messages.", "favoriteFruit": "banana" }, { "_id": "54727a9095dc4743a5a84bd7", "index": 95, "guid": "1d1b9166-affc-4d15-ab60-b2edc51f29b4", "isActive": true, "balance": "$1,063.39", "picture": "http://placehold.it/32x32", "age": 22, "eyeColor": "brown", "name": "Catalina Baxter", "gender": "female", "company": "GAZAK", "email": "catalinabaxter@gazak.com", "phone": "+1 (839) 435-3437", "address": "904 Miller Avenue, Callaghan, Kansas, 7896", "about": "Ut ex exercitation commodo sint sint ipsum ea incididunt. Sunt nostrud tempor sint occaecat qui laborum culpa ipsum ullamco veniam est excepteur nostrud. Consequat occaecat id adipisicing esse culpa occaecat. Proident veniam laboris aute minim dolore eiusmod nulla minim elit sint.\r\n", "registered": "2014-05-02T10:13:41 +07:00", "latitude": 18.545597, "longitude": -99.991313, "tags": [ "do", "proident", "reprehenderit", "minim", "cillum", "quis", "esse" ], "friends": [ { "id": 0, "name": "Monique Wilcox" }, { "id": 1, "name": "Hilda Craig" }, { "id": 2, "name": "Leola Higgins" } ], "greeting": "Hello, Catalina Baxter! You have 10 unread messages.", "favoriteFruit": "apple" } ]aeson-1.4.2.0/benchmarks/json-data/dates-fract.json0000755000000000000000000000044200000000000020200 0ustar0000000000000000["2015-02-02T09:10:11.123Z","2015-02-03T09:10:11.000+0000","2014-01-02T09:10:11.333Z","2014-01-03T02:09:12.000-02:00","2013-05-06T07:08:09.444Z","2015-02-02T09:10:11.66+03:00","2015-02-03T09:10:11.66Z","2014-01-02T09:10:11.66-1200","2014-01-03T02:09:12.66Z","2013-05-06T07:08:09.66+00:00"] aeson-1.4.2.0/benchmarks/json-data/dates.json0000755000000000000000000000037600000000000017111 0ustar0000000000000000["2015-02-02T09:10:11Z","2015-02-03T09:10:11+0000","2014-01-02T09:10:11Z","2014-01-03T02:09:12-0300","2013-05-06T07:08:09Z","2015-02-02T09:10:11+04:00","2015-02-03T09:10:11Z","2014-01-02T09:10:11-11:45","2014-01-03T02:09:12Z","2013-05-06T07:08:09+0000"] aeson-1.4.2.0/benchmarks/json-data/example.json0000755000000000000000000000661400000000000017445 0ustar0000000000000000{"web-app": { "servlet": [ { "servlet-name": "cofaxCDS", "servlet-class": "org.cofax.cds.CDSServlet", "init-param": { "configGlossary:installationAt": "Philadelphia, PA", "configGlossary:adminEmail": "ksm@pobox.com", "configGlossary:poweredBy": "Cofax", "configGlossary:poweredByIcon": "/images/cofax.gif", "configGlossary:staticPath": "/content/static", "templateProcessorClass": "org.cofax.WysiwygTemplate", "templateLoaderClass": "org.cofax.FilesTemplateLoader", "templatePath": "templates", "templateOverridePath": "", "defaultListTemplate": "listTemplate.htm", "defaultFileTemplate": "articleTemplate.htm", "useJSP": false, "jspListTemplate": "listTemplate.jsp", "jspFileTemplate": "articleTemplate.jsp", "cachePackageTagsTrack": 200, "cachePackageTagsStore": 200, "cachePackageTagsRefresh": 60, "cacheTemplatesTrack": 100, "cacheTemplatesStore": 50, "cacheTemplatesRefresh": 15, "cachePagesTrack": 200, "cachePagesStore": 100, "cachePagesRefresh": 10, "cachePagesDirtyRead": 10, "searchEngineListTemplate": "forSearchEnginesList.htm", "searchEngineFileTemplate": "forSearchEngines.htm", "searchEngineRobotsDb": "WEB-INF/robots.db", "useDataStore": true, "dataStoreClass": "org.cofax.SqlDataStore", "redirectionClass": "org.cofax.SqlRedirection", "dataStoreName": "cofax", "dataStoreDriver": "com.microsoft.jdbc.sqlserver.SQLServerDriver", "dataStoreUrl": "jdbc:microsoft:sqlserver://LOCALHOST:1433;DatabaseName=goon", "dataStoreUser": "sa", "dataStorePassword": "dataStoreTestQuery", "dataStoreTestQuery": "SET NOCOUNT ON;select test='test';", "dataStoreLogFile": "/usr/local/tomcat/logs/datastore.log", "dataStoreInitConns": 10, "dataStoreMaxConns": 100, "dataStoreConnUsageLimit": 100, "dataStoreLogLevel": "debug", "maxUrlLength": 500}}, { "servlet-name": "cofaxEmail", "servlet-class": "org.cofax.cds.EmailServlet", "init-param": { "mailHost": "mail1", "mailHostOverride": "mail2"}}, { "servlet-name": "cofaxAdmin", "servlet-class": "org.cofax.cds.AdminServlet"}, { "servlet-name": "fileServlet", "servlet-class": "org.cofax.cds.FileServlet"}, { "servlet-name": "cofaxTools", "servlet-class": "org.cofax.cms.CofaxToolsServlet", "init-param": { "templatePath": "toolstemplates/", "log": 1, "logLocation": "/usr/local/tomcat/logs/CofaxTools.log", "logMaxSize": "", "dataLog": 1, "dataLogLocation": "/usr/local/tomcat/logs/dataLog.log", "dataLogMaxSize": "", "removePageCache": "/content/admin/remove?cache=pages&id=", "removeTemplateCache": "/content/admin/remove?cache=templates&id=", "fileTransferFolder": "/usr/local/tomcat/webapps/content/fileTransferFolder", "lookInContext": 1, "adminGroupID": 4, "betaServer": true}}], "servlet-mapping": { "cofaxCDS": "/", "cofaxEmail": "/cofaxutil/aemail/*", "cofaxAdmin": "/admin/*", "fileServlet": "/static/*", "cofaxTools": "/tools/*"}, "taglib": { "taglib-uri": "cofax.tld", "taglib-location": "/WEB-INF/tlds/cofax.tld"}}} aeson-1.4.2.0/benchmarks/json-data/geometry.json0000755000000000000000000020254300000000000017644 0ustar0000000000000000{"geometry": {"type": "Polygon", "coordinates": [[[-0.939359853061118, 51.57401065198471], [-0.939440892477492, 51.57431080772057], [-0.939543636564569, 51.57460846194951], [-0.939564627628489, 51.574822653966265], [-0.939763179055758, 51.575406210178826], [-0.939787182642249, 51.575552991614], [-0.939819571231525, 51.57564949527348], [-0.939851290904264, 51.57571272360808], [-0.939975682132949, 51.57588648747347], [-0.940036822193859, 51.57598774653439], [-0.940072640734852, 51.57606090267849], [-0.940109693338918, 51.576205104339515], [-0.940125502187331, 51.57645611534466], [-0.940118623499009, 51.57662779459441], [-0.94008851367835, 51.57680555827417], [-0.939998015208524, 51.57709787034017], [-0.939928028667517, 51.577252794653916], [-0.939830628174189, 51.57740747134858], [-0.939796941313687, 51.57749078985784], [-0.939785586773343, 51.57754463746666], [-0.939770656147318, 51.57769016804059], [-0.939658154074368, 51.57824573765943], [-0.939485738834128, 51.57883313597966], [-0.93945717030888, 51.579192545519916], [-0.939524336079755, 51.57928306919007], [-0.939540939284811, 51.57931379092206], [-0.939553921057406, 51.579748206813974], [-0.939549110634237, 51.57983088690364], [-0.939520940649101, 51.58004913048237], [-0.93951863934971, 51.58014801827346], [-0.939525037302583, 51.580245186310094], [-0.939540364690294, 51.58033074581249], [-0.939561798495469, 51.58040197377017], [-0.939594984852117, 51.58046431619436], [-0.939708262827559, 51.580619996404984], [-0.939729069878358, 51.58065615108302], [-0.939759224390201, 51.58072476025555], [-0.939813615319267, 51.58093026195459], [-0.939900523550716, 51.58172321441459], [-0.939894144544868, 51.581997403240464], [-0.939910832471369, 51.58208657162566], [-0.940114353648015, 51.582457967531546], [-0.94022333049887, 51.58267475179605], [-0.940267247821581, 51.58277225843995], [-0.94038427828014, 51.583077233742756], [-0.940493362377966, 51.583289522851196], [-0.940571515796737, 51.58340442254201], [-0.940725857371931, 51.58359464061899], [-0.941198340240742, 51.584069167875626], [-0.941335307610427, 51.584261925920295], [-0.941372786463165, 51.5843261048293], [-0.941416540699353, 51.58443080287741], [-0.941461326187118, 51.584739621364996], [-0.941517445876004, 51.5849954910945], [-0.941575869597484, 51.58533860085252], [-0.941574762730556, 51.58538624677686], [-0.941565185406358, 51.58542572382202], [-0.941550002863301, 51.58545795698674], [-0.941515976834126, 51.58549361692739], [-0.941470510606583, 51.585524677868065], [-0.941423872780384, 51.585544039043356], [-0.94131509921043, 51.585566436558274], [-0.941075026707647, 51.58558675057684], [-0.940953181611661, 51.58561262652464], [-0.940734943851404, 51.58568708689612], [-0.940229533088359, 51.585883040066975], [-0.940067635923264, 51.58595531027499], [-0.939917220191166, 51.58603038143916], [-0.939797255285709, 51.586099433232604], [-0.939675637701456, 51.586177461657186], [-0.939611074554604, 51.58622273608784], [-0.939340396866166, 51.586441486256], [-0.93912244296424, 51.58662744303347], [-0.938817233975319, 51.58671729893312], [-0.938661522913105, 51.586771639765516], [-0.938087678078033, 51.586992141762096], [-0.937332636663603, 51.5873072119485], [-0.93492634290483, 51.58836081134952], [-0.934774110277819, 51.58845114531925], [-0.934663126573178, 51.588505886685766], [-0.934565467487243, 51.588546362183585], [-0.934462140700832, 51.588582290320545], [-0.934337145222589, 51.58861892084846], [-0.934213782000904, 51.588647473549656], [-0.934055887760941, 51.588671216763295], [-0.933259701136762, 51.58864510257983], [-0.933213278816969, 51.588716614209304], [-0.932681740160827, 51.588792708227174], [-0.931992471253759, 51.58900853446031], [-0.930629113767652, 51.58946908647644], [-0.928525036745892, 51.59005953842682], [-0.928533690860491, 51.59024394687689], [-0.928456010745829, 51.59047792078815], [-0.928256501298223, 51.5906748158337], [-0.927916132025856, 51.59066181734799], [-0.927671608556404, 51.590624516635486], [-0.927319567022116, 51.59061680481465], [-0.926850285435352, 51.59062240702726], [-0.926313746570405, 51.59066425819173], [-0.925516790702947, 51.59079184232522], [-0.925387133168341, 51.59078076476673], [-0.925293323156809, 51.59077990606886], [-0.925202187496562, 51.59078806346173], [-0.925112304116411, 51.59080432476366], [-0.925036768134577, 51.59082431403807], [-0.924968299737815, 51.59085066215826], [-0.924899640304234, 51.59088510100373], [-0.924851228495836, 51.590917926896914], [-0.924734051019008, 51.59105082982951], [-0.924694255912291, 51.59108553291224], [-0.924446018071168, 51.59126668934789], [-0.924204972773907, 51.59150995377465], [-0.923492520665307, 51.59215352189589], [-0.922775141969353, 51.59288246146081], [-0.922298613651092, 51.59343737077436], [-0.922101568270595, 51.59365046303728], [-0.92149319027045, 51.59422483935332], [-0.921029930136652, 51.59464499018023], [-0.919455791303858, 51.595519790418045], [-0.919908472816787, 51.59560757835559], [-0.919902358174605, 51.595621908790214], [-0.919721503870405, 51.59588190272939], [-0.919513222918683, 51.59614164398608], [-0.919057326435374, 51.59661490568889], [-0.918991959815932, 51.59669253146064], [-0.918853979663433, 51.59690975873926], [-0.91882720841051, 51.59694278142396], [-0.918711889332325, 51.597056812913756], [-0.918614808732714, 51.59713234806153], [-0.918297245740306, 51.59749448485627], [-0.918073703114389, 51.59778825130676], [-0.917853804369843, 51.59811082427763], [-0.917772408698363, 51.59831598343439], [-0.917709563771812, 51.59853030520902], [-0.917692745480418, 51.59856971355161], [-0.917634249201942, 51.59866178857289], [-0.917443039919903, 51.59887043094418], [-0.917335250471836, 51.598971042984616], [-0.916888284039272, 51.599309503426845], [-0.916921110547038, 51.59938623548714], [-0.916942485633783, 51.5995195094582], [-0.916937652924948, 51.599601289122916], [-0.916945811778801, 51.599683188627004], [-0.916964246289877, 51.599757989575366], [-0.917049297107238, 51.59994580090974], [-0.917089705367533, 51.60000731699611], [-0.917171120773417, 51.60010517795964], [-0.91752823274465, 51.60044925531009], [-0.917834023417531, 51.600765883511485], [-0.917913079603466, 51.600902386385464], [-0.918033251654948, 51.60107073894696], [-0.91851090277833, 51.601507638962644], [-0.918694916056997, 51.601663091331545], [-0.919167224655989, 51.60214309940451], [-0.919302231291783, 51.6024167896932], [-0.919552009673002, 51.60266096432073], [-0.919812571846437, 51.60293760761218], [-0.920091738726093, 51.60358667644501], [-0.920208566517809, 51.603592246724574], [-0.920644522919282, 51.60359715428394], [-0.921093152621479, 51.6036156641763], [-0.921168285587618, 51.603613657034074], [-0.921469264587163, 51.6035867495928], [-0.921584776688781, 51.603586911416876], [-0.921718864440287, 51.603595336217005], [-0.921999521996191, 51.60363387995426], [-0.922136050325758, 51.603661209181794], [-0.922248015684399, 51.60368921195661], [-0.922346882036963, 51.60372159023333], [-0.922478548042792, 51.60377135359644], [-0.922605777045377, 51.603825571929555], [-0.92269948345521, 51.60389297005248], [-0.922855181916126, 51.60396453348124], [-0.922908065211369, 51.60398749776935], [-0.923525984356841, 51.604174796116844], [-0.923689774691443, 51.6042095667925], [-0.923842334751645, 51.60423074681459], [-0.924020987014581, 51.604247669912816], [-0.924152253615336, 51.604253368572344], [-0.924379056519158, 51.60424915231234], [-0.924491916632975, 51.60423939614583], [-0.925129396784027, 51.604149022807746], [-0.925308707040747, 51.60413807581467], [-0.925396812395019, 51.604137083863186], [-0.925816640142735, 51.60415261457396], [-0.926339243350925, 51.604157394450915], [-0.926627592983669, 51.60417621577326], [-0.928219342008724, 51.60433911850777], [-0.928540897883304, 51.60435823822504], [-0.928666454251138, 51.6043611822271], [-0.928925123731038, 51.60435275210506], [-0.929272427371303, 51.60432085222454], [-0.929350681081097, 51.604308977474346], [-0.929525019586135, 51.60426381040009], [-0.929730308556221, 51.60419195021111], [-0.929806393059037, 51.60414948374236], [-0.929854111423592, 51.60408517871234], [-0.929877477717563, 51.604012559228565], [-0.929880189120251, 51.60395863398061], [-0.930157001898001, 51.603362311928585], [-0.930233415197893, 51.60324431822904], [-0.930397156019029, 51.60303540508514], [-0.93058677482955, 51.602831223239896], [-0.930747612253953, 51.60268432562219], [-0.931065151604954, 51.602443542878724], [-0.931358556224333, 51.60224659876122], [-0.931494751600125, 51.602165114969594], [-0.931807666849096, 51.601998019766675], [-0.932115553298882, 51.60186055047904], [-0.932344261944379, 51.601774512081256], [-0.932581062209752, 51.601712824287226], [-0.932837650566022, 51.60166929919289], [-0.93304760157037, 51.60164423223924], [-0.933247236692325, 51.60162806284857], [-0.933524572231589, 51.601623388892406], [-0.93367307135076, 51.60163283011416], [-0.933854562367985, 51.601651562386515], [-0.934222940436163, 51.60170526005669], [-0.934582321335698, 51.60177326158339], [-0.935176916778695, 51.60190903449902], [-0.935323237909383, 51.60194992468383], [-0.935449328012611, 51.60199153042619], [-0.935555166022244, 51.60203475076641], [-0.935754957696255, 51.60213547009268], [-0.935920944220561, 51.60219991608389], [-0.936105992086264, 51.60225194623237], [-0.936251123590137, 51.60228203448254], [-0.9362553703842, 51.602285669620606], [-0.935954861941404, 51.603034649313756], [-0.936025513047831, 51.60328615677915], [-0.937604653681525, 51.60374194595848], [-0.937842729718605, 51.6037494948452], [-0.937998245297976, 51.60376798569096], [-0.938149157504488, 51.60379812385097], [-0.938282536474463, 51.60383709493093], [-0.938398403200176, 51.60388400001471], [-0.938549544157173, 51.60396629131982], [-0.938542113846477, 51.60403725821696], [-0.938540670189083, 51.60403724516617], [-0.938690470772444, 51.60417707075241], [-0.93885671831091, 51.60429276731543], [-0.938949655717409, 51.60433227129961], [-0.939171393952754, 51.60435945147724], [-0.939491406642938, 51.60438302306183], [-0.939580914110842, 51.60438383145672], [-0.939698081584302, 51.604374998744255], [-0.939860253923854, 51.60435578228165], [-0.940131370864495, 51.60430877574863], [-0.940224037565311, 51.60429792302206], [-0.941065905352937, 51.604358569226044], [-0.941456261791824, 51.60439985396626], [-0.94172260946072, 51.604433725629356], [-0.942065117075164, 51.604483568721975], [-0.942405972956444, 51.60454238758566], [-0.942542307804962, 51.60457868292929], [-0.942668453620936, 51.60461848302318], [-0.942754322773386, 51.60465162617505], [-0.942930037674105, 51.6047332338937], [-0.94300827141212, 51.60478429141865], [-0.943050642772121, 51.60482513526179], [-0.943095505071305, 51.604883085645305], [-0.943175837511794, 51.60503037259752], [-0.943199044776033, 51.60508812802956], [-0.943264927978451, 51.605360268787045], [-0.94328295289835, 51.6055168856955], [-0.943285556153251, 51.605653582182974], [-0.94327790338372, 51.60573443814757], [-0.943262026480571, 51.60579633763445], [-0.943228365851772, 51.605877858692274], [-0.943092212068021, 51.60614458434088], [-0.943074097962666, 51.60624063192375], [-0.943061365824471, 51.606415854446915], [-0.943044862244347, 51.60650472320056], [-0.943017897594943, 51.606608783583646], [-0.942979591589439, 51.606703750216774], [-0.942905884027612, 51.60683076806164], [-0.942741267849139, 51.60707925374213], [-0.942655006715899, 51.607249318295594], [-0.942630361430127, 51.60731563455148], [-0.942616263944651, 51.607425205688976], [-0.942621958529523, 51.60749089598715], [-0.942636336634899, 51.60755576531453], [-0.942660904708633, 51.607617129739225], [-0.942696981288364, 51.607680396114986], [-0.942747433102709, 51.60774648940761], [-0.942856244975984, 51.6078490746924], [-0.94299552290573, 51.60794563997599], [-0.943040847342192, 51.60798381288104], [-0.943186973159248, 51.608158666884215], [-0.943285889122319, 51.60825217104693], [-0.943509689787491, 51.60844031193307], [-0.94379690141149, 51.609007570967925], [-0.943824004868445, 51.60908424372538], [-0.943831400135399, 51.609201201602104], [-0.943839541642426, 51.60922375393887], [-0.943852077204152, 51.6092436483043], [-0.943874740412961, 51.60926273459518], [-0.943900416430683, 51.60927645299323], [-0.944008015202393, 51.60930709311221], [-0.944074894993692, 51.60934995527111], [-0.944126815315737, 51.60941516198104], [-0.944143328071964, 51.60945037786937], [-0.944150844233183, 51.609499899486615], [-0.944148608042361, 51.60953404761941], [-0.944074023202655, 51.60969882315075], [-0.94403415265091, 51.60986121332522], [-0.944017357658548, 51.60996266784037], [-0.943992023164905, 51.61030771903426], [-0.943965568458423, 51.61051428886229], [-0.943938629028152, 51.61067949277199], [-0.943919488028492, 51.61075754789674], [-0.943885949921455, 51.61083367520212], [-0.943827406881077, 51.61092935920088], [-0.943739589608875, 51.61104186395993], [-0.943638735204063, 51.61115604969767], [-0.943533757272514, 51.611261206608894], [-0.942952360107171, 51.61179457356613], [-0.942768364001955, 51.61194397664764], [-0.942436714102017, 51.61217027698273], [-0.942010518369458, 51.61248743929258], [-0.941742162181165, 51.61266215641604], [-0.941369087685306, 51.61286829880399], [-0.941218061678922, 51.612965845186196], [-0.941055044244821, 51.613082165678385], [-0.940962318642569, 51.61315685920963], [-0.940802313735133, 51.613329853845215], [-0.940532273923746, 51.613638528438315], [-0.940201080800705, 51.61403027273604], [-0.940058816377521, 51.614185443187054], [-0.939985695447699, 51.614286388653916], [-0.939953592073967, 51.614362527773245], [-0.939906859457064, 51.614508669589505], [-0.939802341993177, 51.61490335803689], [-0.939554942446072, 51.615603370947234], [-0.939452722231603, 51.61596121406953], [-0.939421935085161, 51.61604275989804], [-0.939387192811998, 51.616108085051245], [-0.939207265482904, 51.61639149465681], [-0.939036585027605, 51.61671185322904], [-0.938852844916865, 51.61697274874371], [-0.938765881571911, 51.61710953487875], [-0.938636321443754, 51.617400592062225], [-0.93858227703968, 51.617550263869646], [-0.938563060896774, 51.61763101488344], [-0.938557821588965, 51.617793716095726], [-0.938568952285691, 51.6178738422429], [-0.938586194898738, 51.61793963701825], [-0.93864824402059, 51.61806608070808], [-0.938712639101221, 51.61815388154161], [-0.938801458484915, 51.61824729803767], [-0.938902019778203, 51.61833272809444], [-0.939001577491258, 51.61839926656718], [-0.939080060597956, 51.6184404379885], [-0.939144458958051, 51.618466196342986], [-0.93924483456823, 51.61849767462955], [-0.939389936057716, 51.61853135511866], [-0.939533886937889, 51.618552436752374], [-0.939605967169062, 51.618558482633226], [-0.939704125343146, 51.618561167280205], [-0.940011869234288, 51.61855765138392], [-0.940970156479417, 51.61846828865034], [-0.942814559287174, 51.61834913395653], [-0.9433943585448, 51.61832378069166], [-0.943791844341078, 51.61831207069643], [-0.944095316626396, 51.61830580819228], [-0.944345189840605, 51.61830625638639], [-0.944633949874169, 51.618311549349706], [-0.944866264500346, 51.618321729423634], [-0.945069571918896, 51.61833704343469], [-0.945259736594118, 51.618358533188456], [-0.945405071369022, 51.6183823175338], [-0.945538707551366, 51.61841229079249], [-0.945670733169093, 51.618449442740584], [-0.945789657802543, 51.61849097274293], [-0.945898390514756, 51.618536007789324], [-0.946002624502939, 51.61858819565799], [-0.946144975691139, 51.61867849034559], [-0.946290660655923, 51.61881197458077], [-0.946424293873759, 51.618966930407886], [-0.94648587943588, 51.619052004215185], [-0.946597289998464, 51.61923103785771], [-0.946748500992991, 51.619500344620654], [-0.946865282768134, 51.619759451627154], [-0.94692090631825, 51.619852564183816], [-0.946986743272162, 51.619941272483025], [-0.947121992710119, 51.62008904866086], [-0.947221067183078, 51.620177155655796], [-0.947357337089385, 51.62028088174252], [-0.947636341593443, 51.62045871900467], [-0.947732020809812, 51.62050633282523], [-0.947832261440868, 51.62054409665008], [-0.948024909405708, 51.6205835873772], [-0.948272727755043, 51.62061098363029], [-0.94903310890345, 51.62064836261257], [-0.949342820854191, 51.62068530212313], [-0.949548509996597, 51.62072310869445], [-0.949603327033706, 51.620726296510135], [-0.94966121922192, 51.62072141934501], [-0.949725095662238, 51.62070760405018], [-0.949813979767225, 51.620674230793945], [-0.949850856696741, 51.620766275113425], [-0.949938127431095, 51.62092800552347], [-0.95012170684362, 51.62142328688538], [-0.950137689181391, 51.621481875301626], [-0.950144591409982, 51.621558365780544], [-0.950143525838059, 51.62166715485939], [-0.950086848280287, 51.62218276713024], [-0.950081566444785, 51.62234906486587], [-0.950091380322934, 51.6227375905417], [-0.950012857804674, 51.623198158520914], [-0.949963053357781, 51.62366617649237], [-0.94993621019599, 51.62382778558582], [-0.949887611273865, 51.62405573809743], [-0.94981748429385, 51.62434014525264], [-0.949698012983878, 51.6246969431444], [-0.949601071539472, 51.62520410239216], [-0.949519655994856, 51.62547671925938], [-0.949509640700394, 51.62553507516918], [-0.949509569744091, 51.62560071332227], [-0.949517625184728, 51.6256898023632], [-0.949539397678852, 51.62581048474923], [-0.949602831958219, 51.626066413978656], [-0.949622600072634, 51.6262113557699], [-0.949625807500304, 51.62644786389373], [-0.949588359660548, 51.62688092470566], [-0.949587162842075, 51.62718303218221], [-0.949593421398238, 51.627287390862], [-0.949641886384285, 51.62762860642186], [-0.949677564559904, 51.627772791296934], [-0.949732061930258, 51.62791534613564], [-0.949847071945823, 51.62812767746571], [-0.95005020451512, 51.62890367131774], [-0.949860358893705, 51.62924185674224], [-0.949849459019953, 51.62927592739189], [-0.949848649628705, 51.62931098742953], [-0.949857806222275, 51.62935243070728], [-0.949882540677514, 51.62940750068883], [-0.949782851646605, 51.62940750843079], [-0.949684104107472, 51.6296170289926], [-0.949619670293909, 51.62984214210067], [-0.949589348281571, 51.62990391300069], [-0.949478823262764, 51.63006027755304], [-0.949419643728549, 51.63018293320961], [-0.949378577882241, 51.63033452402259], [-0.949364251310331, 51.63051692549393], [-0.949339228920643, 51.63059942443184], [-0.949248633732607, 51.63076855530058], [-0.949181283974238, 51.630869557872636], [-0.949044504574139, 51.63103647701982], [-0.948893935504611, 51.63136242402941], [-0.948761069414249, 51.631297394415576], [-0.948669492362367, 51.63125880992652], [-0.948537801268757, 51.63120547966423], [-0.948447461288637, 51.63117589768262], [-0.948353982967507, 51.63115707745748], [-0.948302104865814, 51.63115121794117], [-0.948079606840815, 51.63115102360314], [-0.947964190602531, 51.63114369566099], [-0.94782149485015, 51.63112892992514], [-0.947725107052886, 51.63111098229264], [-0.947684910040859, 51.63109983219839], [-0.947483021604023, 51.63102069524269], [-0.947447137482345, 51.63101048287877], [-0.947306094892948, 51.630986739722026], [-0.947000710620611, 51.63094713644845], [-0.946674033898238, 51.6308911565172], [-0.946364247153943, 51.63079216747898], [-0.946230490849763, 51.63076579091048], [-0.946172752135344, 51.63076347450912], [-0.94612066649297, 51.630766603772976], [-0.945914796224295, 51.63079712600587], [-0.94583241748209, 51.63079818492752], [-0.945382953779145, 51.63067905708907], [-0.945085984219956, 51.63058827220451], [-0.944883205963743, 51.630547786680644], [-0.944304065189339, 51.630538086402446], [-0.94394898927073, 51.630523204990325], [-0.943611477254356, 51.63049858971805], [-0.943603681926519, 51.6307098224617], [-0.943277115569317, 51.63102249010073], [-0.943359247728321, 51.63109426279834], [-0.942862682241593, 51.631385618132356], [-0.942777562378065, 51.63144239822567], [-0.942532313252267, 51.63161282917167], [-0.942337892928893, 51.63177202827151], [-0.94226606523137, 51.631816339444626], [-0.942197377359527, 51.63184988892168], [-0.942115813951467, 51.631877927416205], [-0.941937005967162, 51.631924871353945], [-0.941512981586086, 51.63201636159427], [-0.94144898217334, 51.6320346671529], [-0.94125937051438, 51.632111184999914], [-0.940790185204025, 51.6323425346351], [-0.940501042462563, 51.632535943664614], [-0.940243238615803, 51.63268647504363], [-0.940131608045529, 51.632764593869275], [-0.939328651391563, 51.63361514453957], [-0.939011405652477, 51.634145481445906], [-0.93882930544315, 51.63451878632893], [-0.93850479164515, 51.63486472819315], [-0.93841585373771, 51.63483694950617], [-0.938308667759282, 51.63503379600045], [-0.938237520065274, 51.63511048065125], [-0.938174497877949, 51.635148574806536], [-0.938097155068085, 51.63518114448376], [-0.938014243480848, 51.63520467214815], [-0.937885103100742, 51.635227781700706], [-0.937899482630853, 51.63529265131639], [-0.937852791962712, 51.635312010611116], [-0.937756752174709, 51.63534081433219], [-0.93768849662133, 51.635355482713884], [-0.937445207164159, 51.63537845841074], [-0.937282775985471, 51.6354039635962], [-0.936848828519967, 51.635485456519916], [-0.935951432459366, 51.63561220386278], [-0.935719677036262, 51.635636179646525], [-0.935420148631615, 51.63565414571281], [-0.935249454884316, 51.63560044703531], [-0.935077590540852, 51.635535048401415], [-0.934717727795324, 51.63535285185533], [-0.934413155884105, 51.635216113905294], [-0.934240481559584, 51.635123731852076], [-0.934130824273522, 51.63505529964683], [-0.934018404467151, 51.63498144729724], [-0.93379675026591, 51.63482118293064], [-0.933679892303923, 51.6347517857655], [-0.933595523374065, 51.63471415412531], [-0.933350473747258, 51.63462740768713], [-0.933261876876166, 51.63458524160035], [-0.933052343088727, 51.63446285066096], [-0.932887751506176, 51.63439571653097], [-0.932638117941304, 51.63431971687678], [-0.932307197466639, 51.63419801967628], [-0.931343887912331, 51.63380981222079], [-0.931071830619705, 51.63376597498289], [-0.930956833347264, 51.63374065092008], [-0.930823331188951, 51.63370346918478], [-0.930701576222194, 51.633658301797674], [-0.930601553796263, 51.63361063468632], [-0.930506119022842, 51.63355221932683], [-0.930386739592999, 51.633467510133144], [-0.930286034494439, 51.633387466714524], [-0.930225334024314, 51.63332666999925], [-0.930188937852857, 51.633276884582266], [-0.930114567680391, 51.63312155131756], [-0.92999324620862, 51.63293521875163], [-0.929900400330813, 51.63282827174111], [-0.929602366751531, 51.6325378240622], [-0.929499431873266, 51.632429885607195], [-0.929341000864788, 51.63222433167361], [-0.929059923028374, 51.631889079042224], [-0.928963213558906, 51.63176231446386], [-0.928896162303318, 51.6316645934755], [-0.928844852932023, 51.631573310156845], [-0.928688841592085, 51.63126527289447], [-0.928672375509884, 51.6312282570475], [-0.928615004479859, 51.631026321392014], [-0.928599834825331, 51.63099561149414], [-0.928552267379979, 51.63092953870757], [-0.928477466267079, 51.630854225808044], [-0.928389580173335, 51.630782390113474], [-0.928294323595921, 51.6307167812279], [-0.928190294396403, 51.63065558801307], [-0.928078937075949, 51.630598823630024], [-0.927494137115659, 51.630339021667446], [-0.927177150281751, 51.63017967221046], [-0.927053070740772, 51.63011110151437], [-0.926922044883713, 51.63003077810591], [-0.926774152423019, 51.6299305188448], [-0.926569924361936, 51.62976860145066], [-0.926465515994788, 51.62966244509719], [-0.926222881099496, 51.62935271335746], [-0.925807083215573, 51.62885077488713], [-0.925685153671251, 51.62869140695483], [-0.925627779063265, 51.628612654944924], [-0.925107975398826, 51.62780494620014], [-0.925039238852947, 51.627717997425265], [-0.924853081975605, 51.627525670804864], [-0.924566287633664, 51.62725149768458], [-0.924018135317732, 51.62666651663998], [-0.9236755124427, 51.62631000590676], [-0.923506463123086, 51.62618886774415], [-0.92325024557972, 51.62602736696645], [-0.923179326155173, 51.62597186775246], [-0.923151247824846, 51.62593744208942], [-0.923025917353845, 51.62573937605691], [-0.922746731858051, 51.625388839233764], [-0.922647729925315, 51.625421200084226], [-0.922438316532782, 51.62517470633975], [-0.922266691774008, 51.62491866820555], [-0.922176577184834, 51.624819832363215], [-0.921722712186069, 51.62440384906751], [-0.921324388846087, 51.624082786314446], [-0.921078577970903, 51.623909687134365], [-0.920860652296657, 51.62377910436709], [-0.920574889783577, 51.623646099345635], [-0.920239048968319, 51.623492851580735], [-0.920014292502202, 51.62371107994427], [-0.919774493442185, 51.623954346092496], [-0.9196346398006, 51.62406455586703], [-0.919395541436808, 51.62427815528515], [-0.919291601043514, 51.624396787581134], [-0.919216417933559, 51.6245210794288], [-0.919153464283899, 51.62467785367513], [-0.919134125069682, 51.624762197061855], [-0.919115026043568, 51.62495803894169], [-0.919049238753011, 51.62517323267518], [-0.919009465019033, 51.625266379578875], [-0.918926652164549, 51.625407685106715], [-0.91889138185638, 51.62549368011671], [-0.918887531877765, 51.62553410703284], [-0.918896749679156, 51.62569334383204], [-0.918892707420934, 51.62574186144837], [-0.918872585162246, 51.62579832350382], [-0.918836276012485, 51.62586722482348], [-0.918763089019947, 51.62596815648993], [-0.918486277330256, 51.626309088016214], [-0.918317614737411, 51.62653682130949], [-0.917905561785174, 51.626975413689514], [-0.917718470441796, 51.62724883363936], [-0.917588198962995, 51.627380709193844], [-0.917518986462533, 51.627435819379606], [-0.917391270738013, 51.627520961779815], [-0.916852199941663, 51.62783249660931], [-0.916708494011591, 51.62822500463541], [-0.916564194300437, 51.62882431452802], [-0.91642514281193, 51.62950639562586], [-0.916399138398425, 51.62974892972319], [-0.916394191477189, 51.62995659074321], [-0.917260413231125, 51.62992321851857], [-0.917422640699178, 51.63166639247214], [-0.91745600722272, 51.63232848375385], [-0.917204699151121, 51.632324368705305], [-0.916787813832452, 51.632356490901394], [-0.916473041038736, 51.63240843616508], [-0.91615824611563, 51.63246127954521], [-0.916096846672852, 51.632491284427324], [-0.916000979824314, 51.632573122584574], [-0.916035541448316, 51.63300234215989], [-0.916058746179642, 51.633180590521675], [-0.916070697537387, 51.63322475979131], [-0.916098260729099, 51.63328076225654], [-0.916287121367376, 51.6334803208717], [-0.916556537933578, 51.63369500893812], [-0.916833436931067, 51.63389897542989], [-0.916980624704717, 51.63396776999687], [-0.917236275570907, 51.634093312450645], [-0.91746761535009, 51.63414759643489], [-0.917599467742121, 51.63382870989293], [-0.917652284973834, 51.63367364156546], [-0.917677934007693, 51.63362802065708], [-0.917745133700401, 51.63359716923921], [-0.917749446066394, 51.633598108140106], [-0.917778102484095, 51.633608262991594], [-0.918084580428658, 51.633662338963], [-0.918258883815884, 51.633684625273325], [-0.918506861448772, 51.63370758977881], [-0.918953829589691, 51.63374767133924], [-0.919245145699076, 51.633771033193085], [-0.919300707852053, 51.63386505735126], [-0.919518444759651, 51.63449197843591], [-0.919277685382965, 51.63446908250848], [-0.919031520477806, 51.63467362436313], [-0.918786199566619, 51.63490335001199], [-0.918632752044247, 51.63503681158531], [-0.918623327237537, 51.63512933850577], [-0.918590569006466, 51.635413172104], [-0.918679820058316, 51.63554886817429], [-0.918329488250497, 51.63557621368664], [-0.918276435808259, 51.635741170885815], [-0.918247752304029, 51.6360358318421], [-0.918226764712395, 51.6364321689642], [-0.918316733144818, 51.63702374696847], [-0.918287332378286, 51.63783452012518], [-0.918306713699577, 51.63835621240955], [-0.918316674296085, 51.639213205140855], [-0.918347519668651, 51.639799742499974], [-0.918322169732004, 51.63995416480466], [-0.918318885834364, 51.64003146244247], [-0.91832686087795, 51.64012145202931], [-0.91837911416845, 51.640354816042915], [-0.918418495846573, 51.64070405330022], [-0.918530296534871, 51.64128953760163], [-0.918512952473936, 51.64147190762244], [-0.918367217757134, 51.64200916315153], [-0.917905817511154, 51.6420255938785], [-0.917874522823857, 51.64200462484983], [-0.9178264462409, 51.64196012300076], [-0.917792775459127, 51.641917552189355], [-0.917773553228143, 51.64187511449974], [-0.917765526057023, 51.64184806570082], [-0.917757894232724, 51.6417436926823], [-0.917749532884981, 51.64142711089125], [-0.917739557627689, 51.64136048104305], [-0.917720785029217, 51.641299165096676], [-0.917688816437575, 51.64124581999865], [-0.917649452591449, 51.641199600032465], [-0.917568381483579, 51.64114490323613], [-0.917433423830488, 51.64098630616572], [-0.917315173490429, 51.64079369481265], [-0.916601390868836, 51.640243120219885], [-0.916329281834837, 51.640018517003504], [-0.916001068304932, 51.63966211774633], [-0.915790319174844, 51.63947044935813], [-0.915502073944432, 51.63913509831614], [-0.915393357554307, 51.63902799332443], [-0.915169439572157, 51.63884339546647], [-0.914312592230519, 51.638234837864296], [-0.913969150495335, 51.63797270396478], [-0.913808719070197, 51.63773204326735], [-0.913709021859032, 51.63761063348384], [-0.913238840648949, 51.637814889395024], [-0.912211197236081, 51.63818662075986], [-0.912057780107923, 51.6382571327065], [-0.911911629192503, 51.63832591344631], [-0.911683066608314, 51.6384568717294], [-0.911571655864317, 51.638583520328496], [-0.910821072629623, 51.63897039510019], [-0.910799442348496, 51.63890815232427], [-0.910457034748542, 51.63884473254883], [-0.90959863753988, 51.63872527019996], [-0.909397970101408, 51.639078576087414], [-0.909048252097236, 51.63925965643008], [-0.909362542404515, 51.63959166868019], [-0.90780907162756, 51.64013291512084], [-0.906217399025103, 51.640939038154336], [-0.905898125060113, 51.64111499768922], [-0.905490384709512, 51.641363863281036], [-0.905329841704473, 51.64154939281248], [-0.905189541321435, 51.641794455508446], [-0.90489098319803, 51.64194992468491], [-0.904781623731163, 51.641990266433346], [-0.904676706895303, 51.64202615370086], [-0.904609919053975, 51.64203901826923], [-0.904237228330216, 51.64209218907456], [-0.90337364044862, 51.64224597828853], [-0.902975191138407, 51.642348358507896], [-0.90292303291413, 51.6422939216028], [-0.902563354675933, 51.64240655335107], [-0.902346768622897, 51.642458479170756], [-0.900824166346957, 51.64291090498388], [-0.900831401206159, 51.64297031739377], [-0.900456613238591, 51.64299018760407], [-0.900019098619797, 51.64297440185565], [-0.899740380937974, 51.64290615240652], [-0.899740489711103, 51.64290165761423], [-0.899316872364163, 51.642849133775655], [-0.899203336991784, 51.642822893203494], [-0.898949902655656, 51.64272520647125], [-0.898783095909619, 51.642631028913314], [-0.898613530793898, 51.64253143027416], [-0.898274969154989, 51.64230885935864], [-0.898003026265053, 51.642080618381755], [-0.897815191816853, 51.641840577798526], [-0.897681652652772, 51.6416262230417], [-0.897327401428262, 51.64091885338664], [-0.896908641882592, 51.6401308512027], [-0.896689777704333, 51.63985994571793], [-0.896199107519928, 51.639356299928586], [-0.896147069948886, 51.63929736526477], [-0.896071667668875, 51.63912941223961], [-0.896034388155249, 51.63881974973283], [-0.89604243255033, 51.63866696761571], [-0.896079873457203, 51.63849378104931], [-0.896158355572289, 51.63829670279626], [-0.896345617779906, 51.63796397393339], [-0.896436991088377, 51.637771512438086], [-0.896627579786388, 51.63748017587825], [-0.896853716275347, 51.63721255114492], [-0.896930541034958, 51.63714313797598], [-0.897052325259386, 51.63706695367484], [-0.897622203318074, 51.636806151704704], [-0.897875248140837, 51.636679946210485], [-0.898045509693898, 51.63657094674504], [-0.898161794997489, 51.63648302058021], [-0.898300490282884, 51.636364732965696], [-0.898761753797595, 51.63587451909389], [-0.898944791614438, 51.635595696246455], [-0.899167964890093, 51.63497197055003], [-0.899296205851425, 51.63450920414348], [-0.899574174378538, 51.633591065468096], [-0.89965934952667, 51.63323579470252], [-0.899745200652967, 51.632733067337156], [-0.89977291429982, 51.632065248259224], [-0.899749317297925, 51.63190587518938], [-0.899730833669311, 51.631833768913715], [-0.899698165870897, 51.631750739777836], [-0.89965967663145, 51.63166945441679], [-0.899415121605884, 51.63126703489972], [-0.899342021743563, 51.6311233827535], [-0.899274678557411, 51.630980683675816], [-0.899221406706553, 51.63067446858268], [-0.899099405183406, 51.63046202142283], [-0.899036514315775, 51.63037421293725], [-0.898969246754073, 51.63028816171176], [-0.898790586842518, 51.63008867047265], [-0.898592010806669, 51.62987640386868], [-0.898497321924236, 51.62978919602221], [-0.898330098469121, 51.62965455114822], [-0.898092642525963, 51.62949676796704], [-0.897090362270362, 51.62894426419184], [-0.896737033461809, 51.62879887742956], [-0.896347312922056, 51.6286648367393], [-0.895633444660858, 51.62837398981453], [-0.895432402381131, 51.628264199314984], [-0.895328663542796, 51.62819308870188], [-0.895257753282041, 51.62813847178444], [-0.895144755729953, 51.62803220648194], [-0.894948239644532, 51.627795675481295], [-0.894944118635818, 51.62766795529761], [-0.894659948504904, 51.62723368184], [-0.894597856997988, 51.62711350846984], [-0.894557343909314, 51.62699713484451], [-0.894469809950127, 51.62655661915932], [-0.894297931114171, 51.625960652861906], [-0.894027819576293, 51.62530531541029], [-0.893931965007508, 51.62514795788166], [-0.893770350871199, 51.62496210671055], [-0.893637995566781, 51.62476124514902], [-0.893507481839104, 51.62466290563429], [-0.892108104715385, 51.62369479825078], [-0.891788795844237, 51.623459800649094], [-0.891922368328922, 51.62337294285213], [-0.891402229815371, 51.62296161084893], [-0.891224922435199, 51.622768414566416], [-0.890089770742591, 51.621276764770215], [-0.890188416566163, 51.62120036880181], [-0.889947380146256, 51.62101466068101], [-0.889727152716072, 51.62086421627997], [-0.889328903798693, 51.62066892786315], [-0.889153387824523, 51.620758083474584], [-0.888409981594066, 51.6201459098237], [-0.888016456293258, 51.619876030785385], [-0.887588982852847, 51.619754191291285], [-0.887143566599165, 51.61965735685454], [-0.88701981132148, 51.61963820065132], [-0.886790744842007, 51.619613550199404], [-0.886603228328527, 51.619602780759124], [-0.886388075513318, 51.619599841439666], [-0.886090409498186, 51.61960421155123], [-0.8851368584814, 51.61967159165818], [-0.883828125903616, 51.61979133688442], [-0.883515973065361, 51.619797361107345], [-0.883424375160774, 51.6198216668555], [-0.883259776293847, 51.619877648328995], [-0.883163867754863, 51.61990101371408], [-0.883044634749604, 51.619815357981636], [-0.881854770311083, 51.61956485587701], [-0.881704286246311, 51.61951666620604], [-0.881635675440863, 51.619487239450166], [-0.881560131370525, 51.619446057447796], [-0.881477720403852, 51.619390423316226], [-0.881374708667671, 51.619291432867335], [-0.880834298239682, 51.61853547912722], [-0.880617549323506, 51.618127888748454], [-0.880388345702594, 51.61816796449318], [-0.879226788544387, 51.6185884841998], [-0.878534686661489, 51.61883184500677], [-0.878385021629543, 51.61898507235025], [-0.878148819949825, 51.61913297697072], [-0.878102165244257, 51.61915051459153], [-0.87804120240859, 51.61916252048532], [-0.877967464227806, 51.619165412606506], [-0.877896924603018, 51.61915574690363], [-0.877839648002824, 51.61913541789456], [-0.877812586845032, 51.61911987344738], [-0.877382402665225, 51.61869944717381], [-0.877261875140598, 51.61866682400238], [-0.877087293116294, 51.618600414623565], [-0.876592344555959, 51.61846350297477], [-0.876408990128558, 51.61845995037962], [-0.876374465270622, 51.61845422502283], [-0.876347205240439, 51.61844677083749], [-0.87630299358364, 51.61842386858449], [-0.876241963569583, 51.618380124514495], [-0.876216636094276, 51.618352907107045], [-0.876152781748704, 51.618131100785114], [-0.876106882196741, 51.61811807314475], [-0.876305643178539, 51.617614643124426], [-0.875030363348109, 51.6174927341714], [-0.874705473526163, 51.61748872204597], [-0.874564111923802, 51.6174810731233], [-0.874279482039409, 51.61730930128958], [-0.874259717266618, 51.61699889890464], [-0.874416434195306, 51.61673604585861], [-0.874423036602998, 51.61652750219062], [-0.870144618410033, 51.61769939147719], [-0.870074692270606, 51.617607003497994], [-0.869665459226217, 51.61768399010514], [-0.869137937974611, 51.617812887107476], [-0.868711126950696, 51.61789959196275], [-0.868460959800069, 51.617969115035805], [-0.866874516019656, 51.61827841686334], [-0.866642434191741, 51.6183175388698], [-0.866517885416195, 51.61833072340073], [-0.866392071649004, 51.61833670224208], [-0.865776872894858, 51.61833166083683], [-0.865633662902087, 51.618340168339564], [-0.865493072065054, 51.618359490991885], [-0.864874419821269, 51.618492883413026], [-0.864829070270363, 51.61851582340227], [-0.8648101986804, 51.61846169086974], [-0.864778464993556, 51.618402038980314], [-0.864733824417545, 51.61833866562683], [-0.864681918741689, 51.61827702035103], [-0.864649512487616, 51.61824433697217], [-0.864492159027339, 51.61812502442397], [-0.864510219622979, 51.618037979732996], [-0.864490008258273, 51.61792179156664], [-0.863791866117017, 51.616668790850674], [-0.863578496430752, 51.61619016667409], [-0.863939572338851, 51.6160749702936], [-0.864141702322916, 51.61602027805823], [-0.864343742093738, 51.615969181278444], [-0.864684853799959, 51.61590144547291], [-0.864287415633653, 51.61573755014447], [-0.864114344880943, 51.615611790807684], [-0.86394143216696, 51.615479738556914], [-0.863424226660599, 51.6150224515856], [-0.863108525016747, 51.61470918210108], [-0.862999136822108, 51.61463618943345], [-0.862947760773663, 51.614611414387845], [-0.862827479233939, 51.614569786988696], [-0.862764327092327, 51.6145538895073], [-0.862690954996651, 51.614542388851355], [-0.862422671693898, 51.614528100870835], [-0.862278208948609, 51.61452939875511], [-0.862025067586916, 51.614544929155834], [-0.861633333855888, 51.61461576315295], [-0.861195617216796, 51.61467715820802], [-0.860991546767721, 51.61469406144679], [-0.860819513274215, 51.61470048511226], [-0.860591345418716, 51.61469917048917], [-0.860366335624517, 51.61468709604235], [-0.860199196800327, 51.61467108707321], [-0.860140174693704, 51.6146633207896], [-0.859842784619867, 51.61460018922178], [-0.85969929013584, 51.61456282905675], [-0.859501466379857, 51.61450336097874], [-0.859306643699259, 51.614439425872085], [-0.859175017225196, 51.614389591981386], [-0.858977780895874, 51.61430675031806], [-0.858172868778381, 51.61392127488393], [-0.856305510909038, 51.61299763777437], [-0.855879431428414, 51.61282624136621], [-0.855413827571698, 51.612676038205095], [-0.855073660630441, 51.61259179657028], [-0.854915624510577, 51.612558784566126], [-0.854688372582268, 51.61252150056368], [-0.854459541396129, 51.6124895957323], [-0.854208848612115, 51.61246556965946], [-0.853413812340721, 51.612436228916096], [-0.851724243907319, 51.61242871018406], [-0.851450292115, 51.612410744947404], [-0.850998615679464, 51.61233888823236], [-0.850653274334699, 51.61223120468302], [-0.850372939737194, 51.61235164666859], [-0.850315593337778, 51.61233490012849], [-0.850193999216673, 51.612288751000705], [-0.850146601119627, 51.612278395984944], [-0.849926028861458, 51.61226274823948], [-0.849854084982468, 51.61225215268858], [-0.849714847013531, 51.612218418620564], [-0.849473435162227, 51.61217019573735], [-0.849372523204365, 51.61216291272777], [-0.849235958321253, 51.61219484371945], [-0.849170915863905, 51.6121969037703], [-0.849112126238191, 51.61218014249445], [-0.8487984760956, 51.61201881385575], [-0.848813983178796, 51.61186251023449], [-0.848805967905994, 51.611779707971536], [-0.848777693193183, 51.61169850541887], [-0.848751669639592, 51.61164250170296], [-0.848740414389996, 51.61163070213332], [-0.848685616135578, 51.61162746733029], [-0.848598109857592, 51.61148993537107], [-0.848561752293423, 51.61144282198033], [-0.848420551583887, 51.61131555337684], [-0.848346143135118, 51.61123120073643], [-0.848017978126262, 51.61073074025961], [-0.84803240586268, 51.61067423405594], [-0.848009203184881, 51.61062095534751], [-0.848010806265629, 51.61061467688053], [-0.848360723390725, 51.61054078070849], [-0.848731046077576, 51.61040234328455], [-0.848814480324059, 51.61035820278237], [-0.848820437461021, 51.610351067821576], [-0.848690278305866, 51.610072847084595], [-0.847947554822518, 51.60900543974003], [-0.847435103308081, 51.6083125448088], [-0.847167998407497, 51.60796823756615], [-0.846186886755928, 51.60662333116728], [-0.845549998419521, 51.605828497430636], [-0.845383680959569, 51.60566770865375], [-0.844840468159951, 51.60522267062485], [-0.84443530295085, 51.60497141150611], [-0.844232696249957, 51.60481835643492], [-0.843486943931864, 51.60416181103064], [-0.84332558359401, 51.60420428093958], [-0.842908147301968, 51.603868373383044], [-0.842663709069561, 51.603714004109015], [-0.842310199280505, 51.603533382087996], [-0.841471682375652, 51.60311958453644], [-0.841215384127901, 51.602977683579475], [-0.840873068217364, 51.60281155440105], [-0.840467421086961, 51.602637605395635], [-0.840268344470896, 51.602516948405764], [-0.840203154295604, 51.60246864832527], [-0.838474883614574, 51.601841924417336], [-0.838334815858368, 51.60178568911777], [-0.838125139250388, 51.60168470536249], [-0.837520083534699, 51.60134782062488], [-0.837365310402971, 51.60124558073874], [-0.837143016970701, 51.6010734356079], [-0.83702163004049, 51.600964332538595], [-0.836879440722268, 51.60082175386177], [-0.836733036616179, 51.60067463738169], [-0.836105420124444, 51.59992210370809], [-0.836001567218505, 51.59980508080317], [-0.835894758960057, 51.59969072601903], [-0.835646409012494, 51.5994652683849], [-0.835572705263831, 51.59941148620318], [-0.835355212679077, 51.599278049641256], [-0.835001490423373, 51.59910819321327], [-0.834666328550124, 51.59894661249016], [-0.834023851532118, 51.59860753956394], [-0.833813699592692, 51.59846967713012], [-0.832219972267628, 51.59727861587006], [-0.831975375091702, 51.59713321406168], [-0.83180286996819, 51.597047874561696], [-0.83156138306724, 51.59695015903964], [-0.831279067386554, 51.596868221715724], [-0.831119729288761, 51.59683246683902], [-0.830996129682144, 51.596810555210986], [-0.830798964246538, 51.59678611250204], [-0.829935838169309, 51.596720865686486], [-0.82967342169104, 51.596707460026586], [-0.829378950815281, 51.59670542343618], [-0.828672101908656, 51.596738836236966], [-0.828529092462618, 51.59674190522934], [-0.828241907711544, 51.596737240965595], [-0.828066024571149, 51.59672739285258], [-0.827854311754233, 51.596707295846045], [-0.827399248313258, 51.59666228882735], [-0.827164974703315, 51.59662128423301], [-0.827063074447412, 51.59659778687348], [-0.826830893268571, 51.59653162563389], [-0.826403126611598, 51.596379885757386], [-0.826320361645679, 51.596342192238744], [-0.826196596762853, 51.596270819297594], [-0.825930135887572, 51.596078429107884], [-0.825702044863314, 51.59590980062742], [-0.825239717878873, 51.595531118786504], [-0.824901250965003, 51.59522021379687], [-0.824412039116432, 51.59470908081712], [-0.8242790371805, 51.59460434384618], [-0.824162427084317, 51.59453573788591], [-0.823734544991122, 51.59433363318264], [-0.822923577534385, 51.59387232098135], [-0.82274220720895, 51.593740122024236], [-0.822758790294358, 51.59343366962803], [-0.822450529949737, 51.592123177421634], [-0.822408018987733, 51.591980681321466], [-0.82236394886053, 51.59184266543808], [-0.822242174035691, 51.59158338051977], [-0.821801765862476, 51.5908065697487], [-0.821372709449585, 51.59009371260957], [-0.821171850754746, 51.58982284235581], [-0.820679968304875, 51.58936291919855], [-0.820417155492676, 51.58914357740762], [-0.82015811620844, 51.5888901042506], [-0.820045903377484, 51.58876399099103], [-0.81975498206002, 51.5884040936899], [-0.819793038416411, 51.58838379523831], [-0.819648800144719, 51.588268149727725], [-0.819147039514258, 51.58763368041164], [-0.818936357700162, 51.58740856531028], [-0.818746726401906, 51.58698404449756], [-0.818744261992127, 51.58691208559554], [-0.818786542624285, 51.586561832259704], [-0.818798419467402, 51.58638211648965], [-0.818772601288344, 51.58593047014409], [-0.818622316220491, 51.585380460186784], [-0.818493730937228, 51.58471737211902], [-0.818460174123387, 51.58461992329734], [-0.818316632401033, 51.58436670899539], [-0.818092592164715, 51.58404524580265], [-0.817774082795079, 51.58341531231479], [-0.817553796530972, 51.58311636524129], [-0.817445537064436, 51.58300557512581], [-0.81689125274485, 51.582562990062094], [-0.816348587477007, 51.58217357091916], [-0.816214612729635, 51.58210837837547], [-0.816144330954904, 51.58209148442308], [-0.816059129697027, 51.58209332267878], [-0.815742672724781, 51.5820523651453], [-0.815217212787465, 51.58194545592985], [-0.815002344756643, 51.58188304223224], [-0.814826435408141, 51.5818210214772], [-0.814485295861823, 51.581730356582035], [-0.81444044205173, 51.581790148477246], [-0.813566956536122, 51.581635656767844], [-0.813282023122958, 51.58154825394594], [-0.813052037332166, 51.581456910143594], [-0.812870182657061, 51.581346270732034], [-0.812790810356639, 51.58129061819263], [-0.812604263086127, 51.581138568732094], [-0.812386509085548, 51.58085492331321], [-0.812249092317067, 51.58070067277682], [-0.812167619564544, 51.58055957666617], [-0.812051961231651, 51.58029045130041], [-0.812042798783181, 51.580254391465495], [-0.812034433182585, 51.580187767648724], [-0.812033188044369, 51.58012481260171], [-0.812058064730261, 51.580000977815104], [-0.81229781440549, 51.579440518478464], [-0.812247901650195, 51.57941753400863], [-0.812446355706805, 51.57916777205078], [-0.81277233113049, 51.578787120404634], [-0.813191367818544, 51.57821318632392], [-0.813476583358647, 51.57767926033569], [-0.81372993476285, 51.57714950751218], [-0.813894821439398, 51.57669169369027], [-0.813998634879093, 51.57614064720803], [-0.814138744624452, 51.57508193151095], [-0.814120940539715, 51.57493428638376], [-0.81419874804071, 51.57321943977239], [-0.814492542549023, 51.572575897898666], [-0.814547744449169, 51.57211787423915], [-0.814549364628156, 51.57200009817749], [-0.81449843948966, 51.57157247390041], [-0.81447275908744, 51.57022974030085], [-0.814470739157426, 51.56964165674743], [-0.814429823166273, 51.56938407823071], [-0.814416473674158, 51.5693425811485], [-0.814362577800679, 51.569251219648685], [-0.81406844007837, 51.5689659058573], [-0.813908308238922, 51.56874308971205], [-0.813853532979604, 51.56863013877188], [-0.81375715260415, 51.56839717647337], [-0.81371284208748, 51.56815934527622], [-0.813667666933597, 51.567788426746645], [-0.813915408556528, 51.567527470860746], [-0.814280993234198, 51.56684059466537], [-0.814704823511867, 51.56613272518902], [-0.814994772052415, 51.56569055892733], [-0.815202529336662, 51.56519091397622], [-0.815219131565213, 51.56505170869626], [-0.815351636137841, 51.564671793906264], [-0.815511116853932, 51.56436408558186], [-0.815565592175225, 51.5642108755608], [-0.815662011458114, 51.564053592855515], [-0.815731002538058, 51.56389693250399], [-0.815762954470268, 51.56377766396064], [-0.815882314039101, 51.56307031436626], [-0.815899206541573, 51.563030920866616], [-0.815918960262566, 51.5629924554096], [-0.816100387305838, 51.56272812828101], [-0.816239061970809, 51.562387838558415], [-0.816351227865814, 51.56217946080997], [-0.816402225233145, 51.562104443964415], [-0.816445731089239, 51.56204014171416], [-0.816755073070336, 51.56173843863565], [-0.81682883069147, 51.5615089920632], [-0.81709149295673, 51.56100450196165], [-0.817126546068515, 51.5610435199925], [-0.817036868291134, 51.56144185218239], [-0.817602599672938, 51.56148891511105], [-0.817650902097453, 51.56129517879352], [-0.81772376875861, 51.56109989153342], [-0.818544773098936, 51.56114952106405], [-0.818940645385275, 51.56112652991029], [-0.819286252234888, 51.56087194248433], [-0.820505192935939, 51.560762809232635], [-0.821152924392013, 51.56109751750433], [-0.821401734784996, 51.56112699167495], [-0.821468077854438, 51.561127657861135], [-0.821837057068471, 51.56108460493917], [-0.822551882107614, 51.56083281445182], [-0.822991148836609, 51.56069335159132], [-0.823298868990794, 51.56056425765945], [-0.823427756279142, 51.560489119484224], [-0.823816316952276, 51.56018999039105], [-0.823841530161624, 51.56016326766115], [-0.823879440321637, 51.5600917131651], [-0.823939663402364, 51.55926686943448], [-0.824000930577316, 51.55924050793579], [-0.823876052668265, 51.55798579953388], [-0.823797968341331, 51.557154174451156], [-0.823813910366727, 51.55698348995032], [-0.824268965579194, 51.556733581409404], [-0.824612742777356, 51.55649154853787], [-0.826344281900068, 51.55484359477631], [-0.826657025878971, 51.55457337099326], [-0.827233265990788, 51.554040521447654], [-0.827929376968602, 51.55344502444081], [-0.828029419518581, 51.553368693973354], [-0.828246668974642, 51.55322159923911], [-0.828485269800709, 51.5530855074047], [-0.828605105979095, 51.55302466009866], [-0.829372820563392, 51.55267264797847], [-0.830416538296143, 51.552300003050114], [-0.830341853307235, 51.55217517181714], [-0.830015969895102, 51.55217192349864], [-0.82991663595149, 51.55216463892005], [-0.829524156953837, 51.55211486704629], [-0.829282415323888, 51.552092673855796], [-0.828838545910614, 51.55207835426137], [-0.828599504055965, 51.55206338004898], [-0.828680519991051, 51.55199764928292], [-0.828534433277995, 51.55195752639793], [-0.828384829125967, 51.55188589688778], [-0.827987906418731, 51.55167242458396], [-0.827957477145366, 51.551621766572], [-0.827834232346298, 51.55159086272802], [-0.827633977763617, 51.551525919798664], [-0.827259642164726, 51.55144395104261], [-0.826879262755715, 51.5513727108443], [-0.826619197529414, 51.551334143723224], [-0.825020961294276, 51.55117248609027], [-0.825087548806697, 51.55099511486544], [-0.825080332863119, 51.55093929339289], [-0.825041927300218, 51.55086247849746], [-0.82502361605882, 51.55078946149474], [-0.825044884876699, 51.55069166368164], [-0.825058487270179, 51.550667521970404], [-0.82509857658956, 51.550622964257876], [-0.825145597538488, 51.55058926609727], [-0.825325151596322, 51.5505056412203], [-0.824909915146001, 51.550164291306395], [-0.82525013660448, 51.550002248032946], [-0.825332063085088, 51.549957209837], [-0.825638185418255, 51.54977504214384], [-0.82578350044032, 51.54967668704559], [-0.825923116734683, 51.54957557721289], [-0.826170603160388, 51.54937393870707], [-0.826371785812396, 51.54917813090106], [-0.826492161334072, 51.549039961540565], [-0.826611394860751, 51.548890091280356], [-0.82670116630089, 51.54876420424681], [-0.826782355507479, 51.54863553380353], [-0.826823019292071, 51.54856850170786], [-0.827062757600335, 51.548106920435835], [-0.827101368877001, 51.54800749719491], [-0.827194201898492, 51.54770629998806], [-0.827307057244965, 51.54741159704493], [-0.827582602426052, 51.54684696658141], [-0.827901482950928, 51.54639156924703], [-0.828226190833503, 51.54604592938406], [-0.828636291311094, 51.545744301711125], [-0.82879259021163, 51.54566673370386], [-0.828904643767125, 51.545627388779295], [-0.829074413403866, 51.54558682127211], [-0.829642313890905, 51.54554213206049], [-0.831137752395514, 51.5457125947128], [-0.831296230672639, 51.545718668970665], [-0.831381409559054, 51.545715021306385], [-0.831520416985355, 51.54569302674314], [-0.831658465956176, 51.54565213966273], [-0.832162223002951, 51.54540897973132], [-0.832259763552867, 51.545373083913695], [-0.832342495362879, 51.54535232675641], [-0.832449690786029, 51.545333611293344], [-0.832560958333776, 51.54532482723805], [-0.832748224427793, 51.54533298427906], [-0.833594396864807, 51.5455158387706], [-0.833803468208608, 51.5455736658201], [-0.834066591719905, 51.54566080332341], [-0.834319302360527, 51.54576042533909], [-0.834632701147966, 51.545911902800114], [-0.834743597643834, 51.54597414830218], [-0.834972095381443, 51.546118487532766], [-0.835101437527799, 51.546192605160904], [-0.835308853525451, 51.54642845092972], [-0.835597379030446, 51.546650714213946], [-0.835675530378703, 51.54669644865621], [-0.835765285050956, 51.54673960061442], [-0.835946924814448, 51.54679895002405], [-0.836738145066418, 51.54693268079673], [-0.837616543696299, 51.54698454508781], [-0.837668585980954, 51.546979665457], [-0.837867989708348, 51.546964555807335], [-0.83797367625272, 51.54694851789646], [-0.838105566972017, 51.54692284834119], [-0.838233315283634, 51.54688994418392], [-0.838329229403341, 51.54686122067977], [-0.838482151664417, 51.546802489195365], [-0.839036827411148, 51.54642762424692], [-0.83955396219585, 51.54605418383688], [-0.840116011657223, 51.54567219327131], [-0.840736658187885, 51.54525391246058], [-0.840941426195899, 51.54514083988849], [-0.841049279937165, 51.54509604683764], [-0.841194847094701, 51.5450426342828], [-0.841299520083949, 51.545009498946165], [-0.841898633062652, 51.544870644649805], [-0.842282244574123, 51.54481328536381], [-0.842762474116396, 51.54475597844143], [-0.843565178344648, 51.54477737891959], [-0.844086979548171, 51.54484366398717], [-0.845732620874625, 51.545006428046236], [-0.847066038668597, 51.54519847249473], [-0.847735465249349, 51.545415455459946], [-0.84773690700669, 51.54541546961599], [-0.848634731053663, 51.54572550693968], [-0.849946581441456, 51.54620234699594], [-0.850255922443757, 51.54628810259981], [-0.850450510421732, 51.5463493547082], [-0.850677807173489, 51.54642891042725], [-0.850994850981171, 51.546552505063595], [-0.852786328510159, 51.547342426670774], [-0.85300310746802, 51.547496506935786], [-0.853571212311598, 51.54778799706584], [-0.854020445083318, 51.54798930492918], [-0.854581807452525, 51.548205193183556], [-0.85478620907829, 51.54827822314386], [-0.854963577157503, 51.54833660211785], [-0.855161244465997, 51.54839068294659], [-0.855663052553423, 51.5485088736389], [-0.856166529832507, 51.54867563412252], [-0.856279761006, 51.54870371304979], [-0.856530960852844, 51.54875111981111], [-0.856804082121709, 51.54878705024175], [-0.857112033920981, 51.54881432744164], [-0.857381573472553, 51.548820548731904], [-0.857549123049589, 51.54881049056259], [-0.857844479857821, 51.548764809719025], [-0.858057604662229, 51.54872012637499], [-0.858337617310588, 51.54865361386837], [-0.858552497890933, 51.54859635820055], [-0.859049392399301, 51.548450127924276], [-0.859439117962245, 51.5483792842905], [-0.859697682244768, 51.54836291412634], [-0.859779823131423, 51.54836551056866], [-0.860170027263243, 51.548390881318824], [-0.860456238387038, 51.54842243448379], [-0.861009536104037, 51.548500639150554], [-0.861158816462501, 51.54852906321894], [-0.861352413335375, 51.54857320311727], [-0.861544411683264, 51.54862362144007], [-0.861731905414109, 51.5486811891874], [-0.862073439754406, 51.548807688741114], [-0.86254414698236, 51.54901726458452], [-0.86282747298222, 51.54916477803516], [-0.863015068128655, 51.549276295417606], [-0.863120154717426, 51.549342054318615], [-0.863285809311142, 51.54946594721784], [-0.863418211576468, 51.54959311456195], [-0.863530092020445, 51.54973357070672], [-0.863653360363745, 51.549937978681236], [-0.863733641061499, 51.550131180181424], [-0.863790336700716, 51.5503448343906], [-0.863824973966162, 51.550691353426465], [-0.863841717303786, 51.55100353042492], [-0.863889686614544, 51.55116225019172], [-0.863971345177536, 51.55135816235228], [-0.864192531443895, 51.5518009005184], [-0.864636908176204, 51.552606367995786], [-0.864885616784935, 51.55304487507487], [-0.864984710926909, 51.55317801261536], [-0.865042267578469, 51.5532415116859], [-0.86524661818949, 51.553434113390985], [-0.866448255146234, 51.55464702695421], [-0.866553639357719, 51.55475954277147], [-0.86713929523259, 51.555454866418074], [-0.86728119491555, 51.55560729781788], [-0.867357192432134, 51.55568356216347], [-0.867846797612144, 51.55612348793147], [-0.867948777192819, 51.5561991033314], [-0.868039688780355, 51.55625572917072], [-0.868162193200772, 51.55631805467487], [-0.868334859667638, 51.55639345221028], [-0.868507816648064, 51.556457162985154], [-0.868686743286876, 51.556512838449954], [-0.868885971532242, 51.55656421341042], [-0.869870431325262, 51.55700170522159], [-0.870538382015661, 51.557289577406756], [-0.87065953954758, 51.55734829060127], [-0.870968323528286, 51.55751940747054], [-0.871084688448939, 51.55759695683154], [-0.871173919806704, 51.55766345498963], [-0.871421843971099, 51.55790412108149], [-0.871517352960249, 51.558008444760674], [-0.871560414081151, 51.55807539786269], [-0.871689483441928, 51.558339198343305], [-0.871715457861831, 51.558455441841], [-0.871819115572425, 51.558871857901316], [-0.872116688986198, 51.559438501590606], [-0.87224925001588, 51.559678057158926], [-0.872395481580982, 51.5598898694294], [-0.872503199025109, 51.56002578071336], [-0.872616797176149, 51.56015725249727], [-0.872767427555836, 51.560307962534345], [-0.873712440787397, 51.560887112412736], [-0.874019840047307, 51.56105730856152], [-0.874413245272104, 51.56124990894107], [-0.875159636577155, 51.56157807024888], [-0.875469862748955, 51.561692540724444], [-0.875618818634067, 51.561736229028845], [-0.87605776549836, 51.56183754414599], [-0.876366373823489, 51.56190074371407], [-0.87668521195865, 51.561958645316366], [-0.876968369886447, 51.56200091867397], [-0.877197163756339, 51.56202468778881], [-0.877516822654725, 51.5620493254706], [-0.878098847659676, 51.56208186543848], [-0.879220205739232, 51.56212315048378], [-0.879742407250114, 51.562124539056946], [-0.8803196812009, 51.56211566057546], [-0.88047709073344, 51.562109069498774], [-0.880781923890852, 51.5620912956137], [-0.881058065229737, 51.56206695318683], [-0.881262135404653, 51.56204012483733], [-0.881418631531618, 51.562011943580096], [-0.881649213834679, 51.56196288783239], [-0.882003250428868, 51.56187993977645], [-0.882376388095226, 51.56178278572967], [-0.882764299497775, 51.56167138432022], [-0.883194585739291, 51.561537905452155], [-0.883498576630078, 51.5614364931922], [-0.883756281221724, 51.56134003501421], [-0.884086956514705, 51.56120920221847], [-0.884407665982054, 51.56107287871968], [-0.885457870533961, 51.5606602434964], [-0.885606584631741, 51.56059601575753], [-0.88578613479336, 51.56050960117672], [-0.88595858283258, 51.56041862303493], [-0.886091760097573, 51.560340759581955], [-0.886521253482028, 51.56006159461465], [-0.886883345687433, 51.559824949307504], [-0.887389733197074, 51.559468282123994], [-0.887580604245187, 51.55927227271282], [-0.887708691217493, 51.559107139161064], [-0.888191015763102, 51.55861266662589], [-0.888192457957821, 51.55861268028735], [-0.888287760756616, 51.55849039596854], [-0.888562664893145, 51.558278995716826], [-0.888677108662246, 51.55814070717499], [-0.888887527216288, 51.55791161122132], [-0.889030158653071, 51.55774121885465], [-0.889203011709727, 51.557514464273005], [-0.88945350380216, 51.55717964382524], [-0.889600043815338, 51.556967026485395], [-0.889736358446423, 51.55670036168757], [-0.889858423154084, 51.55648571413559], [-0.889957478394766, 51.55626815130874], [-0.88999480235023, 51.556157006507235], [-0.890171676314085, 51.5555274577222], [-0.89040150985715, 51.554855248874496], [-0.891496918227321, 51.55316795557777], [-0.892148150167392, 51.55212836271704], [-0.892302414411729, 51.5517746441604], [-0.892679622502675, 51.55097074336506], [-0.892968782461996, 51.55046633574481], [-0.893655961353766, 51.54930928124159], [-0.894173495307085, 51.548604708475054], [-0.894625223197592, 51.54805597035748], [-0.895275002004698, 51.547308578527485], [-0.895581553072133, 51.54691762432374], [-0.89567259455686, 51.54679079793778], [-0.895853734572665, 51.54651645501248], [-0.896746527292651, 51.54508077321264], [-0.896901839906062, 51.544860136456265], [-0.897255891587921, 51.54494888564188], [-0.898115394177492, 51.545187148067974], [-0.89822539056202, 51.54523044209882], [-0.898280925208036, 51.54525973711452], [-0.898317695099433, 51.54528975512979], [-0.898473190139101, 51.54530020648797], [-0.899619101095523, 51.54544313546729], [-0.901006352145532, 51.54562517973134], [-0.901825064903737, 51.54570208025918], [-0.903152296119515, 51.54586195719927], [-0.903215411109321, 51.54587603470979], [-0.903297183099556, 51.545893883241035], [-0.903017403675823, 51.54655396139701], [-0.902616538461231, 51.54745118838641], [-0.902395351374664, 51.54801290343283], [-0.902224993241029, 51.54837997226972], [-0.902166365216381, 51.54859882282856], [-0.902146545476892, 51.54876318664974], [-0.902208891983797, 51.54892921824649], [-0.902230894835185, 51.549033728477525], [-0.902380735585514, 51.54999904656443], [-0.902673692529055, 51.551610411429984], [-0.902806620567669, 51.55250003963136], [-0.902816651036337, 51.55268266601908], [-0.902804979597758, 51.55292803179951], [-0.902756997764027, 51.55318384821566], [-0.902654701329301, 51.55353896524768], [-0.902427419928527, 51.55423280167036], [-0.901847751389036, 51.555843197130926], [-0.901770133963284, 51.556011515784924], [-0.90172081219273, 51.556082988265544], [-0.902203201151337, 51.55617741874876], [-0.906010818638152, 51.55679743475821], [-0.906204734572883, 51.556771367660915], [-0.906311884484255, 51.55675438267928], [-0.906358975073264, 51.55689599188705], [-0.90638590166065, 51.55691602462513], [-0.906615524939952, 51.55696492104195], [-0.907278267614382, 51.55705831304524], [-0.907858939004531, 51.55720578727805], [-0.908174621569804, 51.5572752632291], [-0.908339760107985, 51.55730647205926], [-0.908420198492941, 51.557320707807335], [-0.908923514869315, 51.557385632424236], [-0.909322889103033, 51.5574540848968], [-0.909506497855653, 51.557497152980005], [-0.909658336207082, 51.557541723987356], [-0.909754316957776, 51.55756959081508], [-0.909871264277585, 51.557625526703404], [-0.91002439519459, 51.55767640345812], [-0.91014009429463, 51.557724234915874], [-0.910363938659539, 51.55783421414451], [-0.910769828656022, 51.55805288423369], [-0.910899633150579, 51.55817457810929], [-0.911134211672749, 51.55843931338367], [-0.911191431662737, 51.558519870694006], [-0.911262279817118, 51.55863382382822], [-0.911345597527786, 51.558829717406], [-0.911347039740573, 51.55882973078292], [-0.911354152248679, 51.55895478193117], [-0.911501156990394, 51.55932300828838], [-0.911744284152759, 51.55977395051585], [-0.911784714781588, 51.55983277167005], [-0.911848028397377, 51.559899897522016], [-0.911951124589094, 51.55999256899618], [-0.912043240814804, 51.56006176008463], [-0.912343203354435, 51.560247072388215], [-0.91252735254784, 51.560389049785144], [-0.912663001694362, 51.56050809825428], [-0.913644040185922, 51.561715780647766], [-0.914729932802775, 51.56149024267299], [-0.915936249212879, 51.561720788632314], [-0.917099342153636, 51.56255696600573], [-0.917716153850379, 51.56209778262442], [-0.918510926061236, 51.561494569835055], [-0.919190082061234, 51.56187308324347], [-0.919265061021478, 51.56187467281339], [-0.919319677161742, 51.561883268238525], [-0.919395565855925, 51.56190734542486], [-0.919450182060758, 51.561915940789575], [-0.919451624375034, 51.56191595406745], [-0.919612764956992, 51.561873377936905], [-0.919684473323871, 51.562134798108005], [-0.919731696029427, 51.56227280618616], [-0.919795125391412, 51.562396576626476], [-0.919877773921036, 51.56250074208832], [-0.920024454979703, 51.56264236275641], [-0.920273793481437, 51.562835281288635], [-0.920455811890565, 51.56300779833283], [-0.92054707457537, 51.56311384087594], [-0.920622684574115, 51.56321074767881], [-0.920768557091237, 51.56344767224896], [-0.920815933327546, 51.56357938704838], [-0.92087756775181, 51.56365728255545], [-0.920897207761338, 51.56368084160506], [-0.920950783915168, 51.5637334861553], [-0.921113636188415, 51.563862665653886], [-0.921195103215065, 51.56395602921301], [-0.921351882125165, 51.56422002842434], [-0.921395592904906, 51.56432383493418], [-0.921420893006769, 51.56441308549212], [-0.921438619701684, 51.56451755238376], [-0.921413985191466, 51.56464410933019], [-0.92167481147157, 51.56453500840272], [-0.923479752756133, 51.56373602685831], [-0.924155377789785, 51.5634113259626], [-0.924873111301507, 51.56399247344971], [-0.924951149378637, 51.56404803772923], [-0.925274524870032, 51.56428388466152], [-0.92664770764064, 51.56515336065692], [-0.927393574791524, 51.56558368874587], [-0.927927453464337, 51.5659491340051], [-0.92835633038721, 51.56599441223158], [-0.928244524844939, 51.56725223174753], [-0.928125342518282, 51.56741209518939], [-0.9281054698832, 51.56745956981058], [-0.927839528670842, 51.568092855254655], [-0.93052584537502, 51.568532778436946], [-0.930434864440691, 51.56872077542371], [-0.930290537945866, 51.568968530677175], [-0.93032458943141, 51.568993118606556], [-0.930407160146686, 51.56904062792432], [-0.930494248489543, 51.56908008580425], [-0.93056005729139, 51.5691040638391], [-0.930644619283805, 51.56912821268005], [-0.930755210497826, 51.569149901051155], [-0.931002865082897, 51.56917193845677], [-0.931506345671459, 51.5692367670135], [-0.9319179887186, 51.56928007686346], [-0.93222706378822, 51.569328746497334], [-0.932389335623021, 51.56936169347699], [-0.932508352034028, 51.56939334769875], [-0.932608510110525, 51.56942932617174], [-0.932871163025979, 51.56955040480943], [-0.933086053531851, 51.569616199317096], [-0.933414865356232, 51.569684826955594], [-0.93386895042082, 51.56976448240679], [-0.934635570791928, 51.5700537823344], [-0.934785550106084, 51.57011898456062], [-0.934985327167408, 51.57021431104797], [-0.935122135234023, 51.5702874858722], [-0.935333952219633, 51.570423383659445], [-0.935683954424458, 51.570697207984594], [-0.935948857561102, 51.57084617434456], [-0.936321009353978, 51.57109861741231], [-0.936776166293208, 51.57138058458356], [-0.936874033955222, 51.57139136186155], [-0.937185388877335, 51.57140497135624], [-0.937358713203379, 51.57139754881963], [-0.937474500211682, 51.571382411871916], [-0.937604964789291, 51.57135661760672], [-0.938082770631526, 51.571224267138255], [-0.938303744516349, 51.57115343316592], [-0.938622419406116, 51.57103852370375], [-0.938583754985448, 51.57127375671787], [-0.938615426417796, 51.5714008261012], [-0.938651384040882, 51.57152973256723], [-0.938810396393867, 51.572013125409214], [-0.938917102284257, 51.5723881447753], [-0.938977920287056, 51.572564931845086], [-0.939147081147104, 51.57298457478389], [-0.93921529881351, 51.57340150695511], [-0.939295227462625, 51.57374930879435], [-0.939359853061118, 51.57401065198471]]]}} aeson-1.4.2.0/benchmarks/json-data/integers.json0000755000000000000000000001377300000000000017636 0ustar0000000000000000[1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 4, 4, 4, 4, 5, 5, 5, 6, 6, 7, 7, 7, 8, 9, 9, 10, 10, 11, 12, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 23, 24, 26, 27, 29, 31, 33, 35, 37, 39, 42, 44, 47, 50, 53, 56, 60, 63, 67, 72, 76, 81, 86, 91, 96, 102, 109, 115, 122, 130, 138, 146, 155, 165, 175, 186, 197, 209, 222, 236, 250, 266, 282, 299, 318, 337, 358, 380, 403, 428, 454, 482, 511, 543, 576, 611, 649, 688, 730, 775, 823, 873, 926, 983, 1043, 1107, 1175, 1247, 1323, 1404, 1490, 1582, 1679, 1781, 1890, 2006, 2129, 2259, 2398, 2544, 2700, 2865, 3041, 3227, 3425, 3634, 3857, 4093, 4343, 4609, 4891, 5191, 5509, 5846, 6204, 6583, 6986, 7414, 7868, 8349, 8860, 9403, 9978, 10589, 11237, 11925, 12655, 13430, 14252, 15124, 16050, 17032, 18075, 19181, 20355, 21601, 22923, 24326, 25815, 27396, 29072, 30852, 32740, 34744, 36871, 39128, 41523, 44064, 46762, 49624, 52661, 55884, 59305, 62935, 66787, 70875, 75213, 79817, 84702, 89887, 95389, 101227, 107423, 113998, 120976, 128381, 136239, 144578, 153427, 162818, 172784, 183360, 194583, 206493, 219132, 232545, 246778, 261883, 277912, 294923, 312975, 332131, 352460, 374034, 396928, 421223, 447005, 474365, 503400, 534212, 566911, 601610, 638433, 677511, 718980, 762987, 809688, 859247, 911840, 967652, 1026880, 1089734, 1156434, 1227217, 1302333, 1382046, 1466638, 1556408, 1651673, 1752769, 1860052, 1973902, 2094721, 2222934, 2358996, 2503385, 2656613, 2819219, 2991777, 3174898, 3369227, 3575451, 3794297, 4026539, 4272995, 4534536, 4812086, 5106625, 5419191, 5750889, 6102889, 6476435, 6872845, 7293518, 7739939, 8213686, 8716429, 9249944, 9816115, 10416939, 11054539, 11731166, 12449207, 13211198, 14019829, 14877955, 15788605, 16754994, 17780533, 18868844, 20023768, 21249383, 22550016, 23930257, 25394980, 26949356, 28598872, 30349352, 32206975, 34178300, 36270285, 38490317, 40846232, 43346349, 45999492, 48815029, 51802899, 54973651, 58338478, 61909260, 65698602, 69719882, 73987297, 78515911, 83321713, 88421668, 93833782, 99577160, 105672079, 112140056, 119003924, 126287916, 134017747, 142220706, 150925751, 160163614, 169966908, 180370243, 191410345, 203126189, 215559137, 228753081, 242754599, 257613123, 273381107, 290114218, 307871529, 326715729, 346713346, 367934976, 390455540, 414354543, 439716356, 466630515, 495192035, 525501749, 557666661, 591800322, 628023236, 666463282, 707256166, 750545902, 796485316, 845236589, 896971830, 951873682, 1010135966, 1071964368, 1137577163, 1207205986, 1281096650, 1359510014, 1442722903, 1531029087, 1624740315, 1724187420, 1829721484, 1941715077, 2060563573, 2186686548, 2320529259, 2462564214, 2613292844, 2773247272, 2942992191, 3123126858, 3314287206, 3517148098, 3732425698, 3960880011, 4203317554, 4460594215, 4733618266, 5023353573, 5330822998, 5657112012, 6003372524, 6370826950, 6760772526, 7174585891, 7613727944, 8079749004, 8574294281, 9099109685, 9656047991, 10247075377, 10874278366, 11539871197, 12246203633, 12995769265, 13791214310, 14635346955, 15531147272, 16481777734, 17490594386, 18561158687, 19697250088, 20902879371, 22182302812, 23540037202, 24980875800, 26509905246, 28132523526, 29854459026, 31681790754, 33620969802, 35678842122, 37862672691, 40180171161, 42639519077, 45249398761, 48019023960, 50958172379, 54077220194, 57387178688, 60899733121, 64627283986, 68582990784, 72780818484, 77235586822, 81963022620, 86979815309, 92303675844, 97953399235, 103948930895, 110311437058, 117063379497, 124228594829, 131832378662, 139901574895, 148464670491, 157551896043, 167195332496, 177429024407, 188289100133, 199813899374, 212044108527, 225022904322, 238796106249, 253412338321, 268923200725, 285383451995, 302851202324, 321388118716, 341059642687, 361935221296, 384088552321, 407597844432, 432546093294, 459021374572, 487117154867, 516932621682, 548573033590, 582150091830, 617782334651, 655595555791, 695723248569, 738307077168, 783497376747, 831453684183, 882345301285, 936351892486, 993664119121, 1054484312524, 1119027188325, 1187520604468, 1260206365627, 1337341076854, 1419197049486, 1506063262491, 1598246382662, 1696071847252, 1799885012878, 1910052374747, 2026962860500, 2151029203266, 2282689398739, 2422408251457, 2570679015712, 2728025136906, 2895002099486, 3072199387991, 3260242568131, 3459795495242, 3671562657914, 3896291665080, 4134775885316, 4387857247705, 4656429214122, 4941439933460, 5243895588908, 5564863950114, 5905478142772, 6266940648935, 6650527552175, 7057593042589, 7489574197539, 7947996055022, 8434476997558, 8950734465625, 9498591020797, 10079980779998, 10696956243580, 11351695541337, 12046510122031, 12783852913581, 13566326982715, 14396694724673, 15277887615381, 16213016560543, 17205382878181, 18258489953389, 19376055606456, 20562025218016, 21820585657560, 23156180064488, 24573523533875, 26077619762337, 27673778712750, 29367635360200, 31165169585327, 33072727285306, 35097042776985, 37245262571278, 39524970602741, 41944215003394, 44511536515321, 47235998642351, 50127219647252, 53195406507421, 56451390948928, 59906667686130, 63573435001862, 67464637811456, 71594013362620, 75976139732519, 80626487293267, 85561473327514, 90798519986944, 96356115798305, 102253880934088, 108512636478302, 115154477931865, 122202853217119, 129682645456833, 137620260819954, 146043721744222, 154982765864743, 164468950997792, 174535766550465, 185218751749486, 196555621106568, 208586397563259, 221353553785311, 234902162105402, 249280053643550, 264537987166964, 280729828285480, 297912739615178, 316147382581544, 335498131574595, 356033301212013, 377825387512598, 400951323831468, 425492752460545, 451536312853150, 479173947490266, 508503226468250, 539627691953919, 572657223723034, 607708427072674, 644905044476938, 684378392439283, 726267825083707, 770721226121430, 817895530929871, 867957280587026, 921083209817197, 977460870923688, 1037289295911185, 1100779699135317, 1168156222959992, 1239656729054927, 1315533638126921, 1396054821049394, 1481504544536185, 1572184474698156, 1668414742025481, 1770535071555377, 1878905982215138, 1993910059574563, 2115953306501003, 2245466576485316, 2382907094698829, 2528760072151156, 2683540418647385, 2847794560591953] aeson-1.4.2.0/benchmarks/json-data/jp10.json0000755000000000000000000003520700000000000016564 0ustar0000000000000000{"results":[{"from_user_id_str":"2458313","profile_image_url":"http://a2.twimg.com/profile_images/1203653060/fure091226_normal.png","created_at":"Thu, 27 Jan 2011 20:30:04 +0000","from_user":"19princess","id_str":"30724239224995840","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6d77\u6674\u300c\u672c\u65e5\u306e\u6771\u4eac\u306e\u304a\u5929\u6c17\u306f\u6674\u6642\u3005\u66c7\u3067\u3057\u3087\u3046\u3002\u6700\u9ad8\u6c17\u6e29\u306f8\u5ea6\u3001\u6700\u4f4e\u6c17\u6e29\u306f1\u5ea6\u3067\u3059\u3002\u3042\u306a\u305f\u306e\u4eca\u65e5\u306e\u4eba\u751f\u306b\u3068\u3073\u3063\u304d\u308a\u306e\u304a\u5929\u6c17\u3092\u2665\u300d","id":30724239224995840,"from_user_id":2458313,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://babyprincess.sakura.ne.jp/about/" rel="nofollow">\u5929\u4f7f\u5bb6\u306e\u88cf\u5c71</a>"},{"from_user_id_str":"66578965","profile_image_url":"http://a0.twimg.com/profile_images/1183763267/fossetta_normal.png","created_at":"Thu, 27 Jan 2011 20:00:04 +0000","from_user":"Fossetta_Tokyo","id_str":"30716689779785729","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u304a\u306f\u3088\u3046\u3054\u3056\u3044\u307e\u3059!!\u6771\u4eac\u90fd\u3001\u672c\u65e5\u306e\u304a\u5929\u6c17\u306f\u6674\u6642\u3005\u66c7\u3002\u6700\u9ad8\u6c17\u6e298\u5ea6\u3001\u6700\u4f4e\u6c17\u6e291\u5ea6\u3002\u6771\u4eac\u5730\u65b9\u3067\u306f\u3001\u7a7a\u6c17\u306e\u4e7e\u71e5\u3057\u305f\u72b6\u614b\u304c\u7d9a\u3044\u3066\u3044\u307e\u3059\u3002\u706b\u306e\u53d6\u308a\u6271\u3044\u306b\u6ce8\u610f\u3057\u3066\u4e0b\u3055\u3044\u3002\u4f0a\u8c46\u8af8\u5cf6\u3068\u5c0f\u7b20\u539f\u8af8\u5cf6\u306b\u306f\u3001\u5f37\u98a8\u3001\u6ce2\u6d6a\u3001\u4e7e\u71e5\u3001\u971c\u306e\u6ce8\u610f\u5831\u3092\u767a\u8868\u4e2d\u3067\u3059\u3002","id":30716689779785729,"from_user_id":66578965,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://bit.ly/Fossetta" rel="nofollow">\u30d5\u30a9\u30bb\u30c3\u30bf ver.3.1.1</a>"},{"from_user_id_str":"104041146","profile_image_url":"http://a2.twimg.com/profile_images/863965118/001jwatokyo_normal.jpg","created_at":"Thu, 27 Jan 2011 19:44:33 +0000","from_user":"jwa_tokyo","id_str":"30712787537756160","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6c17\u8c61\u5e81\u304b\u3089\u6771\u4eac\u306e\u5929\u6c17\u4e88\u5831\u304c\u767a\u8868\u3055\u308c\u307e\u3057\u305f\u3000\u305d\u306e\u5929\u6c17\u4e88\u5831\u3092\u3053\u3053\u3067\u3064\u3076\u3084\u3053\u3046\u304b\u306a\u3041\uff5e\uff1f\u3000\u8003\u3048\u4e2d\u3000\u307e\u3066\u6b21\u53f7\uff08\u7b11","id":30712787537756160,"from_user_id":104041146,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.docodemo.jp/twil/" rel="nofollow">Twil2 (Tweet Anytime, Anywhere by Mail)</a>"},{"from_user_id_str":"144500192","profile_image_url":"http://a3.twimg.com/a/1294874399/images/default_profile_3_normal.png","created_at":"Thu, 27 Jan 2011 18:59:33 +0000","from_user":"kyo4to4","id_str":"30701462774358016","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u90fd \u516b\u4e08\u5cf6 - \u4eca\u65e5\u306e\u5929\u6c17\u306f\u30fb\u30fb\u30fb\u66c7\u306e\u3061\u6674\u3067\u3059\u306e\uff01","id":30701462774358016,"from_user_id":144500192,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/kyo4to4" rel="nofollow">lost-sheep-bot</a>"},{"from_user_id_str":"165724582","profile_image_url":"http://a0.twimg.com/profile_images/1222842347/163087_1256281064506_1753997852_484926_2761052_n_normal.jpg","created_at":"Thu, 27 Jan 2011 17:39:06 +0000","from_user":"Rifqi_19931020","id_str":"30681213748387840","metadata":{"result_type":"recent"},"to_user_id":113796067,"text":"@CHLionRagbaby \u30b1\u30f3\u3061\u3083\u3093\u3001\u671d\u4eca\u307e\u3067\u306e\u81ea\u5206\u306e\u30db\u30fc\u30e0\u30a8\u30ea\u30a2\u304b\u3089\u307e\u3060\u975e\u5e38\u306b\u5bd2\u3044\u3068\u96e8\u304c\u964d\u3063\u3066\u3044\u305f..\u3069\u306e\u3088\u3046\u306b\u73fe\u5728\u306e\u6771\u4eac\u306e\u5929\u6c17\uff1f","id":30681213748387840,"from_user_id":165724582,"to_user":"CHLionRagbaby","geo":null,"iso_language_code":"ja","to_user_id_str":"113796067","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"120911929","profile_image_url":"http://a0.twimg.com/profile_images/772435076/20100312___capture2_normal.png","created_at":"Thu, 27 Jan 2011 17:28:30 +0000","from_user":"Cirno_fan","id_str":"30678546020040705","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4eca\u65e5\u306e\u6771\u4eac\u306e\u5929\u6c17\u306f\u3001\u66c7\u6642\u3005\u6674\u3067\u6700\u9ad8\u6c17\u6e29\u306f8\u2103\uff01 \u6700\u4f4e\u6c17\u6e29\u306f2\u2103\u3060\u3063\u305f\u3088\uff01 RT @mimi22999 \uff08\uff65\u2200\uff65\uff09\uff4c\u3001\u865a\u5f31\u306a\u8005\u306b\u3068\u3063\u3066\u3001\u6717\u3089\u304b\u306a\u9854\u306f\u4e0a\u5929\u6c17\u3068\u540c\u3058\u304f\u3089\u3044\u3046\u308c\u3057\u3044\u3082\u306e\u3060\u3002\u30d5\u30e9\u30f3\u30af\u30ea\u30f3 #tenki #bot","id":30678546020040705,"from_user_id":120911929,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://blog.livedoor.jp/fairycirno/archives/34686.html" rel="nofollow">\u5e7b\u60f3\u90f7 \u9727\u306e\u6e56</a>"},{"from_user_id_str":"65976527","profile_image_url":"http://a0.twimg.com/profile_images/452810990/little_italies_____normal.jpg","created_at":"Thu, 27 Jan 2011 17:00:03 +0000","from_user":"heta_weather01","id_str":"30671388754845696","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3010\u30d8\u30bf\u5929\u3011Tere hommikust.\u30a8\u30b9\u30c8\u30cb\u30a2\u3067\u3059\u3002\u4eca\u65e5\u306e\u6771\u4eac\u306e\u5929\u6c17\u306f\u6674\u6642\u3005\u66c7\u3067\u660e\u65e5\u306f\u66c7\u308a\u3067\u3059\u3002\u3061\u306a\u307f\u306b\u50d5\u306e\u3068\u3053\u308d\u3067\u306f\u66c7\u308a\u3067\u6c17\u6e29-7\u2103\u3067\u3059\u3002\u3061\u306a\u307f\u306b\u30b9\u30ab\u30a4\u30d7\u306e\u958b\u767a\u672c\u90e8\u306f\u50d5\u306e\u5bb6\u306b\u3042\u308b\u3093\u3067\u3059\u3002","id":30671388754845696,"from_user_id":65976527,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www15.atpages.jp/~kageyanma/" rel="nofollow">\u5730\u7403\u306e\u4e2d</a>"},{"from_user_id_str":"7278433","profile_image_url":"http://a3.twimg.com/profile_images/1218965303/michael-1_normal.png","created_at":"Thu, 27 Jan 2011 16:50:16 +0000","from_user":"shimohiko","id_str":"30668926035689472","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3042\u308a\u3002\n\u3010\u7f8e\u4eba\u5929\u6c17/\u6771\u4eac\u3011\u7f8e\u4eba\u5929\u6c17\u30ad\u30e3\u30b9\u30bf\u30fc\u306e"\u3055\u3042\u3084\u3093\u3055\u3093"\u306b\u3088\u308b\u3068\u300c1/29(\u571f)\u306f\u304f\u3082\u308a\u3067\u3001\u964d\u6c34\u78ba\u738740%\u3001\u6700\u9ad8\u6c17\u6e29\u306f6\u2103\u3067\u6700\u4f4e\u6c17\u6e29\u306f1\u2103\u3067\u3059\u300d\u7f8e\u4eba\u5929\u6c17\u21d2http://bit.ly/djB8th http://twitpic.com/3twnl0 #bt_tenki","id":30668926035689472,"from_user_id":7278433,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://bijintenki.jp" rel="nofollow">bijintenki.jp</a>"},{"from_user_id_str":"61770","profile_image_url":"http://a3.twimg.com/profile_images/1206955079/tw172a_normal.png","created_at":"Thu, 27 Jan 2011 16:40:52 +0000","from_user":"rsky","id_str":"30666561853333504","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3075\u3068\u591c\u7a7a\u3092\u898b\u4e0a\u3052\u3066\u30aa\u30ea\u30aa\u30f3\u304c\u898b\u3048\u306a\u304f\u3066\u300c\u6771\u4eac\u306b\u306f\u7a7a\u304c\u306a\u3044\u300d\u3068\u667a\u6075\u5b50\u306e\u3088\u3046\u306a\u3053\u3068\u3092\u601d\u3063\u305f\u308f\u3051\u3060\u304c\u3001\u305f\u3076\u3093\u534a\u5206\u3050\u3089\u3044\u306f\u5929\u6c17\u306e\u305b\u3044\u3067\u3059","id":30666561853333504,"from_user_id":61770,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"103259265","profile_image_url":"http://a0.twimg.com/profile_images/767857973/anime_icon_normal.gif","created_at":"Thu, 27 Jan 2011 16:37:42 +0000","from_user":"liveshowonly","id_str":"30665765698928640","metadata":{"result_type":"recent"},"to_user_id":null,"text":"iPhone\u5929\u6c17\u3002\u6771\u4eac4\u2103\u3063\u3066\u7d50\u69cb\u5bd2\u304f\u306a\u3044\u3058\u3083\u3093\u3002\uff08\u78ba\u304b\u306b\u3082\u306e\u51c4\u304f\u5bd2\u3044\u8a33\u3067\u306f\u7121\u3044\uff09\u3002\u798f\u5ca1\u5e02\u306f1\u2103\u3060\u3002\u52dd\u3061\u3060\u305c\u3002Rock'n'roll","id":30665765698928640,"from_user_id":103259265,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"165242761","profile_image_url":"http://a1.twimg.com/profile_images/1147334744/SN3E00600001_normal.jpg","created_at":"Thu, 27 Jan 2011 16:37:35 +0000","from_user":"deuxavril0502","id_str":"30665736556912640","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6b8b\u5ff5\u3001\u79c1\u306f\u6c96\u7e04\u3067\u3059(>_<)\u3067\u3082\u304a\u5929\u6c17\u826f\u3055\u305d\u3046\u3067\u826f\u304b\u3063\u305f\u306d\u3002\u3053\u3061\u3089\u306f\u96e8\u3088\uff5eRT @rinandy2010: \u305d\u3046\u3067\u3059\u3063\u266a\u51fa\u5f35\u3067(^^)\u304a\u306d\u3048\u3055\u307e\u306f\u6771\u4eac\u3067\u3059\u304b\uff1f\u3081\u3063\u3061\u3083\u5929\u6c17\u826f\u304f\u3066\u3073\u3063\u304f\u308a\u3067\u3059\u3002\u624b\u888b\u3068\u304b\u5168\u7136\u3044\u3089\u306a\u3044\u3067\u3059\u306d\u30fc RT @deuxavril0502 \u6771\u4eac\u306a\u306e\u30fc\uff1f","id":30665736556912640,"from_user_id":165242761,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"163900288","profile_image_url":"http://a1.twimg.com/profile_images/1210224823/icon12945064955238_normal.jpg","created_at":"Thu, 27 Jan 2011 16:24:37 +0000","from_user":"nyao_yurichan","id_str":"30662472734089216","metadata":{"result_type":"recent"},"to_user_id":100985873,"text":"@ray_ko302 \u767a\u898b\u3042\u308a\u304c\u3068\u3067\u3059\u3045\u3002\u3053\u3061\u3089\u3067\u3082\u3088\u308d\u3057\u304f\u306d\u3002\u6771\u4eac\u306f\u4eca\u65e5\u3082\u4e7e\u71e5\u3067\u5927\u5909\u3088\u3002\u305d\u3063\u3061\u3068\u771f\u9006\u306e\u5929\u6c17\u3060\u306d\u3002\u30a2\u30a4\u30b9\u30d0\u30fc\u30f3\u304d\u3092\u3064\u3051\u3066\u3088\u306d\u3002","id":30662472734089216,"from_user_id":163900288,"to_user":"ray_ko302","geo":null,"iso_language_code":"ja","to_user_id_str":"100985873","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"49227098","profile_image_url":"http://a3.twimg.com/profile_images/965007882/____normal.jpg","created_at":"Thu, 27 Jan 2011 15:52:26 +0000","from_user":"dosannko6","id_str":"30654371016478720","metadata":{"result_type":"recent"},"to_user_id":108570870,"text":"@peke_hajiP \u4ffa\u304c\u6771\u4eac \u6765\u3066\u6700\u521d\u306b\u9a5a\u3044\u305f\u306e\u304c\u3001\u5929\u6c17\u4e88\u5831\u3067\u82b1\u7c89\u60c5\u5831\u304c\u6d41\u308c\u308b\u3053\u3068\u3067\u3001\u6700\u521d\u306b\u8a66\u3057\u305f\u306e\u304c \u30b4\u30ad\u69d8 \u53ec\u559a\u306e\u5100\u5f0f\u3067\u3059\u304a\uff1f","id":30654371016478720,"from_user_id":49227098,"to_user":"peke_hajip","geo":null,"iso_language_code":"ja","to_user_id_str":"108570870","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"71148934","profile_image_url":"http://a0.twimg.com/profile_images/1209223630/image_normal.jpg","created_at":"Thu, 27 Jan 2011 15:46:49 +0000","from_user":"123keiko","id_str":"30652958311981058","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u9727\u5cf6\u306e\u964d\u7070\u306e\u30cb\u30e5\u30fc\u30b9\u3092\u898b\u3066\u601d\u3044\u51fa\u3057\u307e\u3057\u305f\u3002\u4e0a\u4eac\u3057\u305f\u59cb\u3081\u306e\u9803\u3001\u6771\u4eac\u306f1\u5e74\u4e2d\u3001\u7070\u304c\u964d\u3089\u306a\u3044\u304b\u3089\u7a7a\u6c17\u304c\u6f84\u3093\u3067\u3066\u904e\u3054\u3057\u3084\u3059\u3044\u306a\u3041\u3001\u3068\u601d\u3063\u305f\u306a\u3041\u3001\u3063\u3066\u3002\n\u5b9f\u5bb6\u306f\u51ac\u306e\u5b63\u7bc0\u98a8\u3067\u685c\u5cf6\u306e\u7070\u304c\u964d\u308b\u5730\u533a\u3067\u3057\u305f\u3002\u9e7f\u5150\u5cf6\u306e\u5929\u6c17\u4e88\u5831\u3067\u306f\u3001\u6bce\u65e5\u3001\u685c\u5cf6\u4e0a\u7a7a\u306e\u98a8\u5411\u304d\u4e88\u5831\u304c\u3067\u307e\u3059\u3002\u3053\u308c\u304b\u3089\u306f\u9727\u5cf6\u3082\u304b\u306a\uff1f","id":30652958311981058,"from_user_id":71148934,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"91124773","profile_image_url":"http://a3.twimg.com/profile_images/1139308356/prof101007_3-1_normal.jpg","created_at":"Thu, 27 Jan 2011 15:43:35 +0000","from_user":"sanposuruhito","id_str":"30652146277945345","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4eca\u5bb5\u306e\u90fd\u5fc3\u306f\u3001\u8eab\u3082\u5f15\u304d\u7de0\u307e\u308b\u3068\u3044\u3046\u3088\u308a\u306f\u51cd\u3048\u308b\u7a0b\u306e\u51b7\u6c17\u3092\u611f\u3058\u308b\u5bd2\u3044\u591c\u3067\u3059\u3002\u660e\u65e5\u65e5\u4e2d\u306e\u6771\u4eac\u306e\u5929\u6c17\u306f\u3001\u5915\u65b9\u306b\u591a\u5c11\u96f2\u304c\u51fa\u308b\u5834\u6240\u304c\u3042\u308a\u305d\u3046\u306a\u3082\u306e\u306e\u6982\u306d\u6674\u308c\u7a7a\u304c\u5e83\u304c\u308a\u7d9a\u3051\u305d\u3046\u3067\u3059\u3002\u6700\u9ad8\u6c17\u6e29\u306f\u30015-6\u5ea6\u4f4d\u3068\u306a\u308a\u305d\u3046\u3067\u3059\u3002#weather_tokyo","id":30652146277945345,"from_user_id":91124773,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://projects.playwell.jp/go/Saezuri" rel="nofollow">Saezuri</a>"}],"max_id":30724239224995840,"since_id":28179956995457024,"refresh_url":"?since_id=30724239224995840&q=%E6%9D%B1%E4%BA%AC%E3%80%80%E5%A4%A9%E6%B0%97","next_page":"?page=2&max_id=30724239224995840&lang=ja&q=%E6%9D%B1%E4%BA%AC%E3%80%80%E5%A4%A9%E6%B0%97","results_per_page":15,"page":1,"completed_in":0.104827,"warning":"adjusted since_id to 28179956995457024 (), requested since_id was older than allowed -- since_id removed for pagination.","since_id_str":"28179956995457024","max_id_str":"30724239224995840","query":"%E6%9D%B1%E4%BA%AC%E3%80%80%E5%A4%A9%E6%B0%97"} aeson-1.4.2.0/benchmarks/json-data/jp100.json0000755000000000000000000024561600000000000016653 0ustar0000000000000000{"results":[{"from_user_id_str":"178045354","profile_image_url":"http://a0.twimg.com/profile_images/1214479381/154722_10100141954893059_808622_55276626_7445050_n_normal.jpg","created_at":"Fri, 25 Feb 2011 17:40:04 +0000","from_user":"ChuriSta_gt","id_str":"41190705623732224","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3072\u3089\u304c\u306a\u306e\u300c\u3064\u300d\u306f\u3082\u3046Twitter\u306e\u300c\u3064\u300d\u3060\uff01","id":41190705623732224,"from_user_id":178045354,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b for iPhone</a>"},{"from_user_id_str":"71746558","profile_image_url":"http://a2.twimg.com/profile_images/591641547/wwd_normal.gif","created_at":"Fri, 25 Feb 2011 17:40:02 +0000","from_user":"fuckkilldiestar","id_str":"41190699571494912","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u306b\u3057\u3066\u3082Twitter\u3084pixiv\u96e2\u308c\u3092\u3069\u3046\u306b\u304b\u3057\u308d\u674f\u4ec1\u30d6\u30eb\u30de","id":41190699571494912,"from_user_id":71746558,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"131230176","profile_image_url":"http://a2.twimg.com/sticky/default_profile_images/default_profile_5_normal.png","created_at":"Fri, 25 Feb 2011 17:39:58 +0000","from_user":"proory_bot","id_str":"41190683922546688","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30ea\u30cd\u30f3\u30dd\u30fc\u30c1 http://bit.ly/btjqlH","id":41190683922546688,"from_user_id":131230176,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://proory.com/" rel="nofollow">proory tems</a>"},{"from_user_id_str":"120359038","profile_image_url":"http://a1.twimg.com/profile_images/946521484/200805161826000_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:58 +0000","from_user":"tukinosuke","id_str":"41190680835391488","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @fuefukioyasumi: \u3082\u3046\u3044\u3044\u3002\u300c\u671d\u751f\u300d\u306a\u3093\u304b\u3044\u3044\u3002BBC\u3082CNN\u3082\u82f1\u8a9e\u653e\u9001\u3060\u3002\u307f\u3093\u306a\u3001\u30c6\u30ec\u30d3\u3092\u3076\u3061\u3063\u3068\u5207\u3063\u3066Twitter\u3092\u898b\u3088\u3046\u3002\u3053\u3053\u306b\u300c\u751f\u304d\u305f\u60c5\u5831\u300d\u304c\u6d41\u308c\u3066\u3044\u308b\u3002\u300c\u751f\u304d\u305f\u53eb\u3073\u300d\u304c\u3042\u308b\u3002\u3053\u3053\u304b\u3089\u3067\u3082\u6b74\u53f2\u306e\u8ee2\u63db\u70b9\u3092\u611f\u3058\u308b\u4e8b\u304c\u3067\u304d\u308b\u306e\u3060\u3002 @gjmorley #libjp","id":41190680835391488,"from_user_id":120359038,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"166512109","profile_image_url":"http://a3.twimg.com/profile_images/1224583217/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:50 +0000","from_user":"yurii1129","id_str":"41190649839620096","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4eca\u6c17\u4ed8\u3044\u305f\u2026\u307f\u3043\u304f\u3093\u306eTwitter\u540d\u3001\u3084\u307e\u306d\u3084\u3093(\uffe3\u25c7\uffe3;)","id":41190649839620096,"from_user_id":166512109,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"228999619","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_6_normal.png","created_at":"Fri, 25 Feb 2011 17:39:49 +0000","from_user":"takami926","id_str":"41190644793745408","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u7530\u539f\u3055\u3093\u3001\u5fdc\u63f4\u3057\u3066\u307e\u3059\u3002WEB\u3082TWITTER\u3082\u62dd\u898b\u3057\u3066\u307e\u3059\u3002\u7530\u539f\u3055\u3093\u304c\u653f\u6cbb\u5bb6\u306b\u306a\u3063\u3066\u3001\u65e5\u672c\u3092\u5909\u3048\u3066\u304f\u3060\u3055\u3044\u3002\u5c16\u95a3\u3001\u5317\u65b9\u554f\u984c\u5171\u306b\u65e5\u672c\u306e\u653f\u6cbb\u306e\u5931\u6557\u3067\u3059\u3002\u8a55\u8ad6\u5bb6\u306f\u8272\u3005\u8a00\u3063\u3066\u307e\u3059\u304c\u3001\u4e2d\u6771\u307b\u3069\u56fd\u6c11\u306e\u71b1\u6c17\u304c\u7121\u304f\u3001\u683c\u5dee\u304c\u3042\u308a\u3001\u4f55\u3082\u5909\u308f\u3089\u306a\u3044\u666f\u6c17\u4f4e\u8ff7\u306e\u65e5\u672c\u306b\u56fd\u6c11\u306f\u8ae6\u3081\u3066\u308b\u3093\u3067\u3059\u3002","id":41190644793745408,"from_user_id":228999619,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"151773701","profile_image_url":"http://a0.twimg.com/profile_images/1213699753/obi_nao_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:44 +0000","from_user":"obi_nao","id_str":"41190622949941248","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3060\u3044\u3076\u5e74\u4e0b\u306e\u5f8c\u8f29\u306b\u3001\u30d3\u30b8\u30cd\u30b9\u3084\u308b\u306a\u3089\u771f\u5263\u306bTwitter\u3084\u308c\uff01\u3063\u3066\u6012\u3089\u308c\u305f\u3002\u306a\u306e\u3067\u4eca\u65e5\u304b\u3089\u771f\u5263\u306b\u3064\u3076\u3084\u304f\u3053\u3068\u306b\u3057\u307e\u3059\u3002\u3088\u308d\u3057\u304f\u3067\u3059\u3002","id":41190622949941248,"from_user_id":151773701,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.flight.co.jp/iPhone/TweetMe/" rel="nofollow">TweetMe for iPhone</a>"},{"from_user_id_str":"20817229","profile_image_url":"http://a0.twimg.com/profile_images/1212012721/205_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:43 +0000","from_user":"allte","id_str":"41190619804082176","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u7206\u7b11\u3057\u3066\u547c\u5438\u56f0\u96e3\u3067\u75d9\u6523\u3059\u308b\u5618\u304f\u3093\u304c\u898b\u308c\u308b\u306e\u306fTwitter\u3060\u3051","id":41190619804082176,"from_user_id":20817229,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.movatwi.jp" rel="nofollow">www.movatwi.jp</a>"},{"from_user_id_str":"166907967","profile_image_url":"http://a2.twimg.com/profile_images/1250526230/___normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:43 +0000","from_user":"NTTYAHOOOOOOOI","id_str":"41190618235412480","metadata":{"result_type":"recent"},"to_user_id":106469594,"text":"@takahirororo \u3066\u304b\u4f55\u3067twitter\u4e0a\u3067\u30a2\u30c9\u30d0\u30a4\u30b9\u3082\u3089\u3063\u3066\u3093\u306d\u3093\uff57","id":41190618235412480,"from_user_id":166907967,"to_user":"takahirororo","geo":null,"iso_language_code":"ja","to_user_id_str":"106469594","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"82581287","profile_image_url":"http://a0.twimg.com/profile_images/774721566/miyaru2_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:38 +0000","from_user":"kine_rahchaos","id_str":"41190598132244480","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30a2\u30aa\u30b7\u30de\u3055\u3093\u304cTwitter\u59cb\u3081\u305f\u3060\u3068\u2026","id":41190598132244480,"from_user_id":82581287,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"136633905","profile_image_url":"http://a2.twimg.com/profile_images/1247161991/yama_normal.png","created_at":"Fri, 25 Feb 2011 17:39:35 +0000","from_user":"yamachi39","id_str":"41190584706285568","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3084\u3063\u3071\u308amixi\u3088\u308atwitter\u306e\u304c\u597d\u304d\u304b\u3082","id":41190584706285568,"from_user_id":136633905,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://jigtwi.jp/?p=1" rel="nofollow">jigtwi</a>"},{"from_user_id_str":"44029295","profile_image_url":"http://a2.twimg.com/profile_images/1112965522/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:32 +0000","from_user":"no2yosee","id_str":"41190572769280000","metadata":{"result_type":"recent"},"to_user_id":97721124,"text":"@hn0345 \u3042\u3001\u500b\u4eba\u7684\u306b\u306f\u4eca\u306ftwitter\u306e\u30d7\u30ed\u30d5\u30a3\u30fc\u30eb\u306b\u66f8\u3044\u3066\u3042\u308b\u30d6\u30ed\u30b0\u306e\u30e6\u30cb\u30c3\u30c8\u3092\u306e\u3093\u3073\u308a\u3084\u3063\u3066\u307e\u3059w","id":41190572769280000,"from_user_id":44029295,"to_user":"hn0345","geo":null,"iso_language_code":"ja","to_user_id_str":"97721124","source":"<a href="http://www.flight.co.jp/iPhone/TweetMe/" rel="nofollow">TweetMe for iPhone</a>"},{"from_user_id_str":"149872179","profile_image_url":"http://a0.twimg.com/profile_images/1145770150/Winter11_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:31 +0000","from_user":"xmyyyxx","id_str":"41190566951653376","metadata":{"result_type":"recent"},"to_user_id":95069405,"text":"@rindofu \u653b\u7565\u672c\u3042\u308c\u3070\u3044\u3044\u306e\u306b\u3063\u3066\u601d\u3044\u307e\u3059(T\u03c9T)/~~~ \u79c1\u3082\u76f4\u3057\u305f\u3044\u3068\u3053\u3044\u3063\u3071\u3044\u3060\u3051\u3069\u3001\u3042\u306860\u5e74\u304f\u3089\u3044\u3044\u304d\u3089\u308c\u308b\u306f\u305a\u3060\u3057\u3001\u306e\u3093\u3073\u308a\u76f4\u308c\u3070\u3044\u3044\u306a\u3042 \u304a\u3084\u3059\u307f\u3067\u3059^^\uff01\u308a\u3093\u3055\u3093\u3068twitter\u3067\u4ef2\u826f\u304f\u306a\u308c\u3066\u3088\u304b\u3063\u305f\u3067\u3059\u3063","id":41190566951653376,"from_user_id":149872179,"to_user":"rindofu","geo":null,"iso_language_code":"ja","to_user_id_str":"95069405","source":"<a href="http://twtr.jp" rel="nofollow">Keitai Web</a>"},{"from_user_id_str":"105579892","profile_image_url":"http://a0.twimg.com/profile_images/1212950455/love_happy_pink_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:30 +0000","from_user":"love_happy_pink","id_str":"41190566494601216","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u305d\u308c\u898b\u305f\u3044\u306a\u266aRT @kazukt \u3046\u308b\u304a\u307c\u7d75\u3001\u4ed6\u306e\u4eba\u306e\u3082\u898b\u3066\u3044\u305f\u3089\u3084\u305f\u3089\u30de\u30f3\u30ac\u306e\u30ad\u30e3\u30e9\u30af\u30bf\u30fc\u3067\u3080\u3061\u3083\u304f\u3061\u3083\u4e0a\u624b\u3044\u4eba\u304c\uff01\u2026\u3068\u3001\u30d7\u30ed\u30d5\u30a3\u30fc\u30eb\u898b\u305f\u3089\u3001\u306a\u3093\u3068\u3054\u672c\u4eba\u304c\u66f8\u3044\u3066\u3044\u3089\u3063\u3057\u3083\u3063\u305f\u3002Twitter\u3063\u3066\u30b9\u30b4\u30a4\u308f\u3002","id":41190566494601216,"from_user_id":105579892,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.nibirutech.com/" rel="nofollow">TwitBird iPad</a>"},{"from_user_id_str":"16996368","profile_image_url":"http://a0.twimg.com/profile_images/1198892387/pochi_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:30 +0000","from_user":"HyoYoshikawa","id_str":"41190564187611136","metadata":{"result_type":"recent"},"to_user_id":1800565,"text":"@shinichiro_beck \u73fe\u5730\u304b\u3089\u306a\u3089\u826f\u304f\u3066\u4ed6\u306e\u5730\u57df\u304b\u3089\u3060\u4f59\u8a08\u306a\u3089\u3001\u4f55\u306e\u305f\u3081\u306bTwitter\u304c\u3042\u308b\u306e\u304b\u308f\u304b\u3089\u306a\u3044\u3088\u3002\u3044\u307e\u8d77\u304d\u3066\u308b\u3053\u3068\u306e\u8aac\u660e\u3082\u3064\u304b\u306a\u3044\u3002\u30a2\u30eb\u30b8\u30e3\u30b8\u30fc\u30e9\u304c\u4f1d\u3048\u3066\u308b\u3053\u3068\u304c\u5168\u3066\u3058\u3083\u306a\u3044\u3057\u3001\u65e5\u672c\u306eTV\u306f\u4f1d\u3048\u306a\u3044\u3067\u3057\u3087\u3046\u3002\u77e5\u308a\u305f\u304c\u3063\u3066\u308b\u4eba\u3082\u305f\u304f\u3055\u3093\u3044\u308b\u3002","id":41190564187611136,"from_user_id":16996368,"to_user":"shinichiro_beck","geo":null,"iso_language_code":"ja","to_user_id_str":"1800565","source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"119070802","profile_image_url":"http://a2.twimg.com/profile_images/1229773005/346d8435099798113a1326e1ba4949ee_normal.jpeg","created_at":"Fri, 25 Feb 2011 17:39:25 +0000","from_user":"takotako726","id_str":"41190545439207424","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u9b54\u6cd5\u5c11\u5973\u307e\u3069\u304b\u30de\u30ae\u30ab\u306e\u53cd\u97ff\u304ctwitter\u3067\u306f\u3093\u3071\u306d\u3048\u4ef6\u3002","id":41190545439207424,"from_user_id":119070802,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://z.twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b/twipple</a>"},{"from_user_id_str":"165695316","profile_image_url":"http://a1.twimg.com/profile_images/681748782/ring_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:21 +0000","from_user":"pandora_shotbar","id_str":"41190526447390720","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u300e\u30b7\u30e7\u30c3\u30c8\u30d0\u30fc\u3000\u30d1\u30f3\u30c9\u30e9\u3000\u30c4\u30a4\u30c3\u30bf\u30fc\u306e\u3064\u3076\u3084\u304d\u300f\u30b7\u30e7\u30c3\u30c8\u30d0\u30fc\u3000\u30d1\u30f3\u30c9\u30e9\u3000\u30c4\u30a4\u30c3\u30bf\u30fc\u306e\u3064\u2026\uff5chttp://pandora-twitter.seesaa.net/article/187809936.html","id":41190526447390720,"from_user_id":165695316,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://blog.seesaa.jp/" rel="nofollow">SeesaaBlog</a>"},{"from_user_id_str":"88862311","profile_image_url":"http://a2.twimg.com/profile_images/1182243698/161113_100001897885617_169366_q_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:16 +0000","from_user":"amebaguide","id_str":"41190504926416896","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u300e\u30a2\u30e1\u30d6\u30ed\u653b\u7565\u30ac\u30a4\u30c9\u306e\u30c4\u30a4\u30c3\u30bf\u30fc\u306e\u3064\u3076\u3084\u304d\u300f\u30d6\u30ed\u30b0\u306e\u653b\u7565\u3000\u30c4\u30a4\u30c3\u30bf\u30fc\u306e\u3064\u3076\u3084\u304d\u96c6\uff5chttp://accessup-twitter.seesaa.net/article/187809931.html","id":41190504926416896,"from_user_id":88862311,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://blog.seesaa.jp/" rel="nofollow">SeesaaBlog</a>"},{"from_user_id_str":"186895007","profile_image_url":"http://a2.twimg.com/profile_images/1229610799/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:11 +0000","from_user":"zizikt","id_str":"41190486123356161","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3053\u308c\u306f\u500b\u4eba\u7684\u306b\u306f\u91cd\u5b9d\u3067\u3059\u3002\n\u25c6iPhone&iPad\u5411\u3051Twitter\u30a2\u30d7\u30ea\u300c\u3064\u3044\u3063\u3077\u308b\u300d\u306bEvernote\u3068\u306e\u9023\u643a\u6a5f\u80fd\u3092\u8ffd\u52a0 \nhttp://bit.ly/hPf44u","id":41190486123356161,"from_user_id":186895007,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"132320738","profile_image_url":"http://a3.twimg.com/profile_images/1229760475/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:04 +0000","from_user":"faina_","id_str":"41190453592334336","metadata":{"result_type":"recent"},"to_user_id":167894537,"text":"@gjmorley \u30e2\u30fc\u30ea\u30fc\u3055\u3093\u306e\u7ffb\u8a33\u306e\u8a00\u8449\u306e\u30bb\u30f3\u30b9\u304c\u3059\u304d\u3067\u3059\u3002\u305d\u3057\u3066\u3001Twitter\u3067\u77e5\u308b\u3001\u73fe\u5730\u306e\u4eba\u306e\u76ee\u306e\u529b\u3084\u3001\u60c5\u5831\u3092\u4f1d\u3048\u3066\u304f\u308c\u308b\u7686\u3055\u3093\u306e\u60c5\u71b1\u306b\u611f\u52d5\u3057\u3066\u3044\u307e\u3059\u3002\u611f\u52d5\u3059\u308b\u3063\u3066\u3059\u3054\u3044\u30a8\u30cd\u30eb\u30ae\u30fc\u3067\u3059\uff01\uff01","id":41190453592334336,"from_user_id":132320738,"to_user":"gjmorley","geo":null,"iso_language_code":"ja","to_user_id_str":"167894537","source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"24870552","profile_image_url":"http://a3.twimg.com/profile_images/907130634/4_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:03 +0000","from_user":"tana1192","id_str":"41190450480021504","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u500b\u4eba\u7684\u306b\u306f\u3001\u30bf\u30b0\u5f3e\u304d\u3059\u308c\u3070\u3044\u3044\uff08\u5f3e\u3051\u308b\u30c4\u30fc\u30eb\u3092\u4f7f\u3063\u3066Twitter\u3092\u3059\u308c\u3070\u3044\u3044\uff09\u3068\u601d\u3046\u3093\u3060\u3051\u3069\u306a\u3042\u3002\u307f\u3093\u306a\u305d\u308c\u306a\u308a\u306bTwitter\u3084\u308b\u4eba\u3060\u3057\u3001\u30c4\u30fc\u30eb\u9078\u3073\u304f\u3089\u3044\u5e45\u3092\u6301\u3063\u3066\u3084\u3063\u3066\u3082\u3002 \u307e\u3042\u3001\u4ffa\u30a2\u30cb\u30e1\u306f\u89b3\u308b\u89b3\u308b\u8a50\u6b3a\u3059\u308b\u3060\u3051\u306e\u4eba\u3060\u304b\u3089\u95a2\u4fc2\u306a\u3044\u3093\u3060\u3051\u3069\u3082\uff57\uff57\u5b9f\u6cc1\u306f\u697d\u3057\u305d\u3046\u306b\u898b\u3048\u308b\u3088\u3002","id":41190450480021504,"from_user_id":24870552,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"58509646","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Fri, 25 Feb 2011 17:39:02 +0000","from_user":"kakuyas","id_str":"41190446663344128","metadata":{"result_type":"recent"},"to_user_id":107076877,"text":"@Dayspool \u6df1\u591c\uff12\uff19\u6642\u304f\u3089\u3044\u307e\u3067\u306f\u6bce\u65e5\u55b6\u696d\u3057\u3066\u308b\u306e\u3067\u3001twitter\u3001\u30e1\u30c3\u30bb\u3001PS3\u306a\u3069\u3067\u3088\u3093\u3067\u3051\u308c\u3002\u3053\u3063\u3061\u304b\u3089\u58f0\u304b\u3051\u308b\u3053\u3068\u3082\u3042\u308b\u304b\u3082\u3060\u304c\uff57","id":41190446663344128,"from_user_id":58509646,"to_user":"Dayspool","geo":null,"iso_language_code":"ja","to_user_id_str":"107076877","source":"<a href="http://cheebow.info/chemt/archives/2007/04/twitterwindowst.html" rel="nofollow">Twit for Windows</a>"},{"from_user_id_str":"149128527","profile_image_url":"http://a2.twimg.com/profile_images/1254922702/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:39:00 +0000","from_user":"uni13yoki","id_str":"41190437087748096","metadata":{"result_type":"recent"},"to_user_id":119468594,"text":"@kuro_wr84 \u304a\u308c\u3068\u304a\u524d\u3067Twitter\u3067\u4f1a\u8a71\u3057\u305f\u3089\u3001\u5927\u5909\u306a\u3053\u3068\u306b\u306a\u308b\u306a","id":41190437087748096,"from_user_id":149128527,"to_user":"kuro_wr84","geo":null,"iso_language_code":"ja","to_user_id_str":"119468594","source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"18670595","profile_image_url":"http://a2.twimg.com/profile_images/1250674062/ProfilePhoto_normal.png","created_at":"Fri, 25 Feb 2011 17:38:59 +0000","from_user":"nyuuuuun","id_str":"41190436450222080","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3078\u30fc\u3053\u3093\u306a\u306b\u3088\u304f\u4f3c\u308b\u3053\u3068\u3082\u3042\u308b\u3093\u3060\u30fc\nhttp://twitter.com/Re_44/status/35943233016168448\nhttp://twitter.com/3510_misaka/status/36122114821988352","id":41190436450222080,"from_user_id":18670595,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"96267603","profile_image_url":"http://a3.twimg.com/profile_images/1245253473/DSiLL3_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:59 +0000","from_user":"arivis","id_str":"41190433119940608","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://twitter.com/#!/arivis/status/40636755380142080 \u306a\u3093\u3064\u3046\u304b\u3053\u308c\u3067\u8d64\u3063\u3066\u306e\u3082\u3061\u3087\u3063\u3068\u3042\u308c\u3063\u3059\u306d\u3002\u305d\u3057\u3066\u4e88\u671f\u3057\u3066\u3044\u305f\u304b\u306e\u3088\u3046\u3060","id":41190433119940608,"from_user_id":96267603,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"148097776","profile_image_url":"http://a3.twimg.com/profile_images/1166904064/broken-heart_normal.png","created_at":"Fri, 25 Feb 2011 17:38:56 +0000","from_user":"ReajuBreaker_A","id_str":"41190422135058432","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u672c\u57a2\u30d5\u30a9\u30ed\u30fc\u3088\u308d\u3057\u304f\u3067\u3059\u2192 http://twitter.com/ReajuBreaker \uff08\uff20\u3060\u3068\u30ea\u30d7\u30e9\u30a4\u304c\u57cb\u307e\u308b\u305f\u3081\u3001URL\u306b\u3057\u3066\u3042\u308a\u307e\u3059\uff09","id":41190422135058432,"from_user_id":148097776,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.twitter.com/ReajuBreaker" rel="nofollow">\u73fe\u5145\u6bba\u3057\u306e\u7121\u4eba\u9023\u545f\uff1c\u30aa\u30fc\u30c8\u30c4\u30a4\u30fc\u30c8\uff1e</a>"},{"from_user_id_str":"59711654","profile_image_url":"http://a2.twimg.com/profile_images/416212928/flowers-06-1_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:56 +0000","from_user":"agamo45","id_str":"41190421522546688","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @ebizo66: \u30ea\u30d3\u30a2\u30fb\u30c8\u30ea\u30dd\u30ea\u306eTw\uff1a\u6551\u6025\u8eca\u304c\u6765\u305f\u304c\u3001\u8ca0\u50b7\u8005\u3092\u8eca\u5185\u3067\u6bba\u5bb3\u3057\u3066\u3044\u305f\u3001\u3068\u3002\uff08\u6ec5\u8336\u82e6\u8336\u3060\uff01\uff09http://ow.ly/43pQ2 #libjp","id":41190421522546688,"from_user_id":59711654,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"145311373","profile_image_url":"http://a3.twimg.com/profile_images/1187802576/a_gam_02_normal.png","created_at":"Fri, 25 Feb 2011 17:38:55 +0000","from_user":"nogic1008","id_str":"41190418141937664","metadata":{"result_type":"recent"},"to_user_id":88117317,"text":"@runasoru \u307e\u3042\u5acc\u306a\u3089\u6df1\u591c\u5e2f\u306bTwitter\u898b\u306a\u304d\u3083\u3044\u3044\u3060\u3051\u3067\u3059\u304b\u3089\u306d\u30fc \u30103/19BDM\u30aa\u30d5http://twvt.us/bdoff_kansai\u3011","id":41190418141937664,"from_user_id":145311373,"to_user":"runasoru","geo":null,"iso_language_code":"ja","to_user_id_str":"88117317","source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"195851300","profile_image_url":"http://a2.twimg.com/profile_images/1124572815/be7b4c0a06cb60e8_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:49 +0000","from_user":"LoveLAscrewDoll","id_str":"41190391147540480","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @jp_mjp: SCREW TV SHOW Vol.6\u306e\u653e\u9001\u304c\u7121\u4e8b\u306b\u7d42\u4e86\u3044\u305f\u3057\u307e\u3057\u305f\u3002\u3054\u89a7\u9802\u304d\u3042\u308a\u304c\u3068\u3046\u3054\u3056\u3044\u307e\u3057\u305f\uff01\u6b21\u56de\u653e\u9001\u306f3\u670818\u65e5(\u91d1)\u3067\u3059\u3002\u8996\u8074\u8005\u30d7\u30ec\u30bc\u30f3\u30c8\u306e\u8a73\u7d30\u306f\u5f8c\u65e5MJP\u3067\u304a\u77e5\u3089\u305b\u3044\u305f\u3057\u307e\u3059\u3002\u305d\u306e\u969b\u306b\u306f\u3001\u3053\u306eTwitter\u3067\u3082\u304a\u77e5\u3089\u305b\u3044\u305f\u3057\u307e\u3059\u306e\u3067\u3001\u304a\u697d\u3057\u307f\u306b\uff01#SCREWTV","id":41190391147540480,"from_user_id":195851300,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://z.twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b/twipple</a>"},{"from_user_id_str":"178045354","profile_image_url":"http://a0.twimg.com/profile_images/1214479381/154722_10100141954893059_808622_55276626_7445050_n_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:48 +0000","from_user":"ChuriSta_gt","id_str":"41190389549510656","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3053\u3053\u4e00\u9031\u9593Twitter\u304c\u3084\u305f\u3089\u697d\u3057\u3044\u306e\u3067\u3059\u3051\u3069\u30fc\u30fc\u30fc\uff01\u306b\u3072\u3072\u3063\u7b11","id":41190389549510656,"from_user_id":178045354,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b for iPhone</a>"},{"from_user_id_str":"50592111","profile_image_url":"http://a0.twimg.com/profile_images/1252176582/lFjpi_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:48 +0000","from_user":"crowNeko","id_str":"41190387271864320","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30a8\u30ed\u30b2\u30d7\u30ec\u30a4\u3057\u306a\u304c\u3089\u307e\u3069\u30de\u30aeTL\u3092\u898b\u306a\u3044\u3088\u3046\u306b\u534a\u76ee\u306b\u306a\u308a\u306a\u304c\u3089Twitter\u3057\u3066\u308b\u6df1\u591c2\u6642\u534a\u3002","id":41190387271864320,"from_user_id":50592111,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://stone.com/Twittelator" rel="nofollow">Twittelator</a>"},{"from_user_id_str":"7141467","profile_image_url":"http://a3.twimg.com/profile_images/1198540741/icon12912579345276_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:40 +0000","from_user":"hina_geshi","id_str":"41190355961380864","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u7d50\u5c40\u30cd\u30bf\u30d0\u30ec\u3059\u3093\u306a\u3063\u3066\u8a00\u3046\u65b9\u304c\u30a2\u30ec\u3060\u3088\u306d\u3001\u3057\u306a\u3044\u308f\u3051\u7121\u3044\u3058\u3083\u306a\u3044\u8133\u5185\u5782\u308c\u6d41\u3057\u304cTwitter\u306a\u3093\u3060\u304b\u3089\u3055","id":41190355961380864,"from_user_id":7141467,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://projects.playwell.jp/go/Saezuri" rel="nofollow">Saezuri</a>"},{"from_user_id_str":"149608984","profile_image_url":"http://a0.twimg.com/profile_images/1205950885/090702_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:39 +0000","from_user":"Mr_Tsubaki","id_str":"41190349447774208","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u307e\u3069\u304b\u306fTwitter\u5408\u308f\u305b\u3066\uff11\u6642\u9593\u306f\u697d\u3057\u3044","id":41190349447774208,"from_user_id":149608984,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://z.twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b/twipple</a>"},{"from_user_id_str":"122271550","profile_image_url":"http://a0.twimg.com/profile_images/961936499/neoneko_bot5jpg_____normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:39 +0000","from_user":"neoneko_bot5","id_str":"41190348726345728","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3010\u30c6\u30b9\u30c8\uff1a23\u3011\u4eca\u65e5\u304b\u3089\u5ba3\u4f1d\u958b\u59cb\u2606\u306d\u304a\u306d\u3053\u306eTwitter \u3067 EasyBottex\u3000\u3067\u304d\u308b\u307e\u3067\uff01\u2192http://neoneko.blog31.fc2.com/","id":41190348726345728,"from_user_id":122271550,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www20.atpages.jp/neoneko/" rel="nofollow">neoneko_bot5</a>"},{"from_user_id_str":"127069188","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_6_normal.png","created_at":"Fri, 25 Feb 2011 17:38:37 +0000","from_user":"MYCHEBOT","id_str":"41190340908163074","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30eb\u30d5\u3055\u3093\u304c\u914d\u4fe1\u3092\u7d42\u4e86\u3057\u307e\u3057\u305f\uff01/ http://777labo.com/mychecker/view/745.php / \u30c8\u30d4\u30c3\u30af:XSplit\u30c6\u30b9\u30c8\u3000twitter\u2192http://twitter.com/rukh01","id":41190340908163074,"from_user_id":127069188,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://777labo.com/mychecker/" rel="nofollow">MYCHEBOT</a>"},{"from_user_id_str":"107626142","profile_image_url":"http://a1.twimg.com/profile_images/1104968421/SuperMaika1_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:34 +0000","from_user":"MaikaPaPa","id_str":"41190328614666240","metadata":{"result_type":"recent"},"to_user_id":null,"text":"75\u5e74\u524d\u306e\u4eca\u65e52\u670826\u65e5\u672a\u660e\u3001\u82e5\u304d\u9752\u5e74\u5c06\u6821\u3089\u304c\u653f\u6cbb\u8150\u6557\u3068\u8fb2\u6751\u306e\u56f0\u7aae\u306b\u5bfe\u3057\u3066\u6c7a\u8d77\u3057\u307e\u3057\u305f\u3002\u3082\u3061\u308d\u3093\u5f53\u6642\u306fTwitter\u3082FB\u3082\u3001\u307e\u305f\u5f53\u7136\u306a\u304c\u3089Internet\u3082\u3042\u308a\u307e\u305b\u3093\u3067\u3057\u305f\u3002\u4e00\u65b9\u3001\u30c1\u30e5\u30cb\u30b8\u30a2\u3001\u30a8\u30b8\u30d7\u30c8\u3001\u4e2d\u6771\u306b\u5e83\u304c\u308b\u53cd\u653f\u5e9c\u30c7\u30e2\u3068\u5f37\u6a29\u4f53\u5236\u306e\u5d29\u58ca\u3002\u73fe\u5728\u306e\u65e5\u672c\u3067\u306f\u8003\u3048\u3089\u308c\u306a\u3044\u3053\u3068\u3067\u3059\u3002","id":41190328614666240,"from_user_id":107626142,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"11111695","profile_image_url":"http://a1.twimg.com/sticky/default_profile_images/default_profile_0_normal.png","created_at":"Fri, 25 Feb 2011 17:38:28 +0000","from_user":"kumatchipooh","id_str":"41190306145775617","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @inosenaoki: \u306a\u308b\u307b\u3069\u306d\u3002 RT @dansrmz @inosenaoki \u3053\u3061\u3089\u304c\u30bd\u30d5\u30c8\u30d0\u30f3\u30af\u526f\u793e\u9577\u306e\u677e\u672c\u5fb9\u4e09\u3055\u3093\u306e\u3001Twitter\u306b\u95a2\u3059\u308b\u8ad6\u8003\u3067\u3059\u3002 \u25b6 "Twitter\u306e2\u30c1\u30e3\u30f3\u30cd\u30eb\u5316\u306f\u9632\u6b62\u51fa\u6765\u308b\u304b" http://t.co/Mwzb8Zf","id":41190306145775617,"from_user_id":11111695,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"212161909","profile_image_url":"http://a1.twimg.com/profile_images/1252895790/natm01_normal.gif","created_at":"Fri, 25 Feb 2011 17:38:28 +0000","from_user":"n34hitman","id_str":"41190303830511616","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Twitter\u30fb\u30d6\u30ed\u30b0\u30a2\u30d5\u30a3\u30ea\u30a8\u30a4\u30c8\u81ea\u52d5\u6295.... http://goo.gl/a4RHB 4054","id":41190303830511616,"from_user_id":212161909,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twibow.net/" rel="nofollow">Twibow</a>"},{"from_user_id_str":"105945593","profile_image_url":"http://a2.twimg.com/sticky/default_profile_images/default_profile_5_normal.png","created_at":"Fri, 25 Feb 2011 17:38:24 +0000","from_user":"nakano_bot","id_str":"41190285710983168","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3053\u306ebot\u306f\u4e0d\u52d5\u7523\u4f1a\u793e\u69d8\u5411\u3051\u306e\u4e0d\u52d5\u7523\u30dd\u30fc\u30bf\u30eb\u30b5\u30a4\u30c8\u3078\u306e\u4e00\u62ec\u8ee2\u9001\uff0bTwitter\u7121\u6599\u8ee2\u9001\u30b5\u30fc\u30d3\u30b9\u306b\u3088\u308a\u3064\u3076\u3084\u304d\u307e\u3059\u3002\u3054\u5229\u7528\u306b\u306a\u308a\u305f\u3044\u5834\u5408\u306f http://bit.ly/demey0 \u306b\u304a\u6c17\u8efd\u306b\u304a\u554f\u3044\u5408\u308f\u305b\u4e0b\u3055\u3044\u3002","id":41190285710983168,"from_user_id":105945593,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.teramax.jp/aboutus.html" rel="nofollow">tmxbot</a>"},{"from_user_id_str":"170904226","profile_image_url":"http://a2.twimg.com/profile_images/1249020397/1789kb_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:21 +0000","from_user":"1789kb","id_str":"41190274428305408","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3068\u308a\u3042\u3048\u305a\u4eca\u56de\u521d\u3081\u3066\u30ea\u30a2\u30eb\u30bf\u30a4\u30e0\u3067\u898b\u3066\u308f\u304b\u3063\u305f\u306e\u306f\u3001QB\u306f\u5168\u8eab\u304c\u30a2\u30f3\u30d1\u30f3\u30bf\u30a4\u30d7\u3060\u3068\u3044\u3046\u3053\u3068\u3068\u3001\u307e\u3069\u30de\u30ae\u7d42\u4e86\u5f8c\u306eTwitter\u306e\u3056\u308f\u3064\u304d\u304c\u3059\u3054\u3044\u3068\u3044\u3046\u3053\u3068","id":41190274428305408,"from_user_id":170904226,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"166169644","profile_image_url":"http://a1.twimg.com/profile_images/1217017679/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:18 +0000","from_user":"Okkkkkkkkkkun","id_str":"41190262420017152","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3063\u3066Twitter\u3067\u3064\u3076\u3084\u304f\u81ea\u5206\u3082\u76f8\u5f53\u5c0f\u3055\u3044\u306a\u3002","id":41190262420017152,"from_user_id":166169644,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"196623456","profile_image_url":"http://a3.twimg.com/profile_images/1219076661/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:06 +0000","from_user":"NoMoneyClub","id_str":"41190213342601216","metadata":{"result_type":"recent"},"to_user_id":195462431,"text":"@yosal15 \nTwitter\u3084\u3063\u3066\u308b\u3089\u3057\u3044\u3002\u3051\u3069\u3001\u898b\u3064\u304b\u3089\u306a\u3044\u3002","id":41190213342601216,"from_user_id":196623456,"to_user":"yosal15","geo":null,"iso_language_code":"ja","to_user_id_str":"195462431","source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"126984048","profile_image_url":"http://a3.twimg.com/profile_images/1254579571/zipyaru-20090829-23-0012_normal.png","created_at":"Fri, 25 Feb 2011 17:38:02 +0000","from_user":"minaduki_naduki","id_str":"41190196418584576","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u203b\u30e1\u30fc\u30eb\u3067\u5973\u306e\u5b50\u53e3\u8aac\u304f\u306e\u306b\u5fd9\u3057\u3044\u3093\u3060\u305d\u3046\u3067\u3059\u3000\u307e\u3058\u3058\u3054\u308d RT @yowano_k: \u5fd9\u3057\u304f\u3066\u3082Twitter\u306b\u9854\u3092\u51fa\u3057\u305f\u304f\u306a\u308b\u50d5\u30a7\u2026\u2026","id":41190196418584576,"from_user_id":126984048,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://seesmic.com/seesmic_desktop/sd2" rel="nofollow">Seesmic Desktop</a>"},{"from_user_id_str":"200568705","profile_image_url":"http://a3.twimg.com/profile_images/1242179765/101230_1355_01_normal.jpg","created_at":"Fri, 25 Feb 2011 17:38:01 +0000","from_user":"hammerstrap","id_str":"41190190428979200","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6628\u65e5\u91d1\u66dc\u65e5\u306f\u732e\u8840\u306b\u5f80\u304f\u3002\u4eca\u306e\u50d5\u306e\u4eba\u9593\u3068\u3057\u3066\u306e\u4fa1\u5024\u306f\u3001\u7cbe\u3005\u3053\u306e\u7a0b\u5ea6\u3002\u8179\u304c\u6e1b\u3063\u305f\u3002\u5374\u8aac\u3002twitter\u306e\u767e\u56db\u5341\u6587\u5b57\u306b\u82db\u3005\u3068\u3057\u3066\u3001\u4e00\u3064\u306e\u4eee\u8aac\u306b\u4fe1\u6191\u6027\u3092\u5f97\u308b\u3002\u6226\u6642\u4e0b\u306e\u7d19\u306e\u7d71\u5236\u3068\u3001\u4e2d\u5cf6\u6566\u306e\u6587\u7ae0\u306e\u95a2\u4fc2\u6027\u3002\u73fe\u5728\u30a6\u30a7\u30d6\u30ed\u30b0\u306b\u3001\u7e8f\u3081\u3066\u3044\u308b\u6700\u4e2d\u3002\u8fd1\u65e5\u516c\u958b\u4e88\u5b9a\u3002","id":41190190428979200,"from_user_id":200568705,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"164970427","profile_image_url":"http://a0.twimg.com/profile_images/1227176662/9192b021ef85ce9902c28955f86e604b_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:59 +0000","from_user":"syuigetsuIT","id_str":"41190184041197569","metadata":{"result_type":"recent"},"to_user_id":141926331,"text":"@iliad_tga \u30a4\u30ea\u30a2\u30b9\u3055\u3093\u304c\u305d\u306e\u8fba\u7406\u89e3\u306e\u3042\u308b\u3053\u3068\u306f\u5206\u304b\u3063\u3066\u307e\u3059\uff57\u3000\u30cd\u30bf\u30d0\u30ec\u4e91\u3005\u306ftwitter\u306e\u6c7a\u5b9a\u7684\u306a\u6b20\u70b9\u3060\u3068\u601d\u3044\u307e\u3059\u306d\u3047\u3002","id":41190184041197569,"from_user_id":164970427,"to_user":"iliad_tga","geo":null,"iso_language_code":"ja","to_user_id_str":"141926331","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"94526795","profile_image_url":"http://a0.twimg.com/profile_images/679411954/akb48_in_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:56 +0000","from_user":"akb48_in","id_str":"41190171248431104","metadata":{"result_type":"recent"},"to_user_id":null,"text":"AKB48\u67cf\u6728\u7531\u7d00 \u304a\u75b2\u308c\u69d8\u3002: \n\u3053\u3093\u3070\u3093\u306f(^O^)\uff0f\u266a\n\u3000\n\u3000\n\u3000\n\u4eca\u65e5\u306e\u516c\u6f14\u697d\u3057\u304b\u3063\u305f\u301c\n\u3000\n\u3000\n\u4e45\u3057\u3076\u308a\u3067\u7dca\u5f35\u3057\u305f\u3051\u3069\u3001\u306f\u3058\u3051\u307e\u304f\u3063\u305f\u305c\u3043\uff01\uff01\n\u3000\n\u3000\n\u3000\nMC\u306f\u565b\u307f\u307e\u304f\u308a\u306e\u30c6\u30f3\u30d1\u308a\u307e\u304f... http://bit.ly/ie8bEa akb48 twitter","id":41190171248431104,"from_user_id":94526795,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"222270374","profile_image_url":"http://a3.twimg.com/profile_images/1250946143/P1040062_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:53 +0000","from_user":"chrxpac","id_str":"41190158455943168","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3010\u5b9a\u671f\u3011Twitter\u306f\uff8a\uff9f\uff7f\uff7a\uff9d\u304b\u3089\u3057\u304b\u3067\u304d\u306a\u3044\u306e\u3067\uff98\uff8c\uff9f\u8fd4\u3057\u304c\u9045\u304f\u306a\u308a\u307e\u3059(\u00b4\u30fb\u03c9\u30fb\uff40)\u3054\u4e86\u627f\u4e0b\u3055\u3044!!","id":41190158455943168,"from_user_id":222270374,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twittbot.net/" rel="nofollow">twittbot.net</a>"},{"from_user_id_str":"64009258","profile_image_url":"http://a2.twimg.com/profile_images/1154025023/Mixi___normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:52 +0000","from_user":"Tatsuyuko","id_str":"41190153447944192","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4f01\u696d\u304c\u5c31\u6d3b\u751f\u306bFacebook\u3092\u4f7f\u3063\u3066\u7533\u8acb\u305b\u3088\u3068\u3044\u3044\u3001\u4f01\u696d\u304cFacebook\u3092\u4f7f\u3048\u3068\u4f01\u696d\u304c\u8a00\u3063\u3066\u304d\u305f\u308a\u3059\u308c\u3070\u305d\u308c\u3069\u3053\u308d\u3058\u3083\u306a\u3044\u304b\u3068\u3002\u5c11\u306a\u304f\u3068\u3082\u5c31\u6d3b\u3067Twitter\u306e\u8a00\u52d5\u3084\u30d5\u30a9\u30ed\u30ef\u30fc\u3092\u8abf\u67fb\u3059\u308b\u4f01\u696d\u306f\u304b\u306a\u308a\u591a\u3044\u3067\u3059 RT @Isshee: \u4f01\u696d\u3067\u3082\u540c\u3058\u3067\u3057\u3087 RT","id":41190153447944192,"from_user_id":64009258,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"105145175","profile_image_url":"http://static.twitter.com/images/default_profile_normal.png","created_at":"Fri, 25 Feb 2011 17:37:49 +0000","from_user":"snao813","id_str":"41190141703753728","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @yumisaiki: \u795e\u69d8\u306f\u672c\u5f53\u306b\u4eba\u9593\u3092\u3059\u3070\u3089\u3057\u3044\u30d0\u30e9\u30f3\u30b9\u3067\u914d\u7f6e\u3057\u3066\u304a\u3089\u308c\u308b\u3002\u795d\u5cf6\u307f\u305f\u3044\u306a\u5c0f\u3055\u3044\u3068\u3053\u308d\u306b\u306a\u3093\u3067\u3053\u3093\u306a\u306b\u7acb\u6d3e\u306a\u4eba\u304c\u305f\u304f\u3055\u3093\u3044\u308b\u3093\u3060\u308d\u3046\u3002\u795e\u69d8\u3042\u308a\u304c\u3068\u3046\u3002\u672c\u5f53\u306b\u3042\u308a\u304c\u3068\u3046\u3002\u4eba\u9593\u3063\u3066\u3059\u3070\u3089\u3057\u3044\u3068\u601d\u3048\u305f\u3002twitter\u3082\u3042\u308a\u304c\u3068\u3046\u3002\u3000#kaminoseki","id":41190141703753728,"from_user_id":105145175,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://seesmic.com/seesmic_desktop/sd2" rel="nofollow">Seesmic Desktop</a>"},{"from_user_id_str":"203667204","profile_image_url":"http://a2.twimg.com/profile_images/1254664000/eve_blackcat_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:46 +0000","from_user":"eve_blackcat","id_str":"41190129292943361","metadata":{"result_type":"recent"},"to_user_id":146894340,"text":"@kuroiso02 \u3057\u308a\u3068\u308a\u3068\u304b\uff1f\n\u2026\u3067\u3082Twitter\u3060\u3068\u7d42\u308f\u3089\u306a\u304f\u306a\u308b\u30b1\u30c9\u2026","id":41190129292943361,"from_user_id":203667204,"to_user":"kuroiso02","geo":null,"iso_language_code":"ja","to_user_id_str":"146894340","source":"<a href="http://twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b for iPhone</a>"},{"from_user_id_str":"6528403","profile_image_url":"http://a0.twimg.com/profile_images/1240591244/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:45 +0000","from_user":"sortiee","id_str":"41190125924917248","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30a2\u30cb\u30e1\u5b9f\u6cc1\u306ftwitter\u306e\u764c","id":41190125924917248,"from_user_id":6528403,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sites.google.com/site/peraperaprv/Home" rel="nofollow">P3:PeraPeraPrv</a>"},{"from_user_id_str":"186058304","profile_image_url":"http://a0.twimg.com/profile_images/1250454564/IMG_0210_normal.JPG","created_at":"Fri, 25 Feb 2011 17:37:37 +0000","from_user":"00o8o00","id_str":"41190090386448384","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @fuefukioyasumi: \u3082\u3046\u3044\u3044\u3002\u300c\u671d\u751f\u300d\u306a\u3093\u304b\u3044\u3044\u3002BBC\u3082CNN\u3082\u82f1\u8a9e\u653e\u9001\u3060\u3002\u307f\u3093\u306a\u3001\u30c6\u30ec\u30d3\u3092\u3076\u3061\u3063\u3068\u5207\u3063\u3066Twitter\u3092\u898b\u3088\u3046\u3002\u3053\u3053\u306b\u300c\u751f\u304d\u305f\u60c5\u5831\u300d\u304c\u6d41\u308c\u3066\u3044\u308b\u3002\u300c\u751f\u304d\u305f\u53eb\u3073\u300d\u304c\u3042\u308b\u3002\u3053\u3053\u304b\u3089\u3067\u3082\u6b74\u53f2\u306e\u8ee2\u63db\u70b9\u3092\u611f\u3058\u308b\u4e8b\u304c\u3067\u304d\u308b\u306e\u3060\u3002 @gjmorley #libjp","id":41190090386448384,"from_user_id":186058304,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"49219631","profile_image_url":"http://a2.twimg.com/profile_images/1231873117/__2-colornow__2__normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:33 +0000","from_user":"irisgazer","id_str":"41190073227550720","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3067\u3059\u3088\u306d\u3047 RT @minamitaiheiyou: \u6545\u306b\u30cd\u30bf\u30d0\u30ec\u3092\u3059\u308b\u306e\u3082\u81ea\u7531\u3002\u30cd\u30bf\u3070\u308c\u3057\u305f\u4eba\u3092\u30c7\u30a3\u30b9\u308b\u306e\u3082\u81ea\u7531\u3002\u3042\u3068\u306f\u5404\u3005\u306e\u88c1\u91cf\u3067\u4e57\u308a\u5207\u3063\u3066\u304f\u3060\u3055\u3044\u3088\u3081\u3093\u3069\u304f\u3055\u3044\u306a RT @kihirokiro: Twitter\u3067\u30cd\u30bf\u30d0\u30ec\u4e91\u3005\u3044\u3063\u3066\u3082\u5143\u3005Twitter\u3063\u3066\u300c\u500b\u4eba\u306e\u72ec\u308a\u8a00\u300d\u3060\u308d","id":41190073227550720,"from_user_id":49219631,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"98560114","profile_image_url":"http://a0.twimg.com/profile_images/1252332545/IMGP8170_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:32 +0000","from_user":"qess0093","id_str":"41190070706905088","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30b7\u30e5\u30fc\u30c6\u30a3\u304f\u305d\u3046\u305c\u3048\uff57 RT @syu_thi_bot: \u3044\u3064\u307e\u3067Twitter\u3084\u3063\u3066\u308b\u3093\u3060\u3044\uff1f\u3044\u3044\u52a0\u6e1b\u73fe\u5b9f\u306b\u623b\u308a\u306a\u3088\u3002\u3053\u3053\u306f\u30ad\u30df\u305f\u3061\u4e09\u6b21\u5143\u306e\u4eba\u9593\u304c\u3044\u308b\u3079\u304d\u5834\u6240\u3058\u3083\u306a\u3044\u3093\u3060\u3088\u3002\u305d\u3093\u306a\u306e\u57fa\u672c\u3060\u308d\uff01\uff01","id":41190070706905088,"from_user_id":98560114,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"197459334","profile_image_url":"http://a3.twimg.com/profile_images/1210698414/shiratorishoko_normal.png","created_at":"Fri, 25 Feb 2011 17:37:31 +0000","from_user":"SyokoShiratori","id_str":"41190064243478528","metadata":{"result_type":"recent"},"to_user_id":null,"text":"+0.50kg \u540c\u3058\u304f\u30c0\u30a4\u30a8\u30c3\u30c8\u4e2d\u3067\u3059\u3002\u3088\u304f\u3053\u306e\u30b5\u30a4\u30c8\u3067\u4f53\u91cd\u5831\u544a\u3057\u3066\u307e\u3059\u266a http://bit.ly/fhN2fM RT @msophiah \u3046\u3046\u3046\u30fb\u30fb\u30fb\u304a\u8179\u3059\u3044\u305f\u301c\u30fb\u30fb\u30fb\u6211\u6162\u3001\u6211\u6162\u3001\u6211\u6162\u3002\u30c0\u30a4\u30a8\u30c3\u30c8\u3001\u30c0\u30a4\u30a8\u30c3\u30c8\u3001\u30c0\u30a4\u30a8\u30c3\u30c8\u3002","id":41190064243478528,"from_user_id":197459334,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://mob-mc.com" rel="nofollow">\uff08\u4eee\u79f0\uff09\u30c4\u30a4\u30af\u30ea\u30c3\u30af twiclick</a>"},{"from_user_id_str":"180410237","profile_image_url":"http://a3.twimg.com/profile_images/1254473979/icon_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:30 +0000","from_user":"ka_ph","id_str":"41190062184079360","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3010\u5b9a\u671fpost\u3011\u30d5\u30a7\u30eb\u30c7\u30a3\u30ca\u30f3\u30c8bot( http://twitter.com/ferdinand_bot )\u4f5c\u308a\u307e\u3057\u305f\u3002\u304a\u5b50\u69d8\u306e\u540d\u524d\u304a\u501f\u308a\u3055\u305b\u3066\u304f\u308c\u308b\u65b9\u3044\u307e\u3057\u305f\u3089@ka_ph\u307e\u3067\u304a\u9858\u3044\u3057\u307e\u3059\u3002","id":41190062184079360,"from_user_id":180410237,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twittbot.net/" rel="nofollow">twittbot.net</a>"},{"from_user_id_str":"52283906","profile_image_url":"http://a3.twimg.com/profile_images/387644016/10100654519_s_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:26 +0000","from_user":"rolling_bean","id_str":"41190043313913856","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3081\u307e\u3044\u304c\u3057\u307e\u3059\u306d\u301cRT @yurikalin:\u30b3\u30a4\u30c4\u30e9\u5168\u54e1\u3044\u306a\u304f\u306a\u3063\u305f\u3089\u3001\u660e\u308b\u304f\u306a\u308b\u3060\u308d\u3046\u306a\u3041\uff5e\u266a\uff1e\u65e5\u672c\u306e\u30d3\u30b8\u30e7\u30f3 RT roll \u65e5\u7d4c\uff06CSIS\u30b7\u30f3\u30dd\u30b8\u30a6\u30e0\u300c\u5b89\u4fdd\u6539\u5b9a50\u5468\u5e74\u3001\u3069\u3046\u306a\u308b\u65e5\u7c73\u95a2\u4fc2\u300d http://bit.ly/dES8PY\u3000http://bit.ly/ihg0GT","id":41190043313913856,"from_user_id":52283906,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://tabtter.jp" rel="nofollow">\u30bf\u30d6\u30c3\u30bf\u30fc</a>"},{"from_user_id_str":"351896","profile_image_url":"http://a3.twimg.com/profile_images/1179865336/icon12911887173020_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:26 +0000","from_user":"cicada","id_str":"41190043292925952","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4e2d\u5b66\u53d7\u9a13\u7a0b\u5ea6\u306e\u7b97\u6570\u306e\u554f\u984c\u3092\u51fa\u3059BOT http://twitter.com/arithmetic_bot \u6c17\u306b\u306f\u306a\u308b\u304c\u3001\u3061\u3083\u3093\u3068\u898b\u308b\u65e5\u304c\u6765\u308b\u3060\u308d\u3046\u304b\u30fb\u30fb\u3000#tearai\uff1a\u30ed\u30b3\u30e9\u30dc\u5bae\u5d0e\u770c http://locolabo.com/mz/ #mzlf","id":41190043292925952,"from_user_id":351896,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://locolabo.com/mz/" rel="nofollow">\u30ed\u30b3\u30e9\u30dc\u5bae\u5d0e\u770c</a>"},{"from_user_id_str":"744554","profile_image_url":"http://a1.twimg.com/profile_images/1088753125/11868894_normal.gif","created_at":"Fri, 25 Feb 2011 17:37:20 +0000","from_user":"Febreze","id_str":"41190019020505088","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30cd\u30bf\u30d0\u30ec\u3042\u307e\u308a\u6c17\u306b\u3057\u306a\u3044\u30bf\u30a4\u30d7\u3060\u3051\u3069\u306a\u3093\u304b\u3053\u3046Twitter\u958b\u304f\u3060\u3051\u3067\u30ac\u30f3\u30ac\u30f3\u30cd\u30bf\u30d0\u30ec\u5165\u3063\u3066\u304f\u308b\u306e\u306f\u306a\u3093\u3068\u3082\u8a00\u3048\u306a\u3044\u306a\u3002","id":41190019020505088,"from_user_id":744554,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"203371794","profile_image_url":"http://a1.twimg.com/profile_images/1226537594/___normal.png","created_at":"Fri, 25 Feb 2011 17:37:16 +0000","from_user":"himeko24","id_str":"41190004139114496","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6b21\u3044\u3063\u3066\u307f\u3088\u30fc\u3000\u306f\u3044\u3053\u308c\u3000 \u6fc0\u5b89\u26052010\u5e74\u590f\u65b0\u30c7\u30b6\u30a4\u30f3\u2605\u30bb\u30af\u30b7\u30fc\u306a\u9023\u4f53\u5f0f\u7121\u5730\u6c34\u7740 \u80f8\u30d1\u30c3\u30c9\u4ed8\u304dQ122 http://bit.ly/h72C4i","id":41190004139114496,"from_user_id":203371794,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.google.co.jp" rel="nofollow">himeko24</a>"},{"from_user_id_str":"119988932","profile_image_url":"http://a3.twimg.com/profile_images/1214344633/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:16 +0000","from_user":"7na_love_6sa","id_str":"41190002000007169","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30d6\u30ed\u30b0\u66f4\u65b0\u3057\u307e\u3057\u305f\uff01Twitter\uff06mixi\u304b\u3089\u3082\u30b3\u30e1\u30f3\u30c8\u5b9c\u3057\u304f\u306d\u266a\n\u300c\u30cd\u30a4\u30eb\u30c1\u30a7\u30f3\u30b8\u266a\u300d http://amba.to/hy0Do2","id":41190002000007169,"from_user_id":119988932,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"217408835","profile_image_url":"http://a1.twimg.com/profile_images/1215428655/____4.0157_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:12 +0000","from_user":"nikubenki1123","id_str":"41189985424125952","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @x68k: \u57fa\u672c\u7684\u306bTwitter\u4e0a\u3067\u306f"\u597d\u304d\u306b\u3084\u308c\u3070\u3044\u3044"\u3060\u3051\u3069\u3001\u540d\u524d\u3082\u30a2\u30a4\u30b3\u30f3\u3082\u30a2\u30f3\u30bf\u3058\u3083\u306a\u3044\u305f\u304f\u3055\u3093\u306e\u4eba\u305f\u3061\u306e\u9b42\u304c\u3053\u3082\u3063\u305f\u3082\u306e\u306a\u306e\u3060\u304b\u3089\u3001\u305d\u308c\u3060\u3051\u306f"\u80cc\u8ca0\u3048"\u3068\u601d\u3046\uff1e\u30ad\u30e3\u30e9\u30af\u30bf\u30fc\u30a2\u30ab\u30a6\u30f3\u30c8","id":41189985424125952,"from_user_id":217408835,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://tweetlogix.com" rel="nofollow">Tweetlogix</a>"},{"from_user_id_str":"139137996","profile_image_url":"http://a0.twimg.com/profile_images/1087408006/cut_work_18_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:12 +0000","from_user":"fujiokayouko","id_str":"41189984354566144","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u591c\u4e2d\u306bTwitter\u3092\u306a\u3093\u3068\u306a\u304f\u8997\u3044\u305f\u3089\u3082\u306e\u3059\u3054\u3044\u307e\u3069\u30de\u30aeTL\u3067","id":41189984354566144,"from_user_id":139137996,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://mobile.twitter.com" rel="nofollow">Mobile Web</a>"},{"from_user_id_str":"61221002","profile_image_url":"http://a3.twimg.com/profile_images/554916301/_1259757374_61_normal.png","created_at":"Fri, 25 Feb 2011 17:37:08 +0000","from_user":"hiromk63","id_str":"41189970613903360","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @kenji_kohashi \u7121\u4e8b\u6620\u753b\u88fd\u4f5c\u306e\u5831\u544a\u306f\u3067\u304d\u305f\u3051\u3069\u4eca\u3060\u7de8\u96c6\u306f\u7d9a\u3044\u3066\u307e\u3059w \u305d\u3093\u306a\u3068\u3053\u3067 \u6620\u753b\u300cDON'T STOP!\u300d\u306eTwitter \u30a2\u30ab\u30a6\u30f3\u30c8 @DONTSTOPMOVIE \u3082\u958b\u59cb\u3001\u3082\u3057\u826f\u304b\u3063\u305f\u3089\u30d5\u30a9\u30ed\u30fc\u3057\u3066\u304f\u3060\u3055\u3044\uff01\u50d5\u3082\u542b\u3081\u6620\u753b\u88fd\u4f5c\u95a2\u4fc2\u8005\u304c\u6c17\u9577\u306b\u3064\u3076\u3084\u304d\u307e\u3059","id":41189970613903360,"from_user_id":61221002,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"147393812","profile_image_url":"http://a1.twimg.com/profile_images/1114001122/hana_10_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:07 +0000","from_user":"tubasa_uki","id_str":"41189965924667392","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\uff10\uff10\uff17\u3082\u3073\u3063\u304f\u308a\u3000\u5927\u56fd\u306e\u5927\u7d71\u9818\u9078\u304b\u3089\u3000\u5cf6\u56fd\u306e\u5730\u65b9\u9078\u306e\u9078\u6319\u307e\u3067\u306b\u3082\u3000\u6697\u8e8d\u3057\u3066\u3044\u308b\uff3e\uff3e\u3000\u3053\u306eTwitter \u30b9\u30ad\u30e3\u30f3\u30c0\u30eb\u3084\u60aa\u8cea\u306a\u4e8b\u4ef6\u306b\u3082\u7d61\u3080\u304c\u3000Twitter\u304b\u3089\u767a\u4fe1\u3055\u308c\u305f\u3000\u5e73\u548c\u3078\u306e\u8ca2\u732e\u306f\u3000\u307e\u3055\u306b\u30ce\u30fc\u3079\u30eb\u5e73\u548c\u8cde\u3082\u306e http://bit.ly/esjWDG #dotubo_ss","id":41189965924667392,"from_user_id":147393812,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twittbot.net/" rel="nofollow">twittbot.net</a>"},{"from_user_id_str":"96081746","profile_image_url":"http://a0.twimg.com/profile_images/1244505419/illust832_normal.png","created_at":"Fri, 25 Feb 2011 17:37:07 +0000","from_user":"kazukt","id_str":"41189963131387904","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3046\u308b\u304a\u307c\u7d75\u3001\u4ed6\u306e\u4eba\u306e\u3082\u898b\u3066\u3044\u305f\u3089\u3084\u305f\u3089\u30de\u30f3\u30ac\u306e\u30ad\u30e3\u30e9\u30af\u30bf\u30fc\u3067\u3080\u3061\u3083\u304f\u3061\u3083\u4e0a\u624b\u3044\u4eba\u304c\uff01\u2026\u3068\u3001\u30d7\u30ed\u30d5\u30a3\u30fc\u30eb\u898b\u305f\u3089\u3001\u306a\u3093\u3068\u3054\u672c\u4eba\u304c\u66f8\u3044\u3066\u3044\u3089\u3063\u3057\u3083\u3063\u305f\u3002Twitter\u3063\u3066\u30b9\u30b4\u30a4\u308f\u3002","id":41189963131387904,"from_user_id":96081746,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://janetter.net/" rel="nofollow">Janetter</a>"},{"from_user_id_str":"86306230","profile_image_url":"http://a1.twimg.com/profile_images/593004766/j2j_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:03 +0000","from_user":"excite_j2j","id_str":"41189949927596032","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u79c1\u306f\u3001\u65e9\u7a32\u7530\u5927\u5b66\u30aa\u30fc\u30d7\u30f3\u30ab\u30ec\u30c3\u30b8\u306e\u5b66\u751f\u306e\u8003\u3048\u3066\u3044\u308b\u3001\u5352\u696d\u751fSoudai /\u65e9\u7a32\u7530\u30ab\u30fc\u30c9\u4f1a\u54e1/ Soudai\u5b66\u751f\u89aa/\u3001\u8ab0\u304b\u304c\u30aa\u30fc\u30d7\u30f3\u30ab\u30ec\u30c3\u30b8\u65e9\u7a32\u7530\u5927\u5b662000\u5186\u306e\u5165\u5834\u6599\u306e\u30e1\u30f3\u30d0\u30fc\u3092\u7d39\u4ecb\u3057\u3066\u304f\u308c\u305f\u65b9\u304c\u305a\u3063\u3068\u5b89\u4e0a\u304c\u308a\u3060\u3002 (\u5143\u767a\u8a00 http://bit.ly/esxiwT )","id":41189949927596032,"from_user_id":86306230,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://d.hatena.ne.jp/fn7" rel="nofollow">\u65e5\u672c\u8a9e\u65e5\u672c\u8a9e\u7ffb\u8a33\u30b8\u30a7\u30cd\u30ec\u30fc\u30bf</a>"},{"from_user_id_str":"120927161","profile_image_url":"http://a0.twimg.com/profile_images/1230006483/20110131_13022_26776_normal.jpg","created_at":"Fri, 25 Feb 2011 17:37:00 +0000","from_user":"FRISKFOSSILFANG","id_str":"41189933855158272","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @syu_thi_bot: \u3044\u3064\u307e\u3067Twitter\u3084\u3063\u3066\u308b\u3093\u3060\u3044\uff1f\u3044\u3044\u52a0\u6e1b\u73fe\u5b9f\u306b\u623b\u308a\u306a\u3088\u3002\u3053\u3053\u306f\u30ad\u30df\u305f\u3061\u4e09\u6b21\u5143\u306e\u4eba\u9593\u304c\u3044\u308b\u3079\u304d\u5834\u6240\u3058\u3083\u306a\u3044\u3093\u3060\u3088\u3002\u305d\u3093\u306a\u306e\u57fa\u672c\u3060\u308d\uff01\uff01","id":41189933855158272,"from_user_id":120927161,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twittbot.net/" rel="nofollow">twittbot.net</a>"},{"from_user_id_str":"228973151","profile_image_url":"http://a1.twimg.com/sticky/default_profile_images/default_profile_0_normal.png","created_at":"Fri, 25 Feb 2011 17:36:59 +0000","from_user":"daisuke1589","id_str":"41189931887890432","metadata":{"result_type":"recent"},"to_user_id":null,"text":"twitter\u3063\u3066\u52dd\u624b\u306b\u30d5\u30a9\u30ed\u30fc\u3057\u3066\u3082\u3044\u3044\u3093\u3060\u3063\u3051\uff1f","id":41189931887890432,"from_user_id":228973151,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"54314110","profile_image_url":"http://a2.twimg.com/profile_images/1193541240/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:57 +0000","from_user":"Alohazuki","id_str":"41189922668953600","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Twitter\u306e\u5e83\u5cf6\u5f01\u3082\u3042\u3063\u305f\u3093\u3060\u306d\u3002","id":41189922668953600,"from_user_id":54314110,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.flight.co.jp/iPhone/TweetMe/" rel="nofollow">TweetMe for iPhone</a>"},{"from_user_id_str":"72594681","profile_image_url":"http://a3.twimg.com/profile_images/1227240916/____normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:56 +0000","from_user":"uri4ichi","id_str":"41189916922744832","metadata":{"result_type":"recent"},"to_user_id":226852303,"text":"@7_fuka Twitter\u304b\u3076\u308c\u306f\u3001\u3059\u3050\u306bD\u306b\u8d70\u308b\u306e\u3067\u3002\u306a\u3093\u3060\u304b\u5fae\u7b11\u307e\u3057\u3044\u306e\u3067\u3059( \u2579\u25e1\u2579)","id":41189916922744832,"from_user_id":72594681,"to_user":"7_fuka","geo":null,"iso_language_code":"ja","to_user_id_str":"226852303","source":"<a href="http://sites.google.com/site/yorufukurou/" rel="nofollow">YoruFukurou</a>"},{"from_user_id_str":"168393854","profile_image_url":"http://a3.twimg.com/profile_images/1253554518/GuNp3xVS_normal","created_at":"Fri, 25 Feb 2011 17:36:55 +0000","from_user":"makonyanhime","id_str":"41189913701515264","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6589\u85e4\u3055\u3093\u3082\u30c0\u30e1\u3060...\u4eca\u591c\u306fTwitter\u5909\u3060\u306a\u3041(;_;)","id":41189913701515264,"from_user_id":168393854,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://mobile.twitter.com" rel="nofollow">Twitter for Android</a>"},{"from_user_id_str":"122636787","profile_image_url":"http://a2.twimg.com/profile_images/1189607563/DSC01987_normal.JPG","created_at":"Fri, 25 Feb 2011 17:36:54 +0000","from_user":"enpy1217","id_str":"41189908500594688","metadata":{"result_type":"recent"},"to_user_id":null,"text":"twitter\u4e45\u3057\u3076\u308a\u306b\u958b\u3044\u305f\u3002\u3068\u3066\u3082\u591a\u5fd9\u3060\u3063\u305f\u3002\u75b2\u308c\u305f\u3002\u304a\u98a8\u5442\u306b\u3082\u5165\u308c\u306a\u304b\u3063\u305f\u3002\u30ad\u30bf\u30cd\u2026","id":41189908500594688,"from_user_id":122636787,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.flight.co.jp/iPhone/TweetMe/" rel="nofollow">TweetMe for iPhone</a>"},{"from_user_id_str":"81663694","profile_image_url":"http://a3.twimg.com/profile_images/1177576126/__normal.png","created_at":"Fri, 25 Feb 2011 17:36:51 +0000","from_user":"progmiya","id_str":"41189895494049792","metadata":{"result_type":"recent"},"to_user_id":94050844,"text":"@hirasai_skyhigh \u6674\u308c\u541b\u3002\u30cd\u30bf\u30d0\u30ec\u306f\u898b\u305f\u304f\u306a\u3044\u3051\u3069\u30012ch\u3082twitter\u3082\u3084\u308a\u305f\u3044\u306e\u304c\u4eba\u3068\u8a00\u3046\u3082\u306e\u3088","id":41189895494049792,"from_user_id":81663694,"to_user":"hirasai_skyhigh","geo":null,"iso_language_code":"ja","to_user_id_str":"94050844","source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"159237469","profile_image_url":"http://a3.twimg.com/profile_images/1140433484/______2_normal.png","created_at":"Fri, 25 Feb 2011 17:36:50 +0000","from_user":"hikari_juku","id_str":"41189892096532480","metadata":{"result_type":"recent"},"to_user_id":135634241,"text":"@sssukimasuky \n\u4f55\u304b\u3042\u3063\u305f\u98a8\u3067\u3059\u306d\uff08\u7b11\uff09\u3000\u78ba\u304b\u306bTwitter\u306f\u6c17\u8efd\u3067\u3059\u3057\u306d\u3002\u30e1\u30fc\u30eb\u306b\u306a\u308b\u3068\u30d5\u30c3\u30c8\u30ef\u30fc\u30af\u304c\u91cd\u304f\u306a\u308b\u5834\u5408\u3082\u3042\u308b\u304b\u3082\u3057\u308c\u307e\u305b\u3093\u306d\u3002\u305d\u3046\u8003\u3048\u308b\u3068\u3059\u3054\u3044\u6642\u4ee3\u3060\u3002","id":41189892096532480,"from_user_id":159237469,"to_user":"sssukimasuky","geo":null,"iso_language_code":"ja","to_user_id_str":"135634241","source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"141915990","profile_image_url":"http://a0.twimg.com/profile_images/1248969898/icon679566266564378764images_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:48 +0000","from_user":"adashino_","id_str":"41189886878949376","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @fuefukioyasumi: \u3082\u3046\u3044\u3044\u3002\u300c\u671d\u751f\u300d\u306a\u3093\u304b\u3044\u3044\u3002BBC\u3082CNN\u3082\u82f1\u8a9e\u653e\u9001\u3060\u3002\u307f\u3093\u306a\u3001\u30c6\u30ec\u30d3\u3092\u3076\u3061\u3063\u3068\u5207\u3063\u3066Twitter\u3092\u898b\u3088\u3046\u3002\u3053\u3053\u306b\u300c\u751f\u304d\u305f\u60c5\u5831\u300d\u304c\u6d41\u308c\u3066\u3044\u308b\u3002\u300c\u751f\u304d\u305f\u53eb\u3073\u300d\u304c\u3042\u308b\u3002\u3053\u3053\u304b\u3089\u3067\u3082\u6b74\u53f2\u306e\u8ee2\u63db\u70b9\u3092\u611f\u3058\u308b\u4e8b\u304c\u3067\u304d\u308b\u306e\u3060\u3002 @gjmorley #libjp","id":41189886878949376,"from_user_id":141915990,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"111308629","profile_image_url":"http://a1.twimg.com/profile_images/1137421845/mmooton_normal.png","created_at":"Fri, 25 Feb 2011 17:36:46 +0000","from_user":"mmooton","id_str":"41189877940748288","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @minponjp: \u3010\u3064\u3076\u3084\u304f\u3060\u3051\u306710000\u5186\u5546\u54c1\u5238GET\u3011<<visa\u30ae\u30d5\u30c8\u30ab\u30fc\u30c910000\u5186\u5206\u3092\u6bce\u6708\u62bd\u9078\u3067\u30d7\u30ec\u30bc\u30f3\u30c8>> \u21d2\u8a73\u3057\u304f\u306f\u4e0b\u306e\uff35\uff32\uff2c\u3088\u308a\u2193\u2193\u2193\u2193\u2193 http://minpon.jp/user_data/twitter_campaign.php","id":41189877940748288,"from_user_id":111308629,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twittbot.net/" rel="nofollow">twittbot.net</a>"},{"from_user_id_str":"140945098","profile_image_url":"http://a0.twimg.com/profile_images/1198948281/b7664c71-87bc-4187-9d46-a61ab8d41b96_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:46 +0000","from_user":"waruimayuko","id_str":"41189877122867200","metadata":{"result_type":"recent"},"to_user_id":113371008,"text":"@toumeisyoujyo \u3042\u3053\u3061\u3083\u3093Twitter\u3084\u3063\u3066\u305f\u306e\u306d\u3002\u307e\u3060\u304a\u5e2d\u3042\u308b\u305d\u3046\u306a\u306e\u3067\u662f\u975e\uff01","id":41189877122867200,"from_user_id":140945098,"to_user":"toumeisyoujyo","geo":null,"iso_language_code":"ja","to_user_id_str":"113371008","source":"<a href="http://twimi.jp/?r=via" rel="nofollow">twimi\u2606new</a>"},{"from_user_id_str":"167512527","profile_image_url":"http://a1.twimg.com/profile_images/1172286365/newspaper_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:45 +0000","from_user":"KoranKaget","id_str":"41189871775252480","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://bit.ly/93Eeud RT @motocentrism \u30d6\u30ed\u30b0\u8a18\u4e8b\u66f8\u304d\u307e\u3057\u305f\u30fc\uff1a MotoGP\u3000\u30d6\u30c3\u30af\u30e1\u30fc\u30ab\u30fc\u306b\u898b\u308b\u5404\u30e9\u30a4\u30c0\u30fc\u306e\u4e0b\u99ac\u8a55 - http://goo.gl/xVe6... http://bit.ly/hDYxyx @motogpudpate","id":41189871775252480,"from_user_id":167512527,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"160251772","profile_image_url":"http://a3.twimg.com/profile_images/1150692471/_____normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:45 +0000","from_user":"keikochaki","id_str":"41189870781075456","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u300c\u305a\u3063\u3068twitter\u3084\u3063\u3066\u308b\u3088\u306d\u300d\u3068\u6012\u3089\u308c\u3066\u3057\u307e\u3063\u305f(\u82e6\u7b11)","id":41189870781075456,"from_user_id":160251772,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twtr.jp" rel="nofollow">Keitai Web</a>"},{"from_user_id_str":"211565766","profile_image_url":"http://a2.twimg.com/sticky/default_profile_images/default_profile_5_normal.png","created_at":"Fri, 25 Feb 2011 17:36:42 +0000","from_user":"sayap1yo","id_str":"41189858236043264","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u304a\u98df\u4e8b\u4f1a\u884c\u304d\u305f\u304b\u3063\u305f\u3051\u3069\n\u53cb\u9054\u3068\u904a\u3093\u3067\u307e\u3093\u305f\ue056\ue326\n\nTwitter\u898b\u3066\u307e\u3057\u305f\u3051\u3069\n\u3064\u3076\u3084\u304f\u30bf\u30a4\u30df\u30f3\u30b0\n\u5931\u3063\u3066\u305f\u3060\u3051\u3067\u3059( \u00b4 \u25bd ` )\uff89\u7b11","id":41189858236043264,"from_user_id":211565766,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.nibirutech.com" rel="nofollow">TwitBird</a>"},{"from_user_id_str":"19603191","profile_image_url":"http://a1.twimg.com/profile_images/1254077264/116_normal.gif","created_at":"Fri, 25 Feb 2011 17:36:40 +0000","from_user":"Purple_Flash","id_str":"41189851873157120","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @syu_thi_bot: \u3044\u3064\u307e\u3067Twitter\u3084\u3063\u3066\u308b\u3093\u3060\u3044\uff1f\u3044\u3044\u52a0\u6e1b\u73fe\u5b9f\u306b\u623b\u308a\u306a\u3088\u3002\u3053\u3053\u306f\u30ad\u30df\u305f\u3061\u4e09\u6b21\u5143\u306e\u4eba\u9593\u304c\u3044\u308b\u3079\u304d\u5834\u6240\u3058\u3083\u306a\u3044\u3093\u3060\u3088\u3002\u305d\u3093\u306a\u306e\u57fa\u672c\u3060\u308d\uff01\uff01","id":41189851873157120,"from_user_id":19603191,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twittbot.net/" rel="nofollow">twittbot.net</a>"},{"from_user_id_str":"215930291","profile_image_url":"http://a0.twimg.com/profile_images/1247906106/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:30 +0000","from_user":"minori_millie","id_str":"41189810055938048","metadata":{"result_type":"recent"},"to_user_id":212972774,"text":"@c_c_chika \u7b11\u3063\u3066\u305d\u3046\u3060\u306a\u3063\u3066\u601d\u3063\u3066\u305f(o^^o)\u30c1\u30ab\u306e\u7b11\u3044\u58f0\u304c\u805e\u3053\u3048\u3066\u304d\u305f\u3082\u3093\u3002mail\u306bTwitter\u3067\u5927\u5fd9\u3057\u3084\u3002","id":41189810055938048,"from_user_id":215930291,"to_user":"c_c_chika","geo":null,"iso_language_code":"ja","to_user_id_str":"212972774","source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"197459334","profile_image_url":"http://a3.twimg.com/profile_images/1210698414/shiratorishoko_normal.png","created_at":"Fri, 25 Feb 2011 17:36:30 +0000","from_user":"SyokoShiratori","id_str":"41189809586311168","metadata":{"result_type":"recent"},"to_user_id":null,"text":"+0.90kg \u30c0\u30a4\u30a8\u30c3\u30c8\u5fdc\u63f4\u3057\u3066\u307e\u3059\u3002(*^^*)\u30c0\u30a4\u30a8\u30c3\u30c8\u4f53\u91cd\u5831\u544a\u306e\u3064\u3076\u3084\u304d\u3067\u3059\u3002 http://bit.ly/fhN2fM RT @hayayumi \u3053\u3093\u306a\u6642\u9593\u306b\u3084\u304d\u306b\u304f\u30fc\u266b\u30c0\u30a4\u30a8\u30c3\u30c8\u671f\u9593\u306a\u306e\u306b\u306d....","id":41189809586311168,"from_user_id":197459334,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://mob-mc.com" rel="nofollow">\uff08\u4eee\u79f0\uff09\u30c4\u30a4\u30af\u30ea\u30c3\u30af twiclick</a>"},{"from_user_id_str":"12337665","profile_image_url":"http://a0.twimg.com/profile_images/1146194926/pixiv-icon_normal.png","created_at":"Fri, 25 Feb 2011 17:36:27 +0000","from_user":"t_a_k_i","id_str":"41189797364121600","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Google\u30ea\u30fc\u30c0\u30fc\u3067\u30b5\u30a4\u30c8\u306e\u66f4\u65b0\u30c1\u30a7\u30c3\u30af\u3059\u308b\u3088\u308a\u3001Twitter\u30a2\u30ab\u30a6\u30f3\u30c8\u3092\u30d5\u30a9\u30ed\u30fc\u3057\u3066\u66f4\u65b0\u3092\u77e5\u308b\u307b\u3046\u304c\u4fbf\u5229\u3060\u306a\u3053\u308c","id":41189797364121600,"from_user_id":12337665,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sites.google.com/site/yorufukurou/" rel="nofollow">YoruFukurou</a>"},{"from_user_id_str":"104862453","profile_image_url":"http://a3.twimg.com/profile_images/1248609864/Image014_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:25 +0000","from_user":"yuz_ume","id_str":"41189787943714816","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @fuefukioyasumi: \u3082\u3046\u3044\u3044\u3002\u300c\u671d\u751f\u300d\u306a\u3093\u304b\u3044\u3044\u3002BBC\u3082CNN\u3082\u82f1\u8a9e\u653e\u9001\u3060\u3002\u307f\u3093\u306a\u3001\u30c6\u30ec\u30d3\u3092\u3076\u3061\u3063\u3068\u5207\u3063\u3066Twitter\u3092\u898b\u3088\u3046\u3002\u3053\u3053\u306b\u300c\u751f\u304d\u305f\u60c5\u5831\u300d\u304c\u6d41\u308c\u3066\u3044\u308b\u3002\u300c\u751f\u304d\u305f\u53eb\u3073\u300d\u304c\u3042\u308b\u3002\u3053\u3053\u304b\u3089\u3067\u3082\u6b74\u53f2\u306e\u8ee2\u63db\u70b9\u3092\u611f\u3058\u308b\u4e8b\u304c\u3067\u304d\u308b\u306e\u3060\u3002 @gjmorley #libjp","id":41189787943714816,"from_user_id":104862453,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"213846746","profile_image_url":"http://a1.twimg.com/profile_images/1242263342/haruhi1_normal.png","created_at":"Fri, 25 Feb 2011 17:36:23 +0000","from_user":"sloth888jpgame","id_str":"41189778409922560","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u643a\u5e2f\u96fb\u8a71\u7528\u306eTwitter\u3092\u5229\u7528\u3057\u305f\u30b2\u30fc\u30e0\u3092\u77e5\u3063\u3066\u3044\u308b\u4eba\u306f\u3001\u7d39\u4ecb\u3057\u3066\u304f\u3060\u3055\u3044\u3002 #TwitterGame","id":41189778409922560,"from_user_id":213846746,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twittbot.net/" rel="nofollow">twittbot.net</a>"},{"from_user_id_str":"17484724","profile_image_url":"http://a2.twimg.com/profile_images/1138677235/iconue_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:22 +0000","from_user":"tsutcho","id_str":"41189777831231490","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30a2\u30aa\u30b7\u30de\u3055\u3093twitter\u306b\u7acb\u3064\u30fb\u30fb\u30fb\u3060\u3068\u30fb\u30fb\u30fb\uff1f\uff12\u756a\u76ee\u306e\u30d5\u30a9\u30ed\u30ef\u30fc\u306e\u5ea7\u3092\u3044\u305f\u3060\u3044\u3066\u304a\u3053\u3046","id":41189777831231490,"from_user_id":17484724,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"220041064","profile_image_url":"http://a1.twimg.com/sticky/default_profile_images/default_profile_0_normal.png","created_at":"Fri, 25 Feb 2011 17:36:21 +0000","from_user":"sloth888jp_bot5","id_str":"41189772521254914","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6642\u3005\u3001TwiAll\uff08\u30c4\u30a4\u30aa\u30fc\u30eb\uff09\u3067Twitter\u306e\u81ea\u52d5\u30d5\u30a9\u30ed\u30fc\u30fb\u30d5\u30a9\u30ed\u30fc\u8fd4\u3057\u3092\u3057\u3066\u3044\u307e\u3059\u3002","id":41189772521254914,"from_user_id":220041064,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twittbot.net/" rel="nofollow">twittbot.net</a>"},{"from_user_id_str":"177693537","profile_image_url":"http://a0.twimg.com/profile_images/1240130924/20110207213206_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:21 +0000","from_user":"Na_Okinawa","id_str":"41189769912397824","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @ebizo66: \u30ea\u30d3\u30a2\u30fb\u30c8\u30ea\u30dd\u30ea\u306eTw\uff1a\u6551\u6025\u8eca\u304c\u6765\u305f\u304c\u3001\u8ca0\u50b7\u8005\u3092\u8eca\u5185\u3067\u6bba\u5bb3\u3057\u3066\u3044\u305f\u3001\u3068\u3002\uff08\u6ec5\u8336\u82e6\u8336\u3060\uff01\uff09http://ow.ly/43pQ2 #libjp","id":41189769912397824,"from_user_id":177693537,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"147006592","profile_image_url":"http://a2.twimg.com/profile_images/1251306448/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:19 +0000","from_user":"takasu_rika","id_str":"41189763532865536","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @kihirokiro: Twitter\u3067\u30cd\u30bf\u30d0\u30ec\u4e91\u3005\u3044\u3063\u3066\u3082\u5143\u3005Twitter\u3063\u3066\u300c\u500b\u4eba\u306e\u72ec\u308a\u8a00\u300d\u3060\u308d","id":41189763532865536,"from_user_id":147006592,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"100239985","profile_image_url":"http://a1.twimg.com/profile_images/733461294/CIMG0207_normal.JPG","created_at":"Fri, 25 Feb 2011 17:36:19 +0000","from_user":"strangebarjun","id_str":"41189762182152192","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Twitter\u3092\u59cb\u3081\u3066\u3001\u305d\u308d\u305d\u308d\u4e00\u5e74\u306b\u306a\u308a\u307e\u3059\u3002\u632f\u308a\u8fd4\u308b\u3068\u3001\u307c\u304f\u306e\u4eba\u9593\u6027\u3092\u305d\u3063\u304f\u308a\u53cd\u6620\u3059\u308b\u304c\u5982\u304f\u3001\u534a\u7aef\u3067\u3059\u306d\u3002\u60c5\u5831\u53ce\u96c6\u30c4\u30fc\u30eb\u3001\u60c5\u5831\u767a\u4fe1\u30c4\u30fc\u30eb\u3001\u30b3\u30df\u30e5\u30cb\u30b1\u30fc\u30b7\u30e7\u30f3\u30c4\u30fc\u30eb\u3001\u3069\u308c\u3082\u6a5f\u80fd\u3057\u5207\u308c\u3066\u3044\u306a\u3044\u306a\u3042\u3001\u3068\u3002\u305d\u3057\u3066\u3042\u308b\u306e\u306f\u300c\u3069\u3053\u304b\u3089\u3082\u76f8\u624b\u306b\u3055\u308c\u3066\u3044\u306a\u3044\u300d\u3068\u3044\u3046\u3001\u65e2\u77e5\u306e\u73fe\u5b9f\u3067\u3059\u3002","id":41189762182152192,"from_user_id":100239985,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"126390384","profile_image_url":"http://a2.twimg.com/profile_images/1176065038/nemunemu_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:18 +0000","from_user":"gesukapper","id_str":"41189757476286464","metadata":{"result_type":"recent"},"to_user_id":80935865,"text":"@tatsugorou \u306a\u3093\u304b\u4e16\u306e\u4e2d\u306b\u306f\u611a\u75f4\u3082\u4e0b\u30cd\u30bf\u3082\u8a00\u3044\u653e\u984c\u306etwitter\u3068\u3044\u3046\u3082\u306e\u304c\u3042\u308b\u305d\u3046\u3067\u3059\u3002","id":41189757476286464,"from_user_id":126390384,"to_user":"tatsugorou","geo":null,"iso_language_code":"ja","to_user_id_str":"80935865","source":"<a href="http://janetter.net/" rel="nofollow">Janetter</a>"},{"from_user_id_str":"196059029","profile_image_url":"http://a1.twimg.com/profile_images/1208831726/ruka2_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:17 +0000","from_user":"luka_m_bot","id_str":"41189756666777600","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u308f\u305f\u3057\u3082twitter\u306f\u3058\u3081\u307e\u3057\u305f","id":41189756666777600,"from_user_id":196059029,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www24.atpages.jp/aoi2/bot.php" rel="nofollow">\u5de1\u308b\u97f3</a>"},{"from_user_id_str":"88135613","profile_image_url":"http://a3.twimg.com/profile_images/1088552877/P9280150_normal.JPG","created_at":"Fri, 25 Feb 2011 17:36:14 +0000","from_user":"Roko38","id_str":"41189740321587200","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\uff46\uff42\u306b\u30ed\u30b0\u30a4\u30f3\u3059\u308b\u6a5f\u4f1a\u304c\u65e5\u306b\u65e5\u306b\u5897\u3048\u3066\u304d\u305f\uff3e\uff3e \u6163\u308c\u3066\u304f\u308b\u3068\u3042\u3063\u3061\u306e\u304c\u9762\u767d\u3044\uff06\u4f7f\u3044\u52dd\u624b\u304c\u3044\u3044\u3088\u3046\u306a\u6c17\u304c\u3059\u308b\u3002\u8907\u5408\u7684\u306b\u8272\u3005\u51fa\u6765\u307e\u3059\u3088\u306d\u2026\u3063\u3066\u3001\u601d\u3063\u305f\u3053\u3068\u3092\u545f\u304f\u306e\u306fTwitter\u3060\u3063\u305f\u308a\u3067\u3059\u304c\u2026(^_^; \u305d\u3057\u3066\u81ea\u5206\u306e\u5834\u5408\u306f\u30c4\u30a4\u3068\u9023\u52d5\u3057\u3065\u3089\u3044\u72b6\u6cc1\u3060\u3063\u305f\u308a\u3067\u2026\u3002","id":41189740321587200,"from_user_id":88135613,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"110825211","profile_image_url":"http://a2.twimg.com/profile_images/1108977866/o_t_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:12 +0000","from_user":"kou_nanjyo","id_str":"41189731941363712","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @x68k: \u57fa\u672c\u7684\u306bTwitter\u4e0a\u3067\u306f"\u597d\u304d\u306b\u3084\u308c\u3070\u3044\u3044"\u3060\u3051\u3069\u3001\u540d\u524d\u3082\u30a2\u30a4\u30b3\u30f3\u3082\u30a2\u30f3\u30bf\u3058\u3083\u306a\u3044\u305f\u304f\u3055\u3093\u306e\u4eba\u305f\u3061\u306e\u9b42\u304c\u3053\u3082\u3063\u305f\u3082\u306e\u306a\u306e\u3060\u304b\u3089\u3001\u305d\u308c\u3060\u3051\u306f"\u80cc\u8ca0\u3048"\u3068\u601d\u3046\uff1e\u30ad\u30e3\u30e9\u30af\u30bf\u30fc\u30a2\u30ab\u30a6\u30f3\u30c8","id":41189731941363712,"from_user_id":110825211,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://tweetlogix.com" rel="nofollow">Tweetlogix</a>"},{"from_user_id_str":"2095960","profile_image_url":"http://a2.twimg.com/profile_images/1248999075/majiresu2_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:10 +0000","from_user":"guldeen","id_str":"41189726945947648","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3042\u308a\u3083\u307e\u3041\u3002\u25bchttp://bit.ly/et4vVa \uff3b\u89d2\u5ddd\u66f8\u5e97\uff3d\u300c\u30b6\u30fb\u30b9\u30cb\u30fc\u30ab\u30fc\u300d\u4f11\u520a\u3078\u3000\u300c\u6dbc\u5bae\u30cf\u30eb\u30d2\u300d\u751f\u3093\u3060\u30e9\u30ce\u30d9\u96d1\u8a8c18\u5e74\u3067\u5e55 via http://twitter.com/lkj777","id":41189726945947648,"from_user_id":2095960,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"164121549","profile_image_url":"http://a1.twimg.com/profile_images/1251758789/m_108-07ae3_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:09 +0000","from_user":"hachi_touhi","id_str":"41189719299727360","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30cd\u30bf\u30d0\u30ec\u6c17\u306b\u3057\u3066\u305f\u3089Twitter\u3084\u3063\u3066\u3089\u308c\u306a\u3044ww","id":41189719299727360,"from_user_id":164121549,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twicca.r246.jp/" rel="nofollow">twicca</a>"},{"from_user_id_str":"194494659","profile_image_url":"http://a3.twimg.com/profile_images/1249717822/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:36:08 +0000","from_user":"tomonattomo","id_str":"41189715415801856","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3046\u308f\u3001\u660e\u65e5\u671d\u304b\u3089\u30d0\u30a4\u30c8\u3084\u306e\u306b\u306a\u3093\u3060\u3053\u306e\u306d\u3075\u304b\u3057\u3002\u3042\u3001\u591c\u66f4\u304b\u3057\u3002\u30d1\u30d4\u30eb\u30b9\u3068BUMP\u3001\u3048\u307f\u3068Twitter\u306eDM\u3057\u3059\u304e\u305f\u306a\u2026","id":41189715415801856,"from_user_id":194494659,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://mixi.jp/promotion.pl?id=voice_twitter" rel="nofollow"> mixi \u30dc\u30a4\u30b9 </a>"},{"from_user_id_str":"97224364","profile_image_url":"http://a3.twimg.com/profile_images/1150074355/fb8bcca60d340862c053a756377bfae8_normal.jpeg","created_at":"Fri, 25 Feb 2011 17:36:06 +0000","from_user":"xxxheat","id_str":"41189709174677504","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Twitter\u5b8c\u5168\u306b\u30d0\u30b0\u3063\u3066\u308borz","id":41189709174677504,"from_user_id":97224364,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"}],"max_id":41190705623732224,"since_id":38643906774044672,"refresh_url":"?since_id=41190705623732224&q=twitter","next_page":"?page=2&max_id=41190705623732224&rpp=100&lang=ja&q=twitter","results_per_page":100,"page":1,"completed_in":0.093336,"warning":"adjusted since_id to 38643906774044672 (), requested since_id was older than allowed -- since_id removed for pagination.","since_id_str":"38643906774044672","max_id_str":"41190705623732224","query":"twitter"} aeson-1.4.2.0/benchmarks/json-data/jp50.json0000755000000000000000000013012500000000000016563 0ustar0000000000000000{"results":[{"from_user_id_str":"2458313","profile_image_url":"http://a2.twimg.com/profile_images/1203653060/fure091226_normal.png","created_at":"Thu, 27 Jan 2011 20:30:04 +0000","from_user":"19princess","id_str":"30724239224995840","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6d77\u6674\u300c\u672c\u65e5\u306e\u6771\u4eac\u306e\u304a\u5929\u6c17\u306f\u6674\u6642\u3005\u66c7\u3067\u3057\u3087\u3046\u3002\u6700\u9ad8\u6c17\u6e29\u306f8\u5ea6\u3001\u6700\u4f4e\u6c17\u6e29\u306f1\u5ea6\u3067\u3059\u3002\u3042\u306a\u305f\u306e\u4eca\u65e5\u306e\u4eba\u751f\u306b\u3068\u3073\u3063\u304d\u308a\u306e\u304a\u5929\u6c17\u3092\u2665\u300d","id":30724239224995840,"from_user_id":2458313,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://babyprincess.sakura.ne.jp/about/" rel="nofollow">\u5929\u4f7f\u5bb6\u306e\u88cf\u5c71</a>"},{"from_user_id_str":"66578965","profile_image_url":"http://a0.twimg.com/profile_images/1183763267/fossetta_normal.png","created_at":"Thu, 27 Jan 2011 20:00:04 +0000","from_user":"Fossetta_Tokyo","id_str":"30716689779785729","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u304a\u306f\u3088\u3046\u3054\u3056\u3044\u307e\u3059!!\u6771\u4eac\u90fd\u3001\u672c\u65e5\u306e\u304a\u5929\u6c17\u306f\u6674\u6642\u3005\u66c7\u3002\u6700\u9ad8\u6c17\u6e298\u5ea6\u3001\u6700\u4f4e\u6c17\u6e291\u5ea6\u3002\u6771\u4eac\u5730\u65b9\u3067\u306f\u3001\u7a7a\u6c17\u306e\u4e7e\u71e5\u3057\u305f\u72b6\u614b\u304c\u7d9a\u3044\u3066\u3044\u307e\u3059\u3002\u706b\u306e\u53d6\u308a\u6271\u3044\u306b\u6ce8\u610f\u3057\u3066\u4e0b\u3055\u3044\u3002\u4f0a\u8c46\u8af8\u5cf6\u3068\u5c0f\u7b20\u539f\u8af8\u5cf6\u306b\u306f\u3001\u5f37\u98a8\u3001\u6ce2\u6d6a\u3001\u4e7e\u71e5\u3001\u971c\u306e\u6ce8\u610f\u5831\u3092\u767a\u8868\u4e2d\u3067\u3059\u3002","id":30716689779785729,"from_user_id":66578965,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://bit.ly/Fossetta" rel="nofollow">\u30d5\u30a9\u30bb\u30c3\u30bf ver.3.1.1</a>"},{"from_user_id_str":"104041146","profile_image_url":"http://a2.twimg.com/profile_images/863965118/001jwatokyo_normal.jpg","created_at":"Thu, 27 Jan 2011 19:44:33 +0000","from_user":"jwa_tokyo","id_str":"30712787537756160","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6c17\u8c61\u5e81\u304b\u3089\u6771\u4eac\u306e\u5929\u6c17\u4e88\u5831\u304c\u767a\u8868\u3055\u308c\u307e\u3057\u305f\u3000\u305d\u306e\u5929\u6c17\u4e88\u5831\u3092\u3053\u3053\u3067\u3064\u3076\u3084\u3053\u3046\u304b\u306a\u3041\uff5e\uff1f\u3000\u8003\u3048\u4e2d\u3000\u307e\u3066\u6b21\u53f7\uff08\u7b11","id":30712787537756160,"from_user_id":104041146,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.docodemo.jp/twil/" rel="nofollow">Twil2 (Tweet Anytime, Anywhere by Mail)</a>"},{"from_user_id_str":"144500192","profile_image_url":"http://a3.twimg.com/a/1294874399/images/default_profile_3_normal.png","created_at":"Thu, 27 Jan 2011 18:59:33 +0000","from_user":"kyo4to4","id_str":"30701462774358016","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u90fd \u516b\u4e08\u5cf6 - \u4eca\u65e5\u306e\u5929\u6c17\u306f\u30fb\u30fb\u30fb\u66c7\u306e\u3061\u6674\u3067\u3059\u306e\uff01","id":30701462774358016,"from_user_id":144500192,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/kyo4to4" rel="nofollow">lost-sheep-bot</a>"},{"from_user_id_str":"165724582","profile_image_url":"http://a0.twimg.com/profile_images/1222842347/163087_1256281064506_1753997852_484926_2761052_n_normal.jpg","created_at":"Thu, 27 Jan 2011 17:39:06 +0000","from_user":"Rifqi_19931020","id_str":"30681213748387840","metadata":{"result_type":"recent"},"to_user_id":113796067,"text":"@CHLionRagbaby \u30b1\u30f3\u3061\u3083\u3093\u3001\u671d\u4eca\u307e\u3067\u306e\u81ea\u5206\u306e\u30db\u30fc\u30e0\u30a8\u30ea\u30a2\u304b\u3089\u307e\u3060\u975e\u5e38\u306b\u5bd2\u3044\u3068\u96e8\u304c\u964d\u3063\u3066\u3044\u305f..\u3069\u306e\u3088\u3046\u306b\u73fe\u5728\u306e\u6771\u4eac\u306e\u5929\u6c17\uff1f","id":30681213748387840,"from_user_id":165724582,"to_user":"CHLionRagbaby","geo":null,"iso_language_code":"ja","to_user_id_str":"113796067","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"120911929","profile_image_url":"http://a0.twimg.com/profile_images/772435076/20100312___capture2_normal.png","created_at":"Thu, 27 Jan 2011 17:28:30 +0000","from_user":"Cirno_fan","id_str":"30678546020040705","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4eca\u65e5\u306e\u6771\u4eac\u306e\u5929\u6c17\u306f\u3001\u66c7\u6642\u3005\u6674\u3067\u6700\u9ad8\u6c17\u6e29\u306f8\u2103\uff01 \u6700\u4f4e\u6c17\u6e29\u306f2\u2103\u3060\u3063\u305f\u3088\uff01 RT @mimi22999 \uff08\uff65\u2200\uff65\uff09\uff4c\u3001\u865a\u5f31\u306a\u8005\u306b\u3068\u3063\u3066\u3001\u6717\u3089\u304b\u306a\u9854\u306f\u4e0a\u5929\u6c17\u3068\u540c\u3058\u304f\u3089\u3044\u3046\u308c\u3057\u3044\u3082\u306e\u3060\u3002\u30d5\u30e9\u30f3\u30af\u30ea\u30f3 #tenki #bot","id":30678546020040705,"from_user_id":120911929,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://blog.livedoor.jp/fairycirno/archives/34686.html" rel="nofollow">\u5e7b\u60f3\u90f7 \u9727\u306e\u6e56</a>"},{"from_user_id_str":"65976527","profile_image_url":"http://a0.twimg.com/profile_images/452810990/little_italies_____normal.jpg","created_at":"Thu, 27 Jan 2011 17:00:03 +0000","from_user":"heta_weather01","id_str":"30671388754845696","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3010\u30d8\u30bf\u5929\u3011Tere hommikust.\u30a8\u30b9\u30c8\u30cb\u30a2\u3067\u3059\u3002\u4eca\u65e5\u306e\u6771\u4eac\u306e\u5929\u6c17\u306f\u6674\u6642\u3005\u66c7\u3067\u660e\u65e5\u306f\u66c7\u308a\u3067\u3059\u3002\u3061\u306a\u307f\u306b\u50d5\u306e\u3068\u3053\u308d\u3067\u306f\u66c7\u308a\u3067\u6c17\u6e29-7\u2103\u3067\u3059\u3002\u3061\u306a\u307f\u306b\u30b9\u30ab\u30a4\u30d7\u306e\u958b\u767a\u672c\u90e8\u306f\u50d5\u306e\u5bb6\u306b\u3042\u308b\u3093\u3067\u3059\u3002","id":30671388754845696,"from_user_id":65976527,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www15.atpages.jp/~kageyanma/" rel="nofollow">\u5730\u7403\u306e\u4e2d</a>"},{"from_user_id_str":"7278433","profile_image_url":"http://a3.twimg.com/profile_images/1218965303/michael-1_normal.png","created_at":"Thu, 27 Jan 2011 16:50:16 +0000","from_user":"shimohiko","id_str":"30668926035689472","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3042\u308a\u3002\n\u3010\u7f8e\u4eba\u5929\u6c17/\u6771\u4eac\u3011\u7f8e\u4eba\u5929\u6c17\u30ad\u30e3\u30b9\u30bf\u30fc\u306e"\u3055\u3042\u3084\u3093\u3055\u3093"\u306b\u3088\u308b\u3068\u300c1/29(\u571f)\u306f\u304f\u3082\u308a\u3067\u3001\u964d\u6c34\u78ba\u738740%\u3001\u6700\u9ad8\u6c17\u6e29\u306f6\u2103\u3067\u6700\u4f4e\u6c17\u6e29\u306f1\u2103\u3067\u3059\u300d\u7f8e\u4eba\u5929\u6c17\u21d2http://bit.ly/djB8th http://twitpic.com/3twnl0 #bt_tenki","id":30668926035689472,"from_user_id":7278433,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://bijintenki.jp" rel="nofollow">bijintenki.jp</a>"},{"from_user_id_str":"61770","profile_image_url":"http://a3.twimg.com/profile_images/1206955079/tw172a_normal.png","created_at":"Thu, 27 Jan 2011 16:40:52 +0000","from_user":"rsky","id_str":"30666561853333504","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3075\u3068\u591c\u7a7a\u3092\u898b\u4e0a\u3052\u3066\u30aa\u30ea\u30aa\u30f3\u304c\u898b\u3048\u306a\u304f\u3066\u300c\u6771\u4eac\u306b\u306f\u7a7a\u304c\u306a\u3044\u300d\u3068\u667a\u6075\u5b50\u306e\u3088\u3046\u306a\u3053\u3068\u3092\u601d\u3063\u305f\u308f\u3051\u3060\u304c\u3001\u305f\u3076\u3093\u534a\u5206\u3050\u3089\u3044\u306f\u5929\u6c17\u306e\u305b\u3044\u3067\u3059","id":30666561853333504,"from_user_id":61770,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"103259265","profile_image_url":"http://a0.twimg.com/profile_images/767857973/anime_icon_normal.gif","created_at":"Thu, 27 Jan 2011 16:37:42 +0000","from_user":"liveshowonly","id_str":"30665765698928640","metadata":{"result_type":"recent"},"to_user_id":null,"text":"iPhone\u5929\u6c17\u3002\u6771\u4eac4\u2103\u3063\u3066\u7d50\u69cb\u5bd2\u304f\u306a\u3044\u3058\u3083\u3093\u3002\uff08\u78ba\u304b\u306b\u3082\u306e\u51c4\u304f\u5bd2\u3044\u8a33\u3067\u306f\u7121\u3044\uff09\u3002\u798f\u5ca1\u5e02\u306f1\u2103\u3060\u3002\u52dd\u3061\u3060\u305c\u3002Rock'n'roll","id":30665765698928640,"from_user_id":103259265,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"165242761","profile_image_url":"http://a1.twimg.com/profile_images/1147334744/SN3E00600001_normal.jpg","created_at":"Thu, 27 Jan 2011 16:37:35 +0000","from_user":"deuxavril0502","id_str":"30665736556912640","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6b8b\u5ff5\u3001\u79c1\u306f\u6c96\u7e04\u3067\u3059(>_<)\u3067\u3082\u304a\u5929\u6c17\u826f\u3055\u305d\u3046\u3067\u826f\u304b\u3063\u305f\u306d\u3002\u3053\u3061\u3089\u306f\u96e8\u3088\uff5eRT @rinandy2010: \u305d\u3046\u3067\u3059\u3063\u266a\u51fa\u5f35\u3067(^^)\u304a\u306d\u3048\u3055\u307e\u306f\u6771\u4eac\u3067\u3059\u304b\uff1f\u3081\u3063\u3061\u3083\u5929\u6c17\u826f\u304f\u3066\u3073\u3063\u304f\u308a\u3067\u3059\u3002\u624b\u888b\u3068\u304b\u5168\u7136\u3044\u3089\u306a\u3044\u3067\u3059\u306d\u30fc RT @deuxavril0502 \u6771\u4eac\u306a\u306e\u30fc\uff1f","id":30665736556912640,"from_user_id":165242761,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"163900288","profile_image_url":"http://a1.twimg.com/profile_images/1210224823/icon12945064955238_normal.jpg","created_at":"Thu, 27 Jan 2011 16:24:37 +0000","from_user":"nyao_yurichan","id_str":"30662472734089216","metadata":{"result_type":"recent"},"to_user_id":100985873,"text":"@ray_ko302 \u767a\u898b\u3042\u308a\u304c\u3068\u3067\u3059\u3045\u3002\u3053\u3061\u3089\u3067\u3082\u3088\u308d\u3057\u304f\u306d\u3002\u6771\u4eac\u306f\u4eca\u65e5\u3082\u4e7e\u71e5\u3067\u5927\u5909\u3088\u3002\u305d\u3063\u3061\u3068\u771f\u9006\u306e\u5929\u6c17\u3060\u306d\u3002\u30a2\u30a4\u30b9\u30d0\u30fc\u30f3\u304d\u3092\u3064\u3051\u3066\u3088\u306d\u3002","id":30662472734089216,"from_user_id":163900288,"to_user":"ray_ko302","geo":null,"iso_language_code":"ja","to_user_id_str":"100985873","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"49227098","profile_image_url":"http://a3.twimg.com/profile_images/965007882/____normal.jpg","created_at":"Thu, 27 Jan 2011 15:52:26 +0000","from_user":"dosannko6","id_str":"30654371016478720","metadata":{"result_type":"recent"},"to_user_id":108570870,"text":"@peke_hajiP \u4ffa\u304c\u6771\u4eac \u6765\u3066\u6700\u521d\u306b\u9a5a\u3044\u305f\u306e\u304c\u3001\u5929\u6c17\u4e88\u5831\u3067\u82b1\u7c89\u60c5\u5831\u304c\u6d41\u308c\u308b\u3053\u3068\u3067\u3001\u6700\u521d\u306b\u8a66\u3057\u305f\u306e\u304c \u30b4\u30ad\u69d8 \u53ec\u559a\u306e\u5100\u5f0f\u3067\u3059\u304a\uff1f","id":30654371016478720,"from_user_id":49227098,"to_user":"peke_hajip","geo":null,"iso_language_code":"ja","to_user_id_str":"108570870","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"71148934","profile_image_url":"http://a0.twimg.com/profile_images/1209223630/image_normal.jpg","created_at":"Thu, 27 Jan 2011 15:46:49 +0000","from_user":"123keiko","id_str":"30652958311981058","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u9727\u5cf6\u306e\u964d\u7070\u306e\u30cb\u30e5\u30fc\u30b9\u3092\u898b\u3066\u601d\u3044\u51fa\u3057\u307e\u3057\u305f\u3002\u4e0a\u4eac\u3057\u305f\u59cb\u3081\u306e\u9803\u3001\u6771\u4eac\u306f1\u5e74\u4e2d\u3001\u7070\u304c\u964d\u3089\u306a\u3044\u304b\u3089\u7a7a\u6c17\u304c\u6f84\u3093\u3067\u3066\u904e\u3054\u3057\u3084\u3059\u3044\u306a\u3041\u3001\u3068\u601d\u3063\u305f\u306a\u3041\u3001\u3063\u3066\u3002\n\u5b9f\u5bb6\u306f\u51ac\u306e\u5b63\u7bc0\u98a8\u3067\u685c\u5cf6\u306e\u7070\u304c\u964d\u308b\u5730\u533a\u3067\u3057\u305f\u3002\u9e7f\u5150\u5cf6\u306e\u5929\u6c17\u4e88\u5831\u3067\u306f\u3001\u6bce\u65e5\u3001\u685c\u5cf6\u4e0a\u7a7a\u306e\u98a8\u5411\u304d\u4e88\u5831\u304c\u3067\u307e\u3059\u3002\u3053\u308c\u304b\u3089\u306f\u9727\u5cf6\u3082\u304b\u306a\uff1f","id":30652958311981058,"from_user_id":71148934,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"91124773","profile_image_url":"http://a3.twimg.com/profile_images/1139308356/prof101007_3-1_normal.jpg","created_at":"Thu, 27 Jan 2011 15:43:35 +0000","from_user":"sanposuruhito","id_str":"30652146277945345","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4eca\u5bb5\u306e\u90fd\u5fc3\u306f\u3001\u8eab\u3082\u5f15\u304d\u7de0\u307e\u308b\u3068\u3044\u3046\u3088\u308a\u306f\u51cd\u3048\u308b\u7a0b\u306e\u51b7\u6c17\u3092\u611f\u3058\u308b\u5bd2\u3044\u591c\u3067\u3059\u3002\u660e\u65e5\u65e5\u4e2d\u306e\u6771\u4eac\u306e\u5929\u6c17\u306f\u3001\u5915\u65b9\u306b\u591a\u5c11\u96f2\u304c\u51fa\u308b\u5834\u6240\u304c\u3042\u308a\u305d\u3046\u306a\u3082\u306e\u306e\u6982\u306d\u6674\u308c\u7a7a\u304c\u5e83\u304c\u308a\u7d9a\u3051\u305d\u3046\u3067\u3059\u3002\u6700\u9ad8\u6c17\u6e29\u306f\u30015-6\u5ea6\u4f4d\u3068\u306a\u308a\u305d\u3046\u3067\u3059\u3002#weather_tokyo","id":30652146277945345,"from_user_id":91124773,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://projects.playwell.jp/go/Saezuri" rel="nofollow">Saezuri</a>"},{"from_user_id_str":"104712480","profile_image_url":"http://a3.twimg.com/profile_images/1204016928/icon5087697006727791368kuro2_normal.jpg","created_at":"Thu, 27 Jan 2011 15:31:51 +0000","from_user":"asongfor_xx","id_str":"30649192296751104","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u7f8e\u4eba\u5929\u6c17\u304b\u3089tweet\u3059\u308b\u3068\u3053\u3093\u306a\u611f\u3058\u306a\u3093\u3060\u306a\u3002 RT asongfor_xx: \u3010\u7f8e\u4eba\u5929\u6c17/\u6771\u4eac\u3011\u7f8e\u4eba\u5929\u6c17\u30ad\u30e3\u30b9\u30bf\u30fc\u306e"\u304b\u306a\u3053\u3055\u3093"\u306b\u3088\u308b\u3068\u300c1/28(\u91d1)\u306f\u6674\u6642\u3005\u304f\u3082\u308a\u3067\u3001\u964d\u6c34\u78ba\u73870%\u3001\u6700\u9ad8\u6c17\u6e29\u306f8\u2103\u3067\u6700\u4f4e\u6c17\u6e29\u306f1\u2103\u3067\u3059\u300d\u7f8e\u4eba\u5929\u6c17\u21d2http://bit.ly/djB8th","id":30649192296751104,"from_user_id":104712480,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b for iPhone</a>"},{"from_user_id_str":"165965113","profile_image_url":"http://a0.twimg.com/profile_images/1200885316/shogomeguro_normal.jpg","created_at":"Thu, 27 Jan 2011 15:24:35 +0000","from_user":"shogomeguro","id_str":"30647362477105152","metadata":{"result_type":"recent"},"to_user_id":null,"text":"2011.1.26 \u793e\u7a93\u304b\u3089\u3002\u4e0d\u601d\u8b70\u306a\u5929\u6c17\u3067\u3053\u306e\u5f8c\u96ea\u304c\u3061\u3089\u3064\u3044\u305f\u3093\u3060\u3088\u306d\u3002\u6771\u4eac\u306e\u521d\u96ea\u3067\u3057\u305f\u3002 http://instagr.am/p/BO_xn/","id":30647362477105152,"from_user_id":165965113,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://instagr.am" rel="nofollow">instagram</a>"},{"from_user_id_str":"166018520","profile_image_url":"http://a0.twimg.com/profile_images/1207460953/100-40030_normal.jpg","created_at":"Thu, 27 Jan 2011 15:18:17 +0000","from_user":"115nayume","id_str":"30645776254238722","metadata":{"result_type":"recent"},"to_user_id":118384679,"text":"@dancinpea09 \u6771\u4eac\u3001\u660e\u65e5\u3082\u5929\u6c17\u826f\u3044\u307f\u305f\u3044\u3067\u3001\u3088\u304b\u3063\u305f\u3067\u3059\u306d\u30fc\u266a \u30ca\u30a4\u30b9\u30c8\u30ea\u30c3\u30d7\uff01\u304a\u3084\u3059\u307f\u306a\u3055\u3044\u3002 http://twitpic.com/3tvun3","id":30645776254238722,"from_user_id":166018520,"to_user":"dancinpea09","geo":null,"iso_language_code":"ja","to_user_id_str":"118384679","source":"<a href="http://tweetli.st/" rel="nofollow">TweetList!</a>"},{"from_user_id_str":"202937674","profile_image_url":"http://a1.twimg.com/profile_images/1218797578/______2_normal.jpg","created_at":"Thu, 27 Jan 2011 15:11:48 +0000","from_user":"ryuusisan","id_str":"30644146498699264","metadata":{"result_type":"recent"},"to_user_id":203058384,"text":"@manaasutakshi \u6771\u4eac\u306f\u964d\u3063\u3066\u306a\u3044\u3093\u3067\u3059\u304b\u30fb\u30fb\u30fb\u5929\u6c17\u4e88\u5831\u306b\u3088\u308b\u3068\u660e\u65e5\u3082\u6771\u4eac\u306f\u964d\u3089\u306a\u3044\u305d\u3046\u3067\u3059\u306d\uff01\uff01\u79c1\u306e\u4f4f\u3093\u3067\u3044\u308b\u3068\u3053\u308d\u306f\u5fae\u5999\u306b\u964d\u308a\u305d\u3046\u3067\u51fa\u52e4\u6642\u306b\u964d\u3063\u3066\u305f\u3089\u3061\u3087\u3063\u3068\u5acc\u3060\u306a\u3041\u3000\u306a\u3093\u3066\u601d\u3044\u307e\u3059","id":30644146498699264,"from_user_id":202937674,"to_user":"manaasutakshi","geo":null,"iso_language_code":"ja","to_user_id_str":"203058384","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"3222182","profile_image_url":"http://a0.twimg.com/profile_images/1199090957/ProfilePhoto_normal.png","created_at":"Thu, 27 Jan 2011 15:09:35 +0000","from_user":"44mune","id_str":"30643589545459713","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3010\u7f8e\u4eba\u5929\u6c17/\u6771\u4eac\u3011\u7f8e\u4eba\u5929\u6c17\u30ad\u30e3\u30b9\u30bf\u30fc\u306e"\u306e\u308a\u3055\u3093"\u306b\u3088\u308b\u3068\u300c1/28(\u91d1)\u306f\u304f\u3082\u308a\u306e\u3061\u6674\u3067\u3001\u964d\u6c34\u78ba\u738710%\u3001\u6700\u9ad8\u6c17\u6e29\u306f9\u2103\u3067\u6700\u4f4e\u6c17\u6e29\u306f2\u2103\u3067\u3059\u300d http://twitpic.com/3tvruh","id":30643589545459713,"from_user_id":3222182,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://bijintenki.jp" rel="nofollow">bijintenki.jp</a>"},{"from_user_id_str":"154341982","profile_image_url":"http://a0.twimg.com/profile_images/1155496864/_____normal.jpg","created_at":"Thu, 27 Jan 2011 15:02:39 +0000","from_user":"slave_420_bot","id_str":"30641845490946049","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4eca\u30f3\u3068\u3053\u899a\u3048\u3066\u308b\u306e\u306f\u300c\u672d\u5e4c\u300d\u300c\u4ed9\u53f0\u300d\u300c\u6771\u4eac\u300d\u300c\u5927\u962a\u300d\u300c\u540d\u53e4\u5c4b\u300d\u300c\u798f\u5ca1\u300d\u306e\u4eca\u65e5\u3068\u660e\u65e5\u306e\u5929\u6c17\u3060\u306a\u3002\u5929\u6c17\u304c\u77e5\u308a\u305f\u3044\u6642\u306f\u300c\u5834\u6240\u300d\u3068\u300c\u4eca\u65e5\u306e\u5929\u6c17\u300d\u304b\u300c\u660e\u65e5\u306e\u5929\u6c17\u300d\u3092\u304a\u7533\u3057\u4ed8\u3051\u304f\u3060\u3055\u3044\u3001\u304a\u5b22\u69d8\uff1f","id":30641845490946049,"from_user_id":154341982,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://bot.syoyu.net/" rel="nofollow">\u7adc\u30f6\u5cf0\u90b8\u306e\u3069\u3053\u304b</a>"},{"from_user_id_str":"72042678","profile_image_url":"http://a3.twimg.com/profile_images/1198771027/larxene_normal.jpg","created_at":"Thu, 27 Jan 2011 15:01:57 +0000","from_user":"larxene_bot","id_str":"30641668772339712","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4eca\u65e5\u306e\u5929\u6c17\u306f \u672d\u5e4c\u304c\u6674\u308c \u4ed9\u53f0\u304c\u66c7\u6642\u3005\u96ea \u6771\u4eac\u304c\u6674\u306e\u3061\u66c7 \u540d\u53e4\u5c4b\u304c\u6674\u6642\u3005\u66c7 \u5927\u962a\u304c\u6674\u6642\u3005\u66c7 \u798f\u5ca1\u304c\u6674\u308c \u3089\u3057\u3044\u308f\u3088 \u6ce8\u610f\u3057\u306a\u3055\u3044","id":30641668772339712,"from_user_id":72042678,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www4.kiwi-us.com/~yuuna/larxene_bot_manual/index.html" rel="nofollow">\u5fd8\u5374\u306e\u57ce \u5730\u4e0a\u306e12\u968e</a>"},{"from_user_id_str":"101331893","profile_image_url":"http://a1.twimg.com/sticky/default_profile_images/default_profile_0_normal.png","created_at":"Thu, 27 Jan 2011 15:01:34 +0000","from_user":"yoshiftan","id_str":"30641572240424961","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306e\u5929\u6c17\u4e88\u5831\u3092\u898b\u3066\u3073\u3063\u304f\u308a\uff01\u6691\u305d\u3046\u3060\u306a\u3053\u308a\u3083\u3002","id":30641572240424961,"from_user_id":101331893,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"Keitai Mail"},{"from_user_id_str":"65207550","profile_image_url":"http://a3.twimg.com/profile_images/448731969/_________R_normal.jpg","created_at":"Thu, 27 Jan 2011 15:01:33 +0000","from_user":"kabuyo","id_str":"30641566469066752","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u5929\u6c17\u4e88\u5831\u3067\u306f\u6771\u4eac\u3067\u306f\u4e7e\u71e5\u6ce8\u610f\u5831\u304c\u7d9a\u3044\u3066\u3044\u308b\u3089\u3057\u3044\u306e\u306b\u3001\u306a\u305c\u79c1\u304c\u5e72\u3057\u305f\u6d17\u6fef\u7269\u306f\u96e8\u306b\u6fe1\u308c\u3066\u3057\u307e\u3063\u305f\u306e\u3060\u308d\u3046\u304b\u2025\u3000\u3088\u3063\u307d\u3069\u904b\u304c\u60aa\u3044\u3089\u3057\u3044\u2025","id":30641566469066752,"from_user_id":65207550,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"80309352","profile_image_url":"http://a1.twimg.com/profile_images/1223620418/image_normal.jpg","created_at":"Thu, 27 Jan 2011 14:54:30 +0000","from_user":"mikutyan","id_str":"30639792026812416","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306e\u660e\u65e5\u306e\u5929\u6c17\u6559\u3048\u3066","id":30639792026812416,"from_user_id":80309352,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"80309352","profile_image_url":"http://a1.twimg.com/profile_images/1223620418/image_normal.jpg","created_at":"Thu, 27 Jan 2011 14:53:06 +0000","from_user":"mikutyan","id_str":"30639439847890944","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u660e\u65e5\u306e\u6771\u4eac\u306e\u5929\u6c17\u306a\u3093\u3060\u308d\u3046 \u96e8\u964d\u3063\u305f\u3089\u56f0\u308b\u3002","id":30639439847890944,"from_user_id":80309352,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"120911929","profile_image_url":"http://a0.twimg.com/profile_images/772435076/20100312___capture2_normal.png","created_at":"Thu, 27 Jan 2011 14:47:19 +0000","from_user":"Cirno_fan","id_str":"30637984684449792","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3042\u305f\u3044\u30c1\u30eb\u30ce\uff01\u30dc\u30c3\u30c8\u3060\u3051\u3069\u5929\u6c17\u4e88\u5831\u3082\u3067\u304d\u308b\u3088\uff01\u300c\u6771\u4eac\u306e\u4eca\u65e5\u306e\u5929\u6c17\u6559\u3048\u3066\u300d\u307f\u305f\u3044\u306bTL\u767a\u8a00\u3057\u3066\u304f\u308c\u308c\u3070\u8abf\u3079\u3066\u3042\u3052\u308b\uff01 #followme #followmejp #followmevip #tenki","id":30637984684449792,"from_user_id":120911929,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://blog.livedoor.jp/fairycirno/archives/34686.html" rel="nofollow">\u5e7b\u60f3\u90f7 \u9727\u306e\u6e56</a>"},{"from_user_id_str":"33858777","profile_image_url":"http://a0.twimg.com/profile_images/352864695/muga_normal.jpg","created_at":"Thu, 27 Jan 2011 14:46:12 +0000","from_user":"collonist","id_str":"30637702105796610","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u3063\u3066\u51ac\u306f\u57fa\u672c\u7684\u306b\u6674\u308c\u3066\u308b\u304b\u3089\u3001\u5929\u6c17\u4e88\u5831\u898b\u306a\u304f\u3066\u3082\u5168\u7136\u554f\u984c\u306a\u3044\u3002\u5c71\u5f62\u3060\u3068\u660e\u65e5\u306f\u3069\u3093\u3060\u3051\u96ea\u304c\u964d\u308b\u306e\u304b\u3001\u3069\u3093\u3060\u3051\u5bd2\u3044\u306e\u304b\u628a\u63e1\u3057\u3066\u3068\u304d\u305f\u3044\u306e\u3067\u3001\u5929\u6c17\u4e88\u5831\u306f\u5fc5\u305a\u30c1\u30a7\u30c3\u30af\u3057\u3066\u305f\u306e\u3060\u304c\u3002","id":30637702105796610,"from_user_id":33858777,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"79336228","profile_image_url":"http://a0.twimg.com/profile_images/1130029876/zmanmu_normal.png","created_at":"Thu, 27 Jan 2011 14:30:23 +0000","from_user":"atsuki777","id_str":"30633725041573890","metadata":{"result_type":"recent"},"to_user_id":null,"text":"MXTV\u306e\u5929\u6c17\u4e88\u5831\u521d\u3081\u3066\u898b\u305f\u3051\u3069\u6771\u4eac\u753a\u7530\u516b\u738b\u5b50\u3063\u3066\u5730\u57df\u8868\u793a\u304c\u2026w\u516b\u738b\u5b50\u3068\u753a\u7530\u306f\u6771\u4eac\u3058\u3083\u306a\u3044\u306e\u304bwww","id":30633725041573890,"from_user_id":79336228,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"90576097","profile_image_url":"http://a0.twimg.com/profile_images/1203320254/nanami1_normal.png","created_at":"Thu, 27 Jan 2011 14:28:26 +0000","from_user":"dycroft","id_str":"30633234245099521","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306e\u660e\u65e5\u306e\u304a\u5929\u6c17\u3067\u3059","id":30633234245099521,"from_user_id":90576097,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"147215268","profile_image_url":"http://a2.twimg.com/profile_images/1198555202/ichika-7.4.0-3P_normal.gif","created_at":"Thu, 27 Jan 2011 14:28:23 +0000","from_user":"kiaran5032","id_str":"30633222211637248","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306e\u660e\u65e5\u306e\u304a\u5929\u6c17\u3067\u3059\u3002\u6674\u308c\u6642\u3005\u304f\u3082\u308a #MX","id":30633222211637248,"from_user_id":147215268,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"1741599","profile_image_url":"http://a0.twimg.com/profile_images/1205744888/950637_normal.jpg","created_at":"Thu, 27 Jan 2011 14:28:21 +0000","from_user":"dasaitama","id_str":"30633212535382016","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306e\u3001\u660e\u65e5\u306e\u304a\u5929\u6c17\u3067\u3059","id":30633212535382016,"from_user_id":1741599,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"34140879","profile_image_url":"http://a3.twimg.com/profile_images/1186413535/__6_normal.jpg","created_at":"Thu, 27 Jan 2011 14:28:17 +0000","from_user":"ryuji_chaos","id_str":"30633197016449024","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306e\u660e\u65e5\u306e\u304a\u5929\u6c17\u3067\u3059\u3002","id":30633197016449024,"from_user_id":34140879,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"1400","profile_image_url":"http://a0.twimg.com/profile_images/1198556839/westerndog_20090104_320x320_normal.jpg","created_at":"Thu, 27 Jan 2011 14:28:16 +0000","from_user":"westerndog","id_str":"30633191232503808","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306e\u660e\u65e5\u306e\u304a\u5929\u6c17\u3067\u3059","id":30633191232503808,"from_user_id":1400,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"89239832","profile_image_url":"http://a3.twimg.com/profile_images/519522846/noriko_normal.jpg","created_at":"Thu, 27 Jan 2011 14:15:01 +0000","from_user":"Noriko_Fujimoto","id_str":"30629857234788352","metadata":{"result_type":"recent"},"to_user_id":115645219,"text":"@nossa430402 \u5bcc\u5c71\u306f\u3059\u3054\u3044\u96ea\u307f\u305f\u3044\u3067\u3059\u306d\uff5e\uff08\u5bd2\u3063\uff09\u3000\u6771\u4eac\u306f\u305d\u306e\u5206\u6bce\u65e5\u826f\u3044\u5929\u6c17\u3067\u3059\u3002\u5bd2\u3044\u3051\u3069\u30fb\u30fb\u30fb\u3002","id":30629857234788352,"from_user_id":89239832,"to_user":"nossa430402","geo":null,"iso_language_code":"ja","to_user_id_str":"115645219","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"107265539","profile_image_url":"http://a0.twimg.com/sticky/default_profile_images/default_profile_3_normal.png","created_at":"Thu, 27 Jan 2011 14:01:10 +0000","from_user":"kurumasuki330","id_str":"30626371826884608","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u4eca\u9031\u571f\u66dc\u65e5\u3001\u8eca\u3067\u6771\u4eac\u304b\u3089\u6771\u540d\u3001\u7c73\u539f\u7d4c\u7531\u3067\u91d1\u6ca2\u306e\u5b9f\u5bb6\u3078\u3002\u305d\u3057\u3066\u3001\u6708\u66dc\u65e5\u306b\u6771\u4eac\u3078\u5e30\u308b\u30b9\u30b1\u30b8\u30e5\u30fc\u30eb\u3002\u5929\u6c17\u4e88\u5831\u3060\u3068\u4eca\u9031\u672b\u3001\u5317\u9678\u5730\u65b9\u306f\u5927\u96ea\uff01\u5e30\u308c\u308b\u304b\u81ea\u4fe1\u304c\u306a\u304f\u306a\u3063\u3066\u304d\u305f\u3002\u307e\u305f\u3001\u305d\u306e\u6642\u5b9f\u6cc1\u4e2d\u7d99\u3057\u307e\u3059\u3002","id":30626371826884608,"from_user_id":107265539,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twtr.jp" rel="nofollow">Keitai Web</a>"},{"from_user_id_str":"155313166","profile_image_url":"http://a3.twimg.com/profile_images/1167554721/73931_1408370184003_1674923704_920888_5686998_n_normal.jpg","created_at":"Thu, 27 Jan 2011 14:00:50 +0000","from_user":"takuya_aoki","id_str":"30626287127105536","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306f\u3081\u3063\u3061\u3083\u3044\u3044\u5929\u6c17\u3067\u904e\u3054\u3057\u3084\u3059\u3044\u3051\u3069\u30c9\u30e9\u30a4\u30a2\u30a4\u306b\u306f\u3061\u3087\u3063\u3068\u304d\u3064\u3044\u306a\u30fb\u30fb\u30fb\u76ee\u85ac\u304c\u624b\u653e\u305b\u306a\u3044","id":30626287127105536,"from_user_id":155313166,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"179984398","profile_image_url":"http://a1.twimg.com/profile_images/1182382310/g4350_normal.jpg","created_at":"Thu, 27 Jan 2011 13:52:50 +0000","from_user":"aiilabo","id_str":"30624271902449664","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u30d6\u30ed\u30b0\u66f4\u65b0 \u25c6\u611f\u60c5\u3092\u307f\u3064\u3081\u308b\u65b9\u6cd5 - \u3053\u3053\u6570\u65e5\u3001\u6642\u6298\u96e8\u304c\u30d1\u30e9\u30d1\u30e9\u3000\u5fae\u5999\u306a\u5929\u6c17\u306e\u6771\u4eac\u304b\u3089\u3042\u308b\u304c\u307e\u307e\u3067\u3059\u3002 \n\n \u4eca\u65e5\u306f\u3001\u6628\u65e5\u306e\u300c\u30de\u30a4\u30ca\u30b9\u611f\u60c5\u306f\u60aa\u3067\u3059\u304b\uff1f\n.. \u27aa http://am6.jp/e3e9tS","id":30624271902449664,"from_user_id":179984398,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://feedtweet.am6.jp/" rel="nofollow">\u261e feedtweet.jp \u261c</a>"},{"from_user_id_str":"185992391","profile_image_url":"http://a2.twimg.com/profile_images/1192695844/otenki_normal.png","created_at":"Thu, 27 Jan 2011 13:00:37 +0000","from_user":"otenki_luci_bot","id_str":"30611130938298368","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u767a\u58f2\u65e5\u304b\u2026\u2026\u541b\u305f\u3061\u306b\u3068\u3063\u3066\u306f\u591a\u5206\u300190\u65e5\u5f8c\u306e\u3053\u3068\u3060\u3002\u3055\u3066\u660e\u65e5\u306e\u6771\u4eac\u90fd\u306e\u5929\u6c17\u306f\u6674\u306e\u3061\u66c7\u3001\u6700\u9ad8\u6c17\u6e29\u306f8\u5ea6\u3060\u305d\u3046\u3060\u3002\u3055\u3059\u304c\u306b\u4f55\u304b\u7740\u305f\u65b9\u304c\u3044\u3044\u305e\u3001\u30a4\u30fc\u30ce\u30c3\u30af\u3002","id":30611130938298368,"from_user_id":185992391,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/otenki_luci_bot" rel="nofollow">\u304a\u3066\u3093\u304d\u308b\u3057\u3075\u3047\u308b</a>"},{"from_user_id_str":"65976527","profile_image_url":"http://a0.twimg.com/profile_images/452810990/little_italies_____normal.jpg","created_at":"Thu, 27 Jan 2011 13:00:04 +0000","from_user":"heta_weather01","id_str":"30610995843964928","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3010\u30d8\u30bf\u5929\u3011Jo napot.\u30cf\u30f3\u30ac\u30ea\u30fc\u3067\u3059\u3002\u6771\u4eac\u306e\u5929\u6c17\u306f\u6674\u306e\u3061\u66c7\u3067\u660e\u65e5\u306f\u6674\u6642\u3005\u66c7\u3001\u79c1\u306e\u3068\u3053\u308d\u3067\u306f\u66c7\u308a\u3067-2\u2103\u3067\u3059\u3002\u3048\u3001\u3053\u306e\u30d5\u30e9\u30a4\u30d1\u30f3\u3067\u3059\u304b\uff1f\u2026\u3061\u3087\u3063\u3068\u500b\u4eba\u7684\u306b\u6bb4\u308a\u305f\u3044\u4eba\u304c\u3044\u308b\u3093\u3067\u3059\u266a","id":30610995843964928,"from_user_id":65976527,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www15.atpages.jp/~kageyanma/" rel="nofollow">\u5730\u7403\u306e\u4e2d</a>"},{"from_user_id_str":"109740077","profile_image_url":"http://a0.twimg.com/profile_images/1212763349/1d3d3821-6b3a-449f-a636-05b95ce3d5d8_normal.png","created_at":"Thu, 27 Jan 2011 12:59:41 +0000","from_user":"snow_arai","id_str":"30610896141156354","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u6771\u4eac\u306f\u3001\u30ab\u30e9\u30ab\u30e9\u9023\u7d9a\u3000\uff13\u4f4d\u30bf\u30a4 - \u65e9\u8d77\u304d\u2606\u304a\u5929\u6c17\u2606ONAIR\u65e5\u8a18\uff1a\u65e5\u7d4c\u30a6\u30fc\u30de\u30f3\u30aa\u30f3\u30e9\u30a4\u30f3 http://j.mp/hxP3Di","id":30610896141156354,"from_user_id":109740077,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"53407951","profile_image_url":"http://a1.twimg.com/profile_images/397960795/airman_normal.jpg","created_at":"Thu, 27 Jan 2011 12:57:32 +0000","from_user":"Airman2009","id_str":"30610355541508096","metadata":{"result_type":"recent"},"to_user_id":null,"text":". @04mmy22 @qsk1 \u98a8\u3068\u96f2\u30fb\u30fb\u30fb\u98db\u884c\u6a5f\u306e\u5927\u5c0f\u554f\u308f\u305a\u3001\u3053\u308c\u3070\u304b\u308a\u306f\u3069\u3046\u3057\u3088\u3046\u3082\u7121\u3044\u3067\u3059\u3088\u306d\u3002 \u6700\u8fd1\u306e\u5357\u6771\u4eac\u306e\u5929\u6c17\u306f\u5909\u3067\u3059\u306d\u3002\u3002\u3002","id":30610355541508096,"from_user_id":53407951,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sourceforge.jp/projects/tween/wiki/FrontPage" rel="nofollow">Tween</a>"},{"from_user_id_str":"111826019","profile_image_url":"http://a1.twimg.com/profile_images/1121742732/DVC00052_normal.jpg","created_at":"Thu, 27 Jan 2011 12:51:12 +0000","from_user":"nijiks","id_str":"30608762859421696","metadata":{"result_type":"recent"},"to_user_id":100014282,"text":"@sanaeru \u79c1\u3053\u3093\u306a\u5929\u6c17\u306e\u4e2d\uff64\u4e8c\u6cca\u4e09\u65e5\u3067\u660e\u65e5\u304b\u3089\u6771\u4eac\u884c\u304f\u3093\u3067\u3059\u3051\u3069\u2026\uff61\u65e5\u66dc\u65e5\u98db\u884c\u6a5f\u98db\u3076\u304b\u3057\u3089\u2026\uff1f","id":30608762859421696,"from_user_id":111826019,"to_user":"sanaeru","geo":null,"iso_language_code":"ja","to_user_id_str":"100014282","source":"<a href="http://z.twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b/twipple</a>"},{"from_user_id_str":"164951488","profile_image_url":"http://a3.twimg.com/profile_images/799082230/twitter_normal.jpg","created_at":"Thu, 27 Jan 2011 12:47:49 +0000","from_user":"minorif_jp","id_str":"30607912309096448","metadata":{"result_type":"recent"},"to_user_id":105078670,"text":"@ecco_HIRADO \u5e73\u6238\u725b\u3063\u3066\u5143\u306f\u30aa\u30e9\u30f3\u30c0\u304b\u3089\u304d\u305f\u725b\u306a\u3093\u3060\u306d\u3002\u304a\u3044\u3057\u305d\u3046\u2026\u3002\u5e73\u6238\u306f\u3088\u304b\u6240\u305f\u3043\u3002\u3042\u305f\u3044\u3052\u3047\u3093\u5b9f\u5bb6\u3093\u65b9\u306f\u30c0\u30d6\u30eb\u706b\u5c71\u3084\u9ce5\u30a4\u30f3\u30d5\u30eb\u3067\u5927\u5909\u3084\u3063\u3069\u3002\u6771\u4eac\u3093\u826f\u304b\u3068\u3053\u306f\u5929\u6c17\u306e\u5fc3\u914d\u305b\u305a\u66ae\u3089\u305b\u308b\u3068\u3053\u3058\u3083\u3063\u3069\u3093\u3002","id":30607912309096448,"from_user_id":164951488,"to_user":"ecco_HIRADO","geo":null,"iso_language_code":"ja","to_user_id_str":"105078670","source":"<a href="http://z.twipple.jp/" rel="nofollow">\u3064\u3044\u3063\u3077\u308b/twipple</a>"},{"from_user_id_str":"10456803","profile_image_url":"http://a1.twimg.com/profile_images/145280215/vot_icon_normal.png","created_at":"Thu, 27 Jan 2011 12:43:37 +0000","from_user":"vot_","id_str":"30606853377363968","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3086\u3063\u304f\u308a\u5929\u6c17\u4e88\u5831\u3067\u3059\u3002\u6771\u4eac\u90fd,\u5927\u5cf6\u5730\u65b9\u300228\u65e5\uff08\u91d1\u66dc\u65e5\u306e\u5929\u6c17\u306f\u6674\u308c\u306e\u3061\u66c7\u308a\u3001\u6700\u9ad8\u6c17\u6e29\u306f7\u5ea6 \u6700\u4f4e\u6c17\u6e29\u306f1\u5ea6\u3067\u3057\u3087\u3046\u3002","id":30606853377363968,"from_user_id":10456803,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://voiceoftwitter.com" rel="nofollow">\uff56\uff4f\uff49\uff43\uff45 \uff4f\uff46 \uff54\uff57\uff49\uff54\uff54\uff45\uff52</a>"},{"from_user_id_str":"23900716","profile_image_url":"http://a3.twimg.com/profile_images/1092646332/twitter_icon_normal.png","created_at":"Thu, 27 Jan 2011 12:38:00 +0000","from_user":"keiyama","id_str":"30605442639990784","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3010\u7f8e\u4eba\u5929\u6c17/\u6771\u4eac\u3011\u7f8e\u4eba\u5929\u6c17\u30ad\u30e3\u30b9\u30bf\u30fc\u306e"\u30c8\u30e2\u30b3\u3055\u3093"\u306b\u3088\u308b\u3068\u300c1/27(\u6728)\u306f\u304f\u3082\u308a\u306e\u3061\u6674\u3067\u3001\u964d\u6c34\u78ba\u738710%\u3001\u6700\u9ad8\u6c17\u6e29\u306f9\u2103\u3067\u6700\u4f4e\u6c17\u6e29\u306f2\u2103\u3067\u3059\u300d\u7f8e\u4eba\u5929\u6c17\u21d2http://bit.ly/djB8th http://twitpic.com/3tuekm #bt_tenki","id":30605442639990784,"from_user_id":23900716,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://bijintenki.jp" rel="nofollow">bijintenki.jp</a>"},{"from_user_id_str":"32018516","profile_image_url":"http://a0.twimg.com/profile_images/1089472069/237_normal.jpg","created_at":"Thu, 27 Jan 2011 12:36:28 +0000","from_user":"DigJandG","id_str":"30605057460281344","metadata":{"result_type":"recent"},"to_user_id":196050661,"text":"@kosumoworld55 \u5929\u6c17\u4e88\u5831\u3092\u898b\u3066\u3044\u3064\u3082\u601d\u3046\u3093\u3060\u3002\u4f55\u3067\u6a2a\u6d5c\u3042\u305f\u308a\u306f\u3044\u3064\u3082\u597d\u3044\u5929\u6c17\u306a\u3093\u3060\u3002\u6771\u4eac\u3082\u3002\u3061\u306a\u307f\u306b\u516c\u9b5a\u306f\u3042\u3093\u307e\u308a\u597d\u304d\u3067\u306f\u3042\u308a\u307e\u305b\u3093\u3002\u306a\u3093\u304b\u81ed\u304f\u3063\u3066\u3002\u3067\u3082\u3001\u7435\u7436\u6e56\u3067\u516c\u9b5a\u3063\u3066\u3042\u307e\u308a\u805e\u304b\u306a\u3044\u69d8\u306a\u30fb\u30fb\u30fb\u3002\u4ffa\u304c\u91e3\u308a\u3092\u3057\u306a\u3044\u304b\u3089\u304b\u306a\uff1f","id":30605057460281344,"from_user_id":32018516,"to_user":"kosumoworld55","geo":null,"iso_language_code":"ja","to_user_id_str":"196050661","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"90935348","profile_image_url":"http://a1.twimg.com/sticky/default_profile_images/default_profile_0_normal.png","created_at":"Thu, 27 Jan 2011 12:34:34 +0000","from_user":"sorakeiko","id_str":"30604575937396737","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u95a2\u6771\u5730\u65b9\u306e\u660e\u65e5\u306e\u5929\u6c17\u2015\u7d9a\u304d\u3002\u660e\u65e5\u671d\u6700\u4f4e\u6c17\u6e29\u30fb\u8ed2\u4e26\u307f\u6c37\u70b9\u4e0b\u30fb\u5b87\u90fd\u5bae\u3001\u6c34\u6238\u30de\u30a4\u30ca\u30b95\u5ea6\u30fb\u6771\u4eac\u3001\u6a2a\u6d5c1\u5ea6\u3002\u6700\u9ad8\u6c17\u6e29\u30fb\u4eca\u65e5\u3088\u308a3\u5ea6\u524d\u5f8c\u4f4e\u304f5\uff5e8\u5ea6\u30fb\u6771\u4eac\u3001\u5343\u84498\u5ea6\u3002\u5411\u3053\u3046\u4e00\u9031\u9593\u30fb\u4e7e\u71e5\u3057\u305f\u6674\u308c\u7d9a\u304f\u30fb\uff08\u571f\uff09\u4f0a\u8c46\u8af8\u5cf6\u306b\u51b7\u305f\u3044\u96e8\u3084\u96ea\u304c\u898b\u3089\u308c\u305d\u3046\u3060\u304c\u3001\u95a2\u6771\u306e\u4e7e\u3044\u305f\u72b6\u614b\u7d9a\u304f\u3002","id":30604575937396737,"from_user_id":90935348,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"6113557","profile_image_url":"http://a3.twimg.com/profile_images/1227080026/profile_red_herencia_normal.png","created_at":"Thu, 27 Jan 2011 12:33:57 +0000","from_user":"fmoto7","id_str":"30604423327653888","metadata":{"result_type":"recent"},"to_user_id":null,"text":""\u6771\u4eac\u6c34\u904b\u7528\u30bb\u30f3\u30bf\u30fc\u306f\u3001\u524d\u534a\u6226\u304c\u7d42\u308f\u3063\u305f\u3068\u3053\u308d\u3067\u4e00\u6c17\u306b\u6c34\u5727\u9ad8\u3081\u3001\u5f8c\u534a\u6226\u59cb\u307e\u308b\u3068\u6c34\u5727\u4e0b\u3052\u3001\u7d42\u308f\u308b\u3068\u307e\u305f\u3059\u3050\u4e0a\u3052\u308b\u3002\u30c6\u30ec\u30d3\u306e\u8996\u8074\u3001\u305d\u306e\u65e5\u306e\u5929\u6c17\u306a\u3069\u30e9\u30a4..." http://tumblr.com/xjy1cwiwrm","id":30604423327653888,"from_user_id":6113557,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.tumblr.com/" rel="nofollow">Tumblr</a>"},{"from_user_id_str":"118092912","profile_image_url":"http://a3.twimg.com/profile_images/1225330653/____normal.PNG","created_at":"Thu, 27 Jan 2011 12:29:13 +0000","from_user":"saechuchun","id_str":"30603231042207744","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u3067\u3082\u5730\u9707\u306e\u8a71\u984c\u306e\u3068\u304d\u306e\u300c\u3082\u3057\u6771\u4eac\u3067\u76f4\u4e0b\u578b\u5730\u9707\u304c\u8d77\u304d\u305f\u3089\u300d\u3068\u304b\u5929\u6c17\u4e88\u5831\u306e\u3068\u304d\u306f\u897f\u3067\u96e8\u3060\u308d\u3046\u3068\u300c\u6771\u4eac\u3067\u306f\u301c\u65e5\u9593\u4e7e\u71e5\u3057\u3066\u307e\u3059\u306d\u30fc\u300d\u3068\u304b\u305d\u3046\u3044\u3046\u30ad\u30fc\u5c40\u306e\u95a2\u6771\u4e2d\u5fc3\u4e3b\u7fa9\u306f\u597d\u304d\u3067\u306f\u306a\u3044","id":30603231042207744,"from_user_id":118092912,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twtr.jp" rel="nofollow">Keitai Web</a>"}],"max_id":30724239224995840,"since_id":28179956995457024,"refresh_url":"?since_id=30724239224995840&q=%E6%9D%B1%E4%BA%AC%E3%80%80%E5%A4%A9%E6%B0%97","next_page":"?page=2&max_id=30724239224995840&rpp=50&lang=ja&q=%E6%9D%B1%E4%BA%AC%E3%80%80%E5%A4%A9%E6%B0%97","results_per_page":50,"page":1,"completed_in":0.170202,"warning":"adjusted since_id to 28179956995457024 (), requested since_id was older than allowed -- since_id removed for pagination.","since_id_str":"28179956995457024","max_id_str":"30724239224995840","query":"%E6%9D%B1%E4%BA%AC%E3%80%80%E5%A4%A9%E6%B0%97"} aeson-1.4.2.0/benchmarks/json-data/numbers.json0000755000000000000000000003121400000000000017457 0ustar0000000000000000[1.15, 1.3224999999999998, 1.5208749999999998, 1.7490062499999994, 2.0113571874999994, 2.313060765624999, 2.6600198804687487, 3.0590228625390607, 3.5178762919199196, 4.045557735707907, 4.652391396064092, 5.350250105473706, 6.152787621294761, 7.075705764488975, 8.137061629162321, 9.357620873536668, 10.761264004567169, 12.375453605252241, 14.231771646040077, 16.36653739294609, 18.821518001888, 21.644745702171196, 24.891457557496874, 28.625176191121405, 32.918952619789614, 37.856795512758055, 43.535314839671756, 50.06561206562252, 57.57545387546589, 66.21177195678577, 76.14353775030362, 87.56506841284916, 100.69982867477653, 115.804802975993, 133.17552342239193, 153.15185193575073, 176.1246297261133, 202.5433241850303, 232.9248228127848, 267.86354623470254, 308.04307816990786, 354.24953989539404, 407.3869708797031, 468.49501651165855, 538.7692689884072, 619.5846593366683, 712.5223582371685, 819.4007119727437, 942.3108187686552, 1083.6574415839534, 1246.2060578215462, 1433.136966494778, 1648.1075114689947, 1895.323638189344, 2179.622183917745, 2506.565511505407, 2882.5503382312177, 3314.9328889659, 3812.172822310785, 4383.998745657402, 5041.598557506012, 5797.838341131914, 6667.5140923017, 7667.641206146955, 8817.787387068996, 10140.455495129345, 11661.523819398746, 13410.752392308557, 15422.365251154839, 17735.720038828065, 20396.078044652273, 23455.489751350113, 26973.813214052625, 31019.885196160518, 35672.867975584595, 41023.79817192228, 47177.36789771062, 54253.97308236721, 62392.06904472228, 71750.87940143062, 82513.5113116452, 94890.53800839197, 109124.11870965076, 125492.73651609836, 144316.6469935131, 165964.14404254008, 190858.76564892105, 219487.5804962592, 252410.71757069806, 290272.32520630275, 333813.17398724816, 383885.1500853353, 441467.9225981356, 507688.1109878559, 583841.3276360342, 671417.5267814393, 772130.1557986551, 887949.6791684533, 1021142.1310437213, 1174313.4507002793, 1350460.4683053212, 1553029.5385511192, 1785983.969333787, 2053881.564733855, 2361963.7994439327, 2716258.369360523, 3123697.124764601, 3592251.6934792907, 4131089.447501184, 4750752.864626361, 5463365.794320315, 6282870.663468362, 7225301.262988616, 8309096.452436907, 9555460.920302443, 10988780.058347808, 12637097.067099977, 14532661.627164973, 16712560.871239718, 19219445.001925673, 22102361.752214525, 25417716.0150467, 29230373.417303704, 33614929.42989926, 38657168.84438414, 44455744.17104176, 51124105.79669802, 58792721.66620272, 67611629.91613312, 77753374.40355308, 89416380.56408603, 102828837.64869894, 118253163.29600377, 135991137.79040432, 156389808.45896497, 179848279.7278097, 206825521.68698114, 237849349.94002828, 273526752.4310325, 314555765.2956874, 361739130.09004045, 415999999.60354644, 478399999.5440784, 550159999.4756901, 632683999.3970436, 727586599.3066001, 836724589.20259, 962233277.5829784, 1106568269.2204251, 1272553509.6034887, 1463436536.044012, 1682952016.4506137, 1935394818.9182055, 2225704041.755936, 2559559648.019326, 2943493595.222225, 3385017634.5055585, 3892770279.681392, 4476685821.6336, 5148188694.87864, 5920416999.1104355, 6808479548.977001, 7829751481.32355, 9004214203.522081, 10354846334.050394, 11908073284.157951, 13694284276.781643, 15748426918.29889, 18110690956.04372, 20827294599.450275, 23951388789.367817, 27544097107.772987, 31675711673.938934, 36427068425.02977, 41891128688.78423, 48174797992.10186, 55401017690.91714, 63711170344.5547, 73267845896.2379, 84258022780.67358, 96896726197.77461, 111431235127.4408, 128145920396.5569, 147367808456.04044, 169472979724.44647, 194893926683.11343, 224128015685.58044, 257747218038.41748, 296409300744.1801, 340870695855.80707, 392001300234.1781, 450801495269.3048, 518421719559.70044, 596184977493.6555, 685612724117.7037, 788454632735.3593, 906722827645.6631, 1042731251792.5125, 1199140939561.3892, 1379012080495.5974, 1585863892569.937, 1823743476455.4275, 2097304997923.7415, 2411900747612.3022, 2773685859754.1475, 3189738738717.2695, 3668199549524.8594, 4218429481953.5884, 4851193904246.626, 5578872989883.619, 6415703938366.162, 7378059529121.086, 8484768458489.248, 9757483727262.635, 11221106286352.03, 12904272229304.832, 14839913063700.555, 17065900023255.637, 19625785026743.98, 22569652780755.58, 25955100697868.91, 29848365802549.246, 34325620672931.63, 39474463773871.375, 45395633339952.07, 52204978340944.88, 60035725092086.61, 69041083855899.59, 79397246434284.53, 91306833399427.2, 105002858409341.27, 120753287170742.45, 138866280246353.81, 159696222283306.88, 183650655625802.88, 211198253969673.3, 242877992065124.28, 279309690874892.9, 321206144506126.8, 369387066182045.8, 424795126109352.6, 488514395025755.5, 561791554279618.75, 646060287421561.5, 742969330534795.8, 854414730115015.0, 982576939632267.1, 1129963480577107.2, 1299458002663673.2, 1494376703063224.0, 1718533208522707.5, 1976313189801113.5, 2272760168271280.5, 2613674193511972.0, 3005725322538767.5, 3456584120919582.5, 3975071739057519.5, 4571332499916147.0, 5257032374903569.0, 6045587231139104.0, 6952425315809969.0, 7995289113181464.0, 9194582480158682.0, 1.0573769852182484e+16, 1.2159835330009856e+16, 1.3983810629511332e+16, 1.6081382223938032e+16, 1.8493589557528736e+16, 2.1267627991158044e+16, 2.4457772189831748e+16, 2.8126438018306508e+16, 3.234540372105248e+16, 3.719721427921035e+16, 4.27767964210919e+16, 4.919331588425568e+16, 5.657231326689403e+16, 6.505816025692813e+16, 7.481688429546734e+16, 8.603941693978744e+16, 9.894532948075555e+16, 1.1378712890286886e+17, 1.3085519823829918e+17, 1.5048347797404406e+17, 1.7305599967015066e+17, 1.9901439962067325e+17, 2.288665595637742e+17, 2.6319654349834032e+17, 3.026760250230913e+17, 3.48077428776555e+17, 4.002890430930382e+17, 4.603323995569939e+17, 5.29382259490543e+17, 6.087895984141244e+17, 7.00108038176243e+17, 8.051242439026793e+17, 9.258928804880812e+17, 1.0647768125612933e+18, 1.224493334445487e+18, 1.4081673346123103e+18, 1.6193924348041567e+18, 1.8623013000247798e+18, 2.1416464950284966e+18, 2.462893469282771e+18, 2.8323274896751867e+18, 3.257176613126464e+18, 3.7457531050954337e+18, 4.3076160708597484e+18, 4.95375848148871e+18, 5.696822253712016e+18, 6.551345591768818e+18, 7.53404743053414e+18, 8.66415454511426e+18, 9.963777726881399e+18, 1.1458344385913608e+19, 1.3177096043800648e+19, 1.5153660450370744e+19, 1.7426709517926355e+19, 2.0040715945615307e+19, 2.30468233374576e+19, 2.650384683807624e+19, 3.047942386378767e+19, 3.505133744335582e+19, 4.030903805985919e+19, 4.635539376883806e+19, 5.330870283416377e+19, 6.130500825928833e+19, 7.0500759498181575e+19, 8.10758734229088e+19, 9.323725443634512e+19, 1.0722284260179688e+20, 1.233062689920664e+20, 1.4180220934087634e+20, 1.6307254074200778e+20, 1.8753342185330894e+20, 2.1566343513130526e+20, 2.4801295040100103e+20, 2.8521489296115116e+20, 3.2799712690532385e+20, 3.7719669594112236e+20, 4.337762003322907e+20, 4.988426303821342e+20, 5.7366902493945437e+20, 6.597193786803724e+20, 7.586772854824282e+20, 8.724788783047925e+20, 1.0033507100505113e+21, 1.1538533165580878e+21, 1.326931314041801e+21, 1.5259710111480708e+21, 1.7548666628202813e+21, 2.0180966622433234e+21, 2.3208111615798217e+21, 2.668932835816795e+21, 3.0692727611893135e+21, 3.529663675367711e+21, 4.059113226672867e+21, 4.667980210673796e+21, 5.368177242274866e+21, 6.173403828616095e+21, 7.099414402908508e+21, 8.164326563344784e+21, 9.388975547846502e+21, 1.0797321880023475e+22, 1.2416920162026996e+22, 1.4279458186331043e+22, 1.64213769142807e+22, 1.8884583451422802e+22, 2.171727096913622e+22, 2.497486161450665e+22, 2.872109085668265e+22, 3.3029254485185042e+22, 3.798364265796279e+22, 4.368118905665721e+22, 5.0233367415155795e+22, 5.7768372527429155e+22, 6.643362840654352e+22, 7.639867266752504e+22, 8.78584735676538e+22, 1.0103724460280185e+23, 1.1619283129322213e+23, 1.3362175598720545e+23, 1.5366501938528623e+23, 1.7671477229307915e+23, 2.0322198813704103e+23, 2.3370528635759717e+23, 2.687610793112367e+23, 3.090752412079222e+23, 3.554365273891105e+23, 4.0875200649747705e+23, 4.700648074720986e+23, 5.405745285929133e+23, 6.216607078818502e+23, 7.149098140641278e+23, 8.221462861737468e+23, 9.454682290998088e+23, 1.0872884634647801e+24, 1.250381732984497e+24, 1.4379389929321714e+24, 1.653629841871997e+24, 1.9016743181527962e+24, 2.1869254658757156e+24, 2.5149642857570727e+24, 2.8922089286206334e+24, 3.326040267913728e+24, 3.824946308100787e+24, 4.3986882543159046e+24, 5.05849149246329e+24, 5.817265216332783e+24, 6.6898549987827e+24, 7.693333248600105e+24, 8.84733323589012e+24, 1.0174433221273637e+25, 1.1700598204464681e+25, 1.3455687935134384e+25, 1.547404112540454e+25, 1.779514729421522e+25, 2.04644193883475e+25, 2.353408229659962e+25, 2.7064194641089563e+25, 3.1123823837253e+25, 3.5792397412840944e+25, 4.116125702476708e+25, 4.733544557848214e+25, 5.443576241525446e+25, 6.260112677754262e+25, 7.199129579417401e+25, 8.27899901633001e+25, 9.52084886877951e+25, 1.0948976199096437e+26, 1.25913226289609e+26, 1.4480021023305035e+26, 1.665202417680079e+26, 1.9149827803320907e+26, 2.202230197381904e+26, 2.5325647269891895e+26, 2.9124494360375676e+26, 3.349316851443203e+26, 3.8517143791596826e+26, 4.429471536033635e+26, 5.09389226643868e+26, 5.857976106404481e+26, 6.736672522365153e+26, 7.747173400719924e+26, 8.909249410827912e+26, 1.0245636822452099e+27, 1.1782482345819913e+27, 1.35498546976929e+27, 1.5582332902346833e+27, 1.7919682837698857e+27, 2.0607635263353683e+27, 2.3698780552856732e+27, 2.725359763578524e+27, 3.1341637281153025e+27, 3.6042882873325974e+27, 4.1449315304324867e+27, 4.7666712599973594e+27, 5.481671948996963e+27, 6.303922741346507e+27, 7.249511152548482e+27, 8.336937825430755e+27, 9.587478499245366e+27, 1.102560027413217e+28, 1.2679440315251995e+28, 1.4581356362539794e+28, 1.6768559816920761e+28, 1.9283843789458875e+28, 2.2176420357877703e+28, 2.5502883411559357e+28, 2.932831592329326e+28, 3.3727563311787245e+28, 3.8786697808555327e+28, 4.460470247983863e+28, 5.129540785181441e+28, 5.8989719029586575e+28, 6.783817688402455e+28, 7.801390341662823e+28, 8.971598892912247e+28, 1.0317338726849081e+29, 1.1864939535876443e+29, 1.3644680466257909e+29, 1.5691382536196593e+29, 1.8045089916626083e+29, 2.0751853404119993e+29, 2.3864631414737988e+29, 2.7444326126948684e+29, 3.1560975045990984e+29, 3.629512130288963e+29, 4.173938949832307e+29, 4.800029792307153e+29, 5.520034261153225e+29, 6.348039400326208e+29, 7.300245310375139e+29, 8.39528210693141e+29, 9.65457442297112e+29, 1.1102760586416787e+30, 1.2768174674379305e+30, 1.46834008755362e+30, 1.6885911006866628e+30, 1.941879765789662e+30, 2.2331617306581113e+30, 2.568135990256828e+30, 2.9533563887953516e+30, 3.396359847114654e+30, 3.905813824181852e+30, 4.491685897809129e+30, 5.165438782480498e+30, 5.940254599852573e+30, 6.831292789830458e+30, 7.855986708305026e+30, 9.034384714550779e+30, 1.0389542421733396e+31, 1.1947973784993405e+31, 1.3740169852742412e+31, 1.5801195330653773e+31, 1.817137463025184e+31, 2.0897080824789613e+31, 2.4031642948508052e+31, 2.7636389390784257e+31, 3.1781847799401893e+31, 3.6549124969312175e+31, 4.2031493714709e+31, 4.833621777191535e+31, 5.558665043770264e+31, 6.392464800335803e+31, 7.3513345203861735e+31, 8.454034698444098e+31, 9.722139903210713e+31, 1.1180460888692319e+32, 1.2857530021996165e+32, 1.478615952529559e+32, 1.7004083454089925e+32, 1.9554695972203414e+32, 2.2487900368033926e+32, 2.586108542323901e+32, 2.974024823672486e+32, 3.420128547223359e+32, 3.933147829306862e+32, 4.523120003702891e+32, 5.2015880042583246e+32, 5.981826204897073e+32, 6.879100135631634e+32, 7.910965155976377e+32, 9.097609929372833e+32, 1.0462251418778757e+33, 1.2031589131595571e+33, 1.3836327501334904e+33, 1.591177662653514e+33, 1.8298543120515409e+33, 2.104332458859272e+33, 2.4199823276881623e+33, 2.7829796768413863e+33, 3.200426628367594e+33, 3.6804906226227334e+33, 4.232564216016143e+33, 4.867448848418564e+33, 5.597566175681348e+33, 6.437201102033549e+33, 7.402781267338582e+33, 8.513198457439368e+33, 9.790178226055273e+33, 1.1258704959963564e+34, 1.2947510703958096e+34, 1.488963730955181e+34, 1.712308290598458e+34, 1.9691545341882266e+34, 2.2645277143164603e+34, 2.604206871463929e+34, 2.994837902183518e+34, 3.4440635875110457e+34, 3.960673125637702e+34, 4.554774094483357e+34, 5.237990208655861e+34, 6.023688739954239e+34, 6.927242050947375e+34, 7.96632835858948e+34, 9.161277612377902e+34, 1.0535469254234585e+35, 1.2115789642369772e+35, 1.3933158088725236e+35, 1.6023131802034022e+35, 1.8426601572339122e+35, 2.119059180818999e+35, 2.4369180579418488e+35, 2.8024557666331258e+35, 3.2228241316280944e+35, 3.706247751372308e+35, 4.262184914078154e+35, 4.901512651189877e+35, 5.636739548868358e+35, 6.482250481198611e+35, 7.454588053378403e+35, 8.572776261385162e+35, 9.858692700592935e+35, 1.1337496605681875e+36, 1.3038121096534156e+36, 1.499383926101428e+36, 1.7242915150166418e+36, 1.982935242269138e+36, 2.2803755286095084e+36] aeson-1.4.2.0/benchmarks/json-data/twitter1.json0000755000000000000000000000152700000000000017573 0ustar0000000000000000{"results":[{"from_user_id_str":"80430860","profile_image_url":"http://a2.twimg.com/profile_images/536455139/icon32_normal.png","created_at":"Wed, 26 Jan 2011 07:07:02 +0000","from_user":"kazu_yamamoto","id_str":"30159761706061824","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell Server Pages \u3063\u3066\u3001\u307e\u3060\u7d9a\u3044\u3066\u3044\u305f\u306e\u304b\uff01","id":30159761706061824,"from_user_id":80430860,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"}],"max_id":30159761706061824,"since_id":0,"refresh_url":"?since_id=30159761706061824&q=haskell","next_page":"?page=2&max_id=30159761706061824&rpp=1&q=haskell","results_per_page":1,"page":1,"completed_in":0.012606,"since_id_str":"0","max_id_str":"30159761706061824","query":"haskell"} aeson-1.4.2.0/benchmarks/json-data/twitter10.json0000755000000000000000000001470200000000000017652 0ustar0000000000000000{"results":[{"from_user_id_str":"207858021","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Wed, 26 Jan 2011 04:30:38 +0000","from_user":"pboudarga","id_str":"30120402839666689","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I'm at Rolla Sushi Grill (27737 Bouquet Canyon Road, #106, Btw Haskell Canyon and Rosedell Drive, Saugus) http://4sq.com/gqqdhs","id":30120402839666689,"from_user_id":207858021,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://foursquare.com" rel="nofollow">foursquare</a>"},{"from_user_id_str":"69988683","profile_image_url":"http://a0.twimg.com/profile_images/1211955817/avatar_7888_normal.gif","created_at":"Wed, 26 Jan 2011 04:25:23 +0000","from_user":"YNK33","id_str":"30119083059978240","metadata":{"result_type":"recent"},"to_user_id":null,"text":"hsndfile 0.5.0: Free and open source Haskell bindings for libsndfile http://bit.ly/gHaBWG Mac Os","id":30119083059978240,"from_user_id":69988683,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"81492","profile_image_url":"http://a1.twimg.com/profile_images/423894208/Picture_7_normal.jpg","created_at":"Wed, 26 Jan 2011 04:24:28 +0000","from_user":"satzz","id_str":"30118851488251904","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Emacs\u306e\u30e2\u30fc\u30c9\u8868\u793a\u304c\u4eca(Ruby Controller Outputz RoR Flymake REl hs)\u3068\u306a\u3063\u3066\u3066\u3088\u304f\u308f\u304b\u3089\u306a\u3044\u3093\u3060\u3051\u3069\u6700\u5f8c\u306eREl\u3068\u304bhs\u3063\u3066\u4f55\u3060\u308d\u3046\u2026haskell\u3068\u304b2\u5e74\u4ee5\u4e0a\u66f8\u3044\u3066\u306a\u3044\u3051\u3069\u2026","id":30118851488251904,"from_user_id":81492,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"9518356","profile_image_url":"http://a2.twimg.com/profile_images/119165723/ocaml-icon_normal.png","created_at":"Wed, 26 Jan 2011 04:19:19 +0000","from_user":"planet_ocaml","id_str":"30117557788741632","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I so miss #haskell type classes in #ocaml - i want to do something like refinement. Also why does ocaml not have... http://bit.ly/geYRwt","id":30117557788741632,"from_user_id":9518356,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"218059","profile_image_url":"http://a1.twimg.com/profile_images/1053837723/twitter-icon9_normal.jpg","created_at":"Wed, 26 Jan 2011 04:16:32 +0000","from_user":"aprikip","id_str":"30116854940835840","metadata":{"result_type":"recent"},"to_user_id":null,"text":"yatex-mode\u3084haskell-mode\u306e\u3053\u3068\u3067\u3059\u306d\u3001\u308f\u304b\u308a\u307e\u3059\u3002","id":30116854940835840,"from_user_id":218059,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sites.google.com/site/yorufukurou/" rel="nofollow">YoruFukurou</a>"},{"from_user_id_str":"216363","profile_image_url":"http://a1.twimg.com/profile_images/72454310/Tim-Avatar_normal.png","created_at":"Wed, 26 Jan 2011 04:15:30 +0000","from_user":"dysinger","id_str":"30116594684264448","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell in Hawaii tonight for me... #fun","id":30116594684264448,"from_user_id":216363,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.nambu.com/" rel="nofollow">Nambu</a>"},{"from_user_id_str":"1774820","profile_image_url":"http://a2.twimg.com/profile_images/61169291/dan_desert_thumb_normal.jpg","created_at":"Wed, 26 Jan 2011 04:13:36 +0000","from_user":"DanMil","id_str":"30116117682851840","metadata":{"result_type":"recent"},"to_user_id":1594784,"text":"@ojrac @chewedwire @tomheon Haskell isn't a language, it's a belief system. A seductive one...","id":30116117682851840,"from_user_id":1774820,"to_user":"ojrac","geo":null,"iso_language_code":"en","to_user_id_str":"1594784","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"659256","profile_image_url":"http://a0.twimg.com/profile_images/746976711/angular-final_normal.jpg","created_at":"Wed, 26 Jan 2011 04:11:06 +0000","from_user":"djspiewak","id_str":"30115488931520512","metadata":{"result_type":"recent"},"to_user_id":null,"text":"One of the very nice things about Haskell as opposed to SML is the reduced proliferation of identifiers (e.g. andb, orb, etc). #typeclasses","id":30115488931520512,"from_user_id":659256,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Wed, 26 Jan 2011 04:06:12 +0000","from_user":"listwarenet","id_str":"30114255890026496","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-cafe/84752-re-haskell-cafe-gpl-license-of-h-matrix-and-prelude-numeric.html Re: Haskell-c","id":30114255890026496,"from_user_id":144546280,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"},{"from_user_id_str":"1594784","profile_image_url":"http://a2.twimg.com/profile_images/378515773/square-profile_normal.jpg","created_at":"Wed, 26 Jan 2011 04:01:29 +0000","from_user":"ojrac","id_str":"30113067333324800","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @tomheon: @ojrac @chewedwire Don't worry, learning Haskell will not give you any clear idea what monad means.","id":30113067333324800,"from_user_id":1594784,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"}],"max_id":30120402839666689,"since_id":0,"refresh_url":"?since_id=30120402839666689&q=haskell","next_page":"?page=2&max_id=30120402839666689&rpp=10&q=haskell","results_per_page":10,"page":1,"completed_in":0.012714,"since_id_str":"0","max_id_str":"30120402839666689","query":"haskell"} aeson-1.4.2.0/benchmarks/json-data/twitter100.json0000755000000000000000000017302500000000000017736 0ustar0000000000000000{"results":[{"from_user_id_str":"3646730","profile_image_url":"http://a3.twimg.com/profile_images/404973767/avatar_normal.jpg","created_at":"Wed, 26 Jan 2011 04:35:07 +0000","from_user":"nicolaslara","id_str":"30121530767708160","metadata":{"result_type":"recent"},"to_user_id":18616016,"text":"@josej30 Python y Clojure. Obviamente son diferentes, y cada uno tiene sus ventajas y desventajas. De Haskell faltar\u00eda pattern matching","id":30121530767708160,"from_user_id":3646730,"to_user":"josej30","geo":null,"iso_language_code":"es","to_user_id_str":"18616016","source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"207858021","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Wed, 26 Jan 2011 04:30:38 +0000","from_user":"pboudarga","id_str":"30120402839666689","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I'm at Rolla Sushi Grill (27737 Bouquet Canyon Road, #106, Btw Haskell Canyon and Rosedell Drive, Saugus) http://4sq.com/gqqdhs","id":30120402839666689,"from_user_id":207858021,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://foursquare.com" rel="nofollow">foursquare</a>"},{"from_user_id_str":"69988683","profile_image_url":"http://a0.twimg.com/profile_images/1211955817/avatar_7888_normal.gif","created_at":"Wed, 26 Jan 2011 04:25:23 +0000","from_user":"YNK33","id_str":"30119083059978240","metadata":{"result_type":"recent"},"to_user_id":null,"text":"hsndfile 0.5.0: Free and open source Haskell bindings for libsndfile http://bit.ly/gHaBWG Mac Os","id":30119083059978240,"from_user_id":69988683,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"81492","profile_image_url":"http://a1.twimg.com/profile_images/423894208/Picture_7_normal.jpg","created_at":"Wed, 26 Jan 2011 04:24:28 +0000","from_user":"satzz","id_str":"30118851488251904","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Emacs\u306e\u30e2\u30fc\u30c9\u8868\u793a\u304c\u4eca(Ruby Controller Outputz RoR Flymake REl hs)\u3068\u306a\u3063\u3066\u3066\u3088\u304f\u308f\u304b\u3089\u306a\u3044\u3093\u3060\u3051\u3069\u6700\u5f8c\u306eREl\u3068\u304bhs\u3063\u3066\u4f55\u3060\u308d\u3046\u2026haskell\u3068\u304b2\u5e74\u4ee5\u4e0a\u66f8\u3044\u3066\u306a\u3044\u3051\u3069\u2026","id":30118851488251904,"from_user_id":81492,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"9518356","profile_image_url":"http://a2.twimg.com/profile_images/119165723/ocaml-icon_normal.png","created_at":"Wed, 26 Jan 2011 04:19:19 +0000","from_user":"planet_ocaml","id_str":"30117557788741632","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I so miss #haskell type classes in #ocaml - i want to do something like refinement. Also why does ocaml not have... http://bit.ly/geYRwt","id":30117557788741632,"from_user_id":9518356,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"218059","profile_image_url":"http://a1.twimg.com/profile_images/1053837723/twitter-icon9_normal.jpg","created_at":"Wed, 26 Jan 2011 04:16:32 +0000","from_user":"aprikip","id_str":"30116854940835840","metadata":{"result_type":"recent"},"to_user_id":null,"text":"yatex-mode\u3084haskell-mode\u306e\u3053\u3068\u3067\u3059\u306d\u3001\u308f\u304b\u308a\u307e\u3059\u3002","id":30116854940835840,"from_user_id":218059,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sites.google.com/site/yorufukurou/" rel="nofollow">YoruFukurou</a>"},{"from_user_id_str":"216363","profile_image_url":"http://a1.twimg.com/profile_images/72454310/Tim-Avatar_normal.png","created_at":"Wed, 26 Jan 2011 04:15:30 +0000","from_user":"dysinger","id_str":"30116594684264448","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell in Hawaii tonight for me... #fun","id":30116594684264448,"from_user_id":216363,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.nambu.com/" rel="nofollow">Nambu</a>"},{"from_user_id_str":"1774820","profile_image_url":"http://a2.twimg.com/profile_images/61169291/dan_desert_thumb_normal.jpg","created_at":"Wed, 26 Jan 2011 04:13:36 +0000","from_user":"DanMil","id_str":"30116117682851840","metadata":{"result_type":"recent"},"to_user_id":1594784,"text":"@ojrac @chewedwire @tomheon Haskell isn't a language, it's a belief system. A seductive one...","id":30116117682851840,"from_user_id":1774820,"to_user":"ojrac","geo":null,"iso_language_code":"en","to_user_id_str":"1594784","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"659256","profile_image_url":"http://a0.twimg.com/profile_images/746976711/angular-final_normal.jpg","created_at":"Wed, 26 Jan 2011 04:11:06 +0000","from_user":"djspiewak","id_str":"30115488931520512","metadata":{"result_type":"recent"},"to_user_id":null,"text":"One of the very nice things about Haskell as opposed to SML is the reduced proliferation of identifiers (e.g. andb, orb, etc). #typeclasses","id":30115488931520512,"from_user_id":659256,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Wed, 26 Jan 2011 04:06:12 +0000","from_user":"listwarenet","id_str":"30114255890026496","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-cafe/84752-re-haskell-cafe-gpl-license-of-h-matrix-and-prelude-numeric.html Re: Haskell-c","id":30114255890026496,"from_user_id":144546280,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"},{"from_user_id_str":"1594784","profile_image_url":"http://a2.twimg.com/profile_images/378515773/square-profile_normal.jpg","created_at":"Wed, 26 Jan 2011 04:01:29 +0000","from_user":"ojrac","id_str":"30113067333324800","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @tomheon: @ojrac @chewedwire Don't worry, learning Haskell will not give you any clear idea what monad means.","id":30113067333324800,"from_user_id":1594784,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"207589736","profile_image_url":"http://a3.twimg.com/profile_images/1225527428/headshot_1_normal.jpg","created_at":"Wed, 26 Jan 2011 04:00:13 +0000","from_user":"ashleevelazq101","id_str":"30112747555397632","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Federal investigation finds safety violations at The Acadia Hospital: By Meg Haskell, BDN Staff The investigatio... http://bit.ly/dONnpn","id":30112747555397632,"from_user_id":207589736,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"17671137","profile_image_url":"http://a2.twimg.com/profile_images/290264834/Haskell-logo-outer-glow_normal.png","created_at":"Wed, 26 Jan 2011 03:58:00 +0000","from_user":"Hackage","id_str":"30112192346984448","metadata":{"result_type":"recent"},"to_user_id":null,"text":"streams 0.4, added by EdwardKmett: Various Haskell 2010 stream comonads http://bit.ly/idBkPe","id":30112192346984448,"from_user_id":17671137,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"17489366","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Wed, 26 Jan 2011 03:58:00 +0000","from_user":"aapnoot","id_str":"30112191881420800","metadata":{"result_type":"recent"},"to_user_id":null,"text":"streams 0.4, added by EdwardKmett: Various Haskell 2010 stream comonads http://bit.ly/idBkPe","id":30112191881420800,"from_user_id":17489366,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"8530482","profile_image_url":"http://a2.twimg.com/profile_images/137867266/n608671563_7396_normal.jpg","created_at":"Wed, 26 Jan 2011 03:50:12 +0000","from_user":"jeffmclamb","id_str":"30110229207187456","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Angel - daemon to run and monitor processes like daemontools or god, written in Haskell http://ff.im/-wNyLk","id":30110229207187456,"from_user_id":8530482,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://friendfeed.com" rel="nofollow">FriendFeed</a>"},{"from_user_id_str":"177539201","profile_image_url":"http://a0.twimg.com/profile_images/1178368800/img_normal.jpeg","created_at":"Wed, 26 Jan 2011 03:46:01 +0000","from_user":"tomheon","id_str":"30109174645919744","metadata":{"result_type":"recent"},"to_user_id":1594784,"text":"@ojrac @chewedwire Don't worry, learning Haskell will not give you any clear idea what monad means.","id":30109174645919744,"from_user_id":177539201,"to_user":"ojrac","geo":null,"iso_language_code":"en","to_user_id_str":"1594784","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"1594784","profile_image_url":"http://a2.twimg.com/profile_images/378515773/square-profile_normal.jpg","created_at":"Wed, 26 Jan 2011 03:44:34 +0000","from_user":"ojrac","id_str":"30108808684503040","metadata":{"result_type":"recent"},"to_user_id":128028225,"text":"@chewedwire @tomheon Why are you making me curious about Haskell? I LIKE not knowing what monad means!!","id":30108808684503040,"from_user_id":1594784,"to_user":"chewedwire","geo":null,"iso_language_code":"en","to_user_id_str":"128028225","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"23750094","profile_image_url":"http://a0.twimg.com/profile_images/951373780/Moeinthecar_normal.jpg","created_at":"Wed, 26 Jan 2011 03:41:54 +0000","from_user":"shokalshab","id_str":"30108140443795456","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I'm at Magnitude Cheer @ Gymnastics Olympica USA (7735 Haskell Ave., btw Saticoy & Strathern, Van Nuys) http://4sq.com/gmXfaL","id":30108140443795456,"from_user_id":23750094,"geo":null,"iso_language_code":"en","place":{"id":"4e4a2a2f86cb2946","type_":"poi","full_name":"Gymnastics Olympica USA, Van Nuys"},"to_user_id_str":null,"source":"<a href="http://foursquare.com" rel="nofollow">foursquare</a>"},{"from_user_id_str":"8135112","profile_image_url":"http://a0.twimg.com/profile_images/1165240350/LIMITED_normal.jpg","created_at":"Wed, 26 Jan 2011 03:41:35 +0000","from_user":"Claricei","id_str":"30108059208515584","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @kristenmchugh22: @KeithOlbermann Ryan looks like Jughead w/o the hat. And sounds as mealy-mouthed as Eddie Haskell.","id":30108059208515584,"from_user_id":8135112,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"128028225","profile_image_url":"http://a1.twimg.com/profile_images/1224994593/Coding_Drunk_normal.jpg","created_at":"Wed, 26 Jan 2011 03:40:02 +0000","from_user":"chewedwire","id_str":"30107670367182848","metadata":{"result_type":"recent"},"to_user_id":177539201,"text":"@tomheon Cool, I'll take a look. I feel like I should mention this: http://bit.ly/hVstDM","id":30107670367182848,"from_user_id":128028225,"to_user":"tomheon","geo":null,"iso_language_code":"en","to_user_id_str":"177539201","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"8679778","profile_image_url":"http://a3.twimg.com/profile_images/1195318056/me_nyc_12_18_10_icon_normal.jpg","created_at":"Wed, 26 Jan 2011 03:38:42 +0000","from_user":"kristenmchugh22","id_str":"30107332381777920","metadata":{"result_type":"recent"},"to_user_id":756269,"text":"@KeithOlbermann Ryan looks like Jughead w/o the hat. And sounds as mealy-mouthed as Eddie Haskell.","id":30107332381777920,"from_user_id":8679778,"to_user":"KeithOlbermann","geo":null,"iso_language_code":"en","to_user_id_str":"756269","source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"103316559","profile_image_url":"http://a1.twimg.com/profile_images/1179458751/bc3beab4-d59d-4e78-b13b-50747986cfa2_normal.png","created_at":"Wed, 26 Jan 2011 03:36:15 +0000","from_user":"cityslikr","id_str":"30106719153557504","metadata":{"result_type":"recent"},"to_user_id":null,"text":""Social safety net into a hammock." So says Eddie Haskell with the GOP response. #SOTU","id":30106719153557504,"from_user_id":103316559,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://blackberry.com/twitter" rel="nofollow">Twitter for BlackBerry\u00ae</a>"},{"from_user_id_str":"169063143","profile_image_url":"http://a0.twimg.com/profile_images/1160506212/9697_1_normal.gif","created_at":"Wed, 26 Jan 2011 03:31:52 +0000","from_user":"wrkforce_safety","id_str":"30105614919143424","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Federal investigation finds safety violations at The Acadia Hospital: By Meg Haskell, BDN Staff The investigatio... http://bit.ly/gA60C1","id":30105614919143424,"from_user_id":169063143,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"177539201","profile_image_url":"http://a0.twimg.com/profile_images/1178368800/img_normal.jpeg","created_at":"Wed, 26 Jan 2011 03:29:40 +0000","from_user":"tomheon","id_str":"30105060960632832","metadata":{"result_type":"recent"},"to_user_id":128028225,"text":"@chewedwire Great book on Haskell: http://oreilly.com/catalog/9780596514983","id":30105060960632832,"from_user_id":177539201,"to_user":"chewedwire","geo":null,"iso_language_code":"en","to_user_id_str":"128028225","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"782692","profile_image_url":"http://a0.twimg.com/profile_images/1031304589/Profile.2007.1_normal.jpg","created_at":"Wed, 26 Jan 2011 03:29:19 +0000","from_user":"turnageb","id_str":"30104974591533057","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @ovillalon: Paul Ryan solves the mystery of whatever happened to Eddie Haskell. #sotu","id":30104974591533057,"from_user_id":782692,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"128028225","profile_image_url":"http://a1.twimg.com/profile_images/1224994593/Coding_Drunk_normal.jpg","created_at":"Wed, 26 Jan 2011 03:28:04 +0000","from_user":"chewedwire","id_str":"30104657267265536","metadata":{"result_type":"recent"},"to_user_id":177539201,"text":"@tomheon I always loved the pattern matching in SML and it looks like Haskell is MUCH better at it. I'm messing around now at tryhaskell.org","id":30104657267265536,"from_user_id":128028225,"to_user":"tomheon","geo":null,"iso_language_code":"en","to_user_id_str":"177539201","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"12834082","profile_image_url":"http://a3.twimg.com/profile_images/1083036140/mugshot_normal.png","created_at":"Wed, 26 Jan 2011 03:28:01 +0000","from_user":"ovillalon","id_str":"30104647213518848","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Paul Ryan solves the mystery of whatever happened to Eddie Haskell. #sotu","id":30104647213518848,"from_user_id":12834082,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"13540930","profile_image_url":"http://a1.twimg.com/profile_images/1205312219/23467_350321383101_821143101_5114147_3010041_n_normal.jpg","created_at":"Wed, 26 Jan 2011 03:26:02 +0000","from_user":"goodfox","id_str":"30104146455560192","metadata":{"result_type":"recent"},"to_user_id":10226179,"text":"@billykeene22 Bordeaux is one of my heroes. I was so excited when he accepted the invitation to campus. He's been a great friend to Haskell.","id":30104146455560192,"from_user_id":13540930,"to_user":"billykeene22","geo":null,"iso_language_code":"en","to_user_id_str":"10226179","source":"<a href="http://www.ubertwitter.com/bb/download.php" rel="nofollow">\u00dcberTwitter</a>"},{"from_user_id_str":"18616016","profile_image_url":"http://a2.twimg.com/profile_images/1173522726/214397343_normal.jpg","created_at":"Wed, 26 Jan 2011 03:25:18 +0000","from_user":"josej30","id_str":"30103962313031681","metadata":{"result_type":"recent"},"to_user_id":14870909,"text":"@cris7ian Ahh bueno multiparadigma ya es respetable :) Empezar\u00e9 a explotar la parte funcional de los lenguajes ahora #Haskell","id":30103962313031681,"from_user_id":18616016,"to_user":"Cris7ian","geo":null,"iso_language_code":"es","to_user_id_str":"14870909","source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"14870909","profile_image_url":"http://a2.twimg.com/profile_images/1176930429/oso_yo_normal.png","created_at":"Wed, 26 Jan 2011 03:23:43 +0000","from_user":"Cris7ian","id_str":"30103562360983553","metadata":{"result_type":"recent"},"to_user_id":18616016,"text":"@josej30 hahaha no, es multiparadigma y es bastante lazy. Nothing like haskell, pero s\u00ed, el de Flash","id":30103562360983553,"from_user_id":14870909,"to_user":"josej30","geo":null,"iso_language_code":"es","to_user_id_str":"18616016","source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"2421643","profile_image_url":"http://a0.twimg.com/profile_images/1190361665/ernestgrumbles-17_normal.jpg","created_at":"Wed, 26 Jan 2011 03:20:24 +0000","from_user":"ernestgrumbles","id_str":"30102730756333568","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Wow... WolframAlpha did not know who Eddie Haskell is. Guess I'll never use that "knowledge engine" again.","id":30102730756333568,"from_user_id":2421643,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"128028225","profile_image_url":"http://a1.twimg.com/profile_images/1224994593/Coding_Drunk_normal.jpg","created_at":"Wed, 26 Jan 2011 03:14:21 +0000","from_user":"chewedwire","id_str":"30101204428132352","metadata":{"result_type":"recent"},"to_user_id":177539201,"text":"@tomheon How is Haskell better/different from CL or Scheme? I honestly don't know, although I'm becoming more curious.","id":30101204428132352,"from_user_id":128028225,"to_user":"tomheon","geo":null,"iso_language_code":"en","to_user_id_str":"177539201","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"13540930","profile_image_url":"http://a1.twimg.com/profile_images/1205312219/23467_350321383101_821143101_5114147_3010041_n_normal.jpg","created_at":"Wed, 26 Jan 2011 03:06:54 +0000","from_user":"goodfox","id_str":"30099329809129473","metadata":{"result_type":"recent"},"to_user_id":null,"text":"A day of vision & speeches. #SOTU now. And a wonderful Haskell Convocation address earlier today by Sinte Gleske President Lionel Bordeaux.","id":30099329809129473,"from_user_id":13540930,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.ubertwitter.com/bb/download.php" rel="nofollow">\u00dcberTwitter</a>"},{"from_user_id_str":"119185220","profile_image_url":"http://a0.twimg.com/profile_images/1089027228/dfg_normal.jpg","created_at":"Wed, 26 Jan 2011 03:03:38 +0000","from_user":"LaLiciouz_03","id_str":"30098510623805440","metadata":{"result_type":"recent"},"to_user_id":null,"text":"The Game with the girl room 330 Haskell follow us...","id":30098510623805440,"from_user_id":119185220,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"18616016","profile_image_url":"http://a2.twimg.com/profile_images/1173522726/214397343_normal.jpg","created_at":"Wed, 26 Jan 2011 02:57:25 +0000","from_user":"josej30","id_str":"30096946144215040","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Voy a extra\u00f1ar Haskell cuando regrese al mundo imperativo. Hay alg\u00fan lenguaje imperativo que tenga este poder funcional? #ci3661","id":30096946144215040,"from_user_id":18616016,"geo":null,"iso_language_code":"es","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"17671137","profile_image_url":"http://a2.twimg.com/profile_images/290264834/Haskell-logo-outer-glow_normal.png","created_at":"Wed, 26 Jan 2011 02:55:32 +0000","from_user":"Hackage","id_str":"30096471814574080","metadata":{"result_type":"recent"},"to_user_id":null,"text":"comonad-transformers 0.9.0, added by EdwardKmett: Haskell 98 comonad transformers http://bit.ly/h6xIsf","id":30096471814574080,"from_user_id":17671137,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"177539201","profile_image_url":"http://a0.twimg.com/profile_images/1178368800/img_normal.jpeg","created_at":"Wed, 26 Jan 2011 02:48:12 +0000","from_user":"tomheon","id_str":"30094626920603649","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Every time I look at Haskell I love it more.","id":30094626920603649,"from_user_id":177539201,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"60792568","profile_image_url":"http://a0.twimg.com/profile_images/1203647517/glenda-flash_normal.jpg","created_at":"Wed, 26 Jan 2011 02:40:42 +0000","from_user":"r_takaishi","id_str":"30092735935422464","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell\u3088\u308aD\u8a00\u8a9e\u304c\u4e0a\u3068\u306f\u601d\u308f\u306a\u304b\u3063\u305f\uff0e http://www.tiobe.com/index.php/content/paperinfo/tpci/index.html","id":30092735935422464,"from_user_id":60792568,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twmode.sf.net/" rel="nofollow">twmode</a>"},{"from_user_id_str":"160145510","profile_image_url":"http://a0.twimg.com/profile_images/1218108166/going_galt_normal.jpg","created_at":"Wed, 26 Jan 2011 02:39:31 +0000","from_user":"wtp1787","id_str":"30092439653974018","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @KLSouth: Eddie Haskell Goes to Washington... "You look really nice tonight, Ms Cleaver"","id":30092439653974018,"from_user_id":160145510,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"96616016","profile_image_url":"http://a1.twimg.com/profile_images/1196978169/Picture0002_normal.jpg","created_at":"Wed, 26 Jan 2011 02:39:20 +0000","from_user":"MelissaRNMBA","id_str":"30092392203816960","metadata":{"result_type":"recent"},"to_user_id":14862975,"text":"@KLSouth At least Eddie Haskell was entertaining.","id":30092392203816960,"from_user_id":96616016,"to_user":"KLSouth","geo":null,"iso_language_code":"en","to_user_id_str":"14862975","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"14862975","profile_image_url":"http://a0.twimg.com/profile_images/421596393/kls_4_normal.JPG","created_at":"Wed, 26 Jan 2011 02:38:29 +0000","from_user":"KLSouth","id_str":"30092178327871489","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Eddie Haskell Goes to Washington... "You look really nice tonight, Ms Cleaver"","id":30092178327871489,"from_user_id":14862975,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Wed, 26 Jan 2011 02:36:17 +0000","from_user":"listwarenet","id_str":"30091626869161984","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-beginners/84641-haskell-beginners-wildcards-in-expressions.html Haskell-beginners - Wild","id":30091626869161984,"from_user_id":144546280,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"},{"from_user_id_str":"24538048","profile_image_url":"http://a2.twimg.com/profile_images/1117267605/rope_normal.jpg","created_at":"Wed, 26 Jan 2011 02:23:14 +0000","from_user":"dbph","id_str":"30088341030440960","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @dnene: Skilled Calisthenics. Haskell code that outputs python which spits ruby which emits the haskell source. http://j.mp/YlQUL via @mfeathers","id":30088341030440960,"from_user_id":24538048,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"158951567","profile_image_url":"http://a3.twimg.com/profile_images/962721419/Logo_3_normal.jpg","created_at":"Wed, 26 Jan 2011 01:58:31 +0000","from_user":"YubaVetTech","id_str":"30082124207886336","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Dr. Haskell has just been awarded the prestigious Hayward Award for \u2018Excellence in Education\u2019. This award honors... http://fb.me/QgQCxd74","id":30082124207886336,"from_user_id":158951567,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.facebook.com/twitter" rel="nofollow">Facebook</a>"},{"from_user_id_str":"158951567","profile_image_url":"http://a3.twimg.com/profile_images/962721419/Logo_3_normal.jpg","created_at":"Wed, 26 Jan 2011 01:56:04 +0000","from_user":"YubaVetTech","id_str":"30081505476743168","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Dr. Haskell has just been awarded the prestigous Haward Award for Excellence in Education. This award honors... http://fb.me/PC9mYmCR","id":30081505476743168,"from_user_id":158951567,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.facebook.com/twitter" rel="nofollow">Facebook</a>"},{"from_user_id_str":"2331498","profile_image_url":"http://a3.twimg.com/profile_images/494632120/me_normal.jpg","created_at":"Wed, 26 Jan 2011 01:43:50 +0000","from_user":"Verus","id_str":"30078427155406848","metadata":{"result_type":"recent"},"to_user_id":79273052,"text":"@kami_joe \u3044\u3084\uff0c\u8ab2\u984c\u306f\u89e3\u6c7a\u5bfe\u8c61(\u30d1\u30ba\u30eb\u3068\u304b)\u3092\u4e0e\u3048\u3089\u308c\u3066\uff0c\u554f\u984c\u5b9a\u7fa9\u3068\u30d7\u30ed\u30b0\u30e9\u30df\u30f3\u30b0(\u6307\u5b9a\u8a00\u8a9e\u306fC++\u3082\u3057\u304f\u306fJava)\u3068\u3044\u3046\u3044\u308f\u3070\u666e\u901a\u306a\u8ab2\u984c\u3067\u306f\u3042\u308b\u3093\u3060\u3051\u3069\uff0e\u95a2\u6570\u578b\u8a00\u8a9e\u306fHaskell\u306e\u6388\u696d\u304c\u307e\u305f\u5225\u306b\u3042\u308b\u306e\uff0e","id":30078427155406848,"from_user_id":2331498,"to_user":"kami_joe","geo":null,"iso_language_code":"ja","to_user_id_str":"79273052","source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"79151233","profile_image_url":"http://a2.twimg.com/a/1295051201/images/default_profile_2_normal.png","created_at":"Wed, 26 Jan 2011 01:40:37 +0000","from_user":"cz_newdrafts","id_str":"30077617361125376","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell programming language http://bit.ly/gpPAwB","id":30077617361125376,"from_user_id":79151233,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://tommorris.org/" rel="nofollow">tommorris' hacksample</a>"},{"from_user_id_str":"2331498","profile_image_url":"http://a3.twimg.com/profile_images/494632120/me_normal.jpg","created_at":"Wed, 26 Jan 2011 01:02:57 +0000","from_user":"Verus","id_str":"30068139416879104","metadata":{"result_type":"recent"},"to_user_id":9252720,"text":"@shukukei Java\u3068C\u306f\u3042\u308b\u7a0b\u5ea6\u66f8\u3051\u3066\u3042\u305f\u308a\u307e\u3048\u306a\u3068\u3053\u308d\u304c\u3042\u308b\u304b\u3089\u306a\u30fc\uff0ePython\u306f\u500b\u4eba\u7684\u306b\u611f\u899a\u304c\u5408\u308f\u306a\u3044\uff0e\u611f\u899a\u306a\u306e\u3067\uff0c\u3082\u3046\u3069\u3046\u3057\u3088\u3046\u3082\u306a\u3044\uff57 \u3044\u307e\u306fScala\u3068Haskell\u3092\u3082\u3063\u3068\u6975\u3081\u305f\u3044\u3068\u3053\u308d\uff0e","id":30068139416879104,"from_user_id":2331498,"to_user":"shukukei","geo":null,"iso_language_code":"ja","to_user_id_str":"9252720","source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"2781460","profile_image_url":"http://a0.twimg.com/profile_images/82526625/.joeyicon_normal.jpg","created_at":"Wed, 26 Jan 2011 01:02:35 +0000","from_user":"joeyhess","id_str":"30068046538219520","metadata":{"result_type":"recent"},"to_user_id":null,"text":"just figured out that I can use parameterized types to remove a dependency loop in git-annex's type definitions. whee #haskell","id":30068046538219520,"from_user_id":2781460,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://identi.ca" rel="nofollow">identica</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Wed, 26 Jan 2011 00:54:22 +0000","from_user":"listwarenet","id_str":"30065977920061440","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-beginners/84466-haskell-beginners-bytestring-question.html Haskell-beginners - Bytestrin","id":30065977920061440,"from_user_id":144546280,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"},{"from_user_id_str":"1291845","profile_image_url":"http://a0.twimg.com/profile_images/1225743404/ThinOxygen-small-opaque-solidarity_normal.png","created_at":"Wed, 26 Jan 2011 00:52:07 +0000","from_user":"_aaron_","id_str":"30065412242669568","metadata":{"result_type":"recent"},"to_user_id":null,"text":"wanted: librly licensed high level native compiled lang with min runtime (otherwise cobra/mono would be perfect) for win. lua? haskell? ooc?","id":30065412242669568,"from_user_id":1291845,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"5912444","profile_image_url":"http://a2.twimg.com/profile_images/546261026/ssf0xg11_normal.jpg","created_at":"Wed, 26 Jan 2011 00:45:45 +0000","from_user":"shelarcy","id_str":"30063810773516288","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @Hackage: download 0.3.1.1, added by MagnusTherning: High-level file download based on URLs http://bit.ly/eHfiJB","id":30063810773516288,"from_user_id":5912444,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"135993","profile_image_url":"http://a2.twimg.com/profile_images/1190667086/myface2010small_normal.jpg","created_at":"Wed, 26 Jan 2011 00:41:00 +0000","from_user":"kudzu_naoki","id_str":"30062613287141376","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @tanakh: \u9b54\u6cd5Haskell\u5c11\u5973\u5019\u88dc\u3092\u63a2\u3059\u306e\u3082\u5927\u5909\u306a\u3093\u3060","id":30062613287141376,"from_user_id":135993,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"52620546","profile_image_url":"http://a1.twimg.com/profile_images/434693356/twitter-icon_normal.png","created_at":"Wed, 26 Jan 2011 00:40:25 +0000","from_user":"omasanori","id_str":"30062465656033280","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u9b54\u6cd5Haskell\u5c11\u5973\u306e\u4e00\u65e5\u306fGHC HEAD\u306e\u30d3\u30eb\u30c9\u304b\u3089\u59cb\u307e\u308b","id":30062465656033280,"from_user_id":52620546,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.movatwi.jp" rel="nofollow">www.movatwi.jp</a>"},{"from_user_id_str":"52620546","profile_image_url":"http://a1.twimg.com/profile_images/434693356/twitter-icon_normal.png","created_at":"Wed, 26 Jan 2011 00:37:12 +0000","from_user":"omasanori","id_str":"30061656331526144","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @tanakh: \u50d5\u3068\u5951\u7d04\u3057\u3066\u9b54\u6cd5Haskell\u5c11\u5973\u306b\u306a\u308d\u3046\u3088\uff01","id":30061656331526144,"from_user_id":52620546,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"135993","profile_image_url":"http://a2.twimg.com/profile_images/1190667086/myface2010small_normal.jpg","created_at":"Wed, 26 Jan 2011 00:35:42 +0000","from_user":"kudzu_naoki","id_str":"30061282665168896","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @tanakh: \u50d5\u3068\u5951\u7d04\u3057\u3066\u9b54\u6cd5Haskell\u5c11\u5973\u306b\u306a\u308d\u3046\u3088\uff01","id":30061282665168896,"from_user_id":135993,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"1631333","profile_image_url":"http://a1.twimg.com/profile_images/81268862/profile300_normal.jpg","created_at":"Wed, 26 Jan 2011 00:30:02 +0000","from_user":"qnighy","id_str":"30059855884582913","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @tanakh: \u50d5\u3068\u5951\u7d04\u3057\u3066\u9b54\u6cd5Haskell\u5c11\u5973\u306b\u306a\u308d\u3046\u3088\uff01","id":30059855884582913,"from_user_id":1631333,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"9093754","profile_image_url":"http://a1.twimg.com/profile_images/99435906/PHD_3d_col_blk_normal.jpg","created_at":"Wed, 26 Jan 2011 00:26:20 +0000","from_user":"phdwine","id_str":"30058925516656640","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Last weekend of Tri Nations Tasting with PHD wines at Haskell Vineyards. Hope you didn't miss the Pinot Noir tasting last week !","id":30058925516656640,"from_user_id":9093754,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"2119923","profile_image_url":"http://a2.twimg.com/profile_images/1096701078/djayprofile_normal.jpg","created_at":"Wed, 26 Jan 2011 00:21:14 +0000","from_user":"djay75","id_str":"30057639543050240","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @dnene: Skilled Calisthenics. Haskell code that outputs python which spits ruby which emits the haskell source. http://j.mp/YlQUL via @mfeathers","id":30057639543050240,"from_user_id":2119923,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"134323731","profile_image_url":"http://a2.twimg.com/profile_images/1225818824/IMG00518-20110125-1547_normal.jpg","created_at":"Wed, 26 Jan 2011 00:19:30 +0000","from_user":"PrinceOfBrkeley","id_str":"30057205554216960","metadata":{"result_type":"recent"},"to_user_id":167093027,"text":"@PayThaPrince go to haskell.","id":30057205554216960,"from_user_id":134323731,"to_user":"PayThaPrince","geo":null,"iso_language_code":"en","to_user_id_str":"167093027","source":"<a href="http://blackberry.com/twitter" rel="nofollow">Twitter for BlackBerry\u00ae</a>"},{"from_user_id_str":"705857","profile_image_url":"http://a1.twimg.com/profile_images/429483912/ben_twitter_normal.jpg","created_at":"Wed, 26 Jan 2011 00:03:28 +0000","from_user":"bennadel","id_str":"30053166972141569","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Using #Homebrew to install Haskell - the last of the Seven Languages (in Seven Weeks) http://bit.ly/eA9Cv1 This has been some journey.","id":30053166972141569,"from_user_id":705857,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"251466","profile_image_url":"http://a2.twimg.com/profile_images/1194100934/pass_normal.jpg","created_at":"Wed, 26 Jan 2011 00:02:54 +0000","from_user":"simonszu","id_str":"30053025502466048","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Ouh yeah! Ich werde doch produktiv sein, diese Semesterferien. Ich werde funktional Programmieren lernen. #haskell, Baby.","id":30053025502466048,"from_user_id":251466,"geo":null,"iso_language_code":"de","to_user_id_str":null,"source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"357786","profile_image_url":"http://a0.twimg.com/profile_images/612044841/FM_2010_normal.jpg","created_at":"Tue, 25 Jan 2011 23:59:13 +0000","from_user":"diligiant","id_str":"30052100973006848","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @paulrbrown: "...we only discovered a single bug after compilation." (http://t.co/K0wlEYz) #haskell","id":30052100973006848,"from_user_id":357786,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"101597523","profile_image_url":"http://a1.twimg.com/profile_images/1206183256/2010-12-12-204902_normal.jpg","created_at":"Tue, 25 Jan 2011 23:54:46 +0000","from_user":"wlad_kent","id_str":"30050977964892160","metadata":{"result_type":"recent"},"to_user_id":86297184,"text":"@Nilson_Neto Isso eh bem basico. quando vc estiver estudando recurs\u00e3o em Haskell, ai vc vai ver oq eh papo de nerd - kkk - 1\u00ba periodo isso.","id":30050977964892160,"from_user_id":101597523,"to_user":"Nilson_Neto","geo":null,"iso_language_code":"pt","to_user_id_str":"86297184","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Tue, 25 Jan 2011 23:51:22 +0000","from_user":"listwarenet","id_str":"30050123383832577","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-cafe/84336-haskell-cafe-monomorphic-let-bindings-and-darcs.html Haskell-cafe - Monomorph","id":30050123383832577,"from_user_id":144546280,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"},{"from_user_id_str":"5776901","profile_image_url":"http://a0.twimg.com/profile_images/472682157/lucabw_normal.JPG","created_at":"Tue, 25 Jan 2011 23:48:40 +0000","from_user":"lsbardel","id_str":"30049446469312512","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Very interesting technology stack these guys use http://bit.ly/ghAjS7 #python #redis #haskell","id":30049446469312512,"from_user_id":5776901,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"3005901","profile_image_url":"http://a0.twimg.com/profile_images/278943006/Lone_Pine_Peak_-_Peter_200x200_normal.jpg","created_at":"Tue, 25 Jan 2011 23:45:48 +0000","from_user":"pmonks","id_str":"30048721110573056","metadata":{"result_type":"recent"},"to_user_id":203834278,"text":"@techielicous Haskell: http://bit.ly/gy3oFi ;-)","id":30048721110573056,"from_user_id":3005901,"to_user":"techielicous","geo":null,"iso_language_code":"en","to_user_id_str":"203834278","source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"162697074","profile_image_url":"http://a2.twimg.com/profile_images/826205838/ryan3_normal.jpg","created_at":"Tue, 25 Jan 2011 23:44:47 +0000","from_user":"TheRonaldMCD","id_str":"30048468781244416","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I'm at Aldi Food Market (4122 Gaston Ave, Haskell, Dallas) http://4sq.com/ekqRY7","id":30048468781244416,"from_user_id":162697074,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://foursquare.com" rel="nofollow">foursquare</a>"},{"from_user_id_str":"203834278","profile_image_url":"http://a0.twimg.com/profile_images/1223375080/me_normal.jpg","created_at":"Tue, 25 Jan 2011 23:44:04 +0000","from_user":"techielicous","id_str":"30048286589067264","metadata":{"result_type":"recent"},"to_user_id":3005901,"text":"@pmonks I was thinking Haskell or Scheme","id":30048286589067264,"from_user_id":203834278,"to_user":"pmonks","geo":null,"iso_language_code":"en","to_user_id_str":"3005901","source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"537690","profile_image_url":"http://a3.twimg.com/profile_images/45665122/nushiostamp_normal.jpg","created_at":"Tue, 25 Jan 2011 23:38:14 +0000","from_user":"nushio","id_str":"30046818658164737","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u305d\u3046\u3044\u3084\u5951\u7d04\u306b\u3088\u308b\u30d7\u30ed\u30b0\u30e9\u30df\u30f3\u30b0\u3068\u304b\u3042\u3063\u305f\u306a\u3002Haskell\u306a\u3093\u304b\u3088\u308a\u3042\u3063\u3061\u306e\u65b9\u304c\u9b54\u6cd5\u5c11\u5973\u547c\u3070\u308f\u308a\u306b\u3075\u3055\u308f\u3057\u3044\u3002","id":30046818658164737,"from_user_id":537690,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"181192","profile_image_url":"http://a2.twimg.com/profile_images/1089890701/q530888600_9828_normal.jpg","created_at":"Tue, 25 Jan 2011 23:38:03 +0000","from_user":"aodag","id_str":"30046772223016960","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @omasanori: \u300c\u3082\u3046\u4f55\u5e74\u3082Haskell\u306e\u3053\u3068\u3057\u304b\u8003\u3048\u3066\u306a\u304b\u3063\u305f\u304b\u3089\u306a\u3001\u30eb\u30fc\u30d7\u306e\u4f7f\u3044\u65b9\u5fd8\u308c\u3066\u305f\u300d","id":30046772223016960,"from_user_id":181192,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.movatwi.jp" rel="nofollow">www.movatwi.jp</a>"},{"from_user_id_str":"5886055","profile_image_url":"http://a3.twimg.com/profile_images/85531669/ichi_normal.jpg","created_at":"Tue, 25 Jan 2011 23:37:53 +0000","from_user":"kanaya","id_str":"30046729243983873","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u9e97\u3057\u3044\u3002\u201c@omasanori: \u300c\u3082\u3046\u4f55\u5e74\u3082Haskell\u306e\u3053\u3068\u3057\u304b\u8003\u3048\u3066\u306a\u304b\u3063\u305f\u304b\u3089\u306a\u3001\u30eb\u30fc\u30d7\u306e\u4f7f\u3044\u65b9\u5fd8\u308c\u3066\u305f\u300d\u201d","id":30046729243983873,"from_user_id":5886055,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://itunes.apple.com/app/twitter/id333903271?mt=8" rel="nofollow">Twitter for iPad</a>"},{"from_user_id_str":"52620546","profile_image_url":"http://a1.twimg.com/profile_images/434693356/twitter-icon_normal.png","created_at":"Tue, 25 Jan 2011 23:36:26 +0000","from_user":"omasanori","id_str":"30046367187476481","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u300c\u3082\u3046\u4f55\u5e74\u3082Haskell\u306e\u3053\u3068\u3057\u304b\u8003\u3048\u3066\u306a\u304b\u3063\u305f\u304b\u3089\u306a\u3001\u30eb\u30fc\u30d7\u306e\u4f7f\u3044\u65b9\u5fd8\u308c\u3066\u305f\u300d","id":30046367187476481,"from_user_id":52620546,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.movatwi.jp" rel="nofollow">www.movatwi.jp</a>"},{"from_user_id_str":"1659992","profile_image_url":"http://a1.twimg.com/profile_images/504488750/1_normal.jpg","created_at":"Tue, 25 Jan 2011 23:16:13 +0000","from_user":"finalfusion","id_str":"30041278544609280","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @necocen: Haskell\u306e\u30df\u30b5\u30ef\u3001\u3068\u3044\u3046\u3082\u306e\u3092\u8003\u3048\u3066\u307f\u3066\u3071\u3063\u3068\u3057\u306a\u3044","id":30041278544609280,"from_user_id":1659992,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"272513","profile_image_url":"http://a2.twimg.com/profile_images/320244078/Mike_Painting2_normal.png","created_at":"Tue, 25 Jan 2011 23:05:09 +0000","from_user":"mikehadlow","id_str":"30038492373319680","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Just written the same simple program in C#, F# and Haskell: 18, 12 and 9 LoC respectively. And I'm much better at C# than F# or Haskell.","id":30038492373319680,"from_user_id":272513,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"89393264","profile_image_url":"http://a0.twimg.com/profile_images/1169486472/020_portland_me_normal.jpg","created_at":"Tue, 25 Jan 2011 23:01:28 +0000","from_user":"newsportlandme","id_str":"30037564589084673","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Governor's Choice to Run Maine DOC Under Scrutiny - MPBN: State Rep. Anne Haskell, a Portland Democrat, says Mai... http://bit.ly/fO30gC","id":30037564589084673,"from_user_id":89393264,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"38138","profile_image_url":"http://a3.twimg.com/profile_images/1212565885/Screen_shot_2011-01-11_at_5.28.47_PM_normal.png","created_at":"Tue, 25 Jan 2011 22:59:55 +0000","from_user":"michaelneale","id_str":"30037174615281664","metadata":{"result_type":"recent"},"to_user_id":null,"text":"The haskell EvilMangler http://t.co/P2Tls7J","id":30037174615281664,"from_user_id":38138,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"45692","profile_image_url":"http://a3.twimg.com/profile_images/1177741507/dogkarno_r_normal.jpg","created_at":"Tue, 25 Jan 2011 22:45:06 +0000","from_user":"karno","id_str":"30033448286552064","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell\u3063\u3066\u95a2\u6570\u306b\u30ab\u30ec\u30fc\u7c89\u3076\u3061\u8fbc\u3080\u3068\u304b\u306a\u3093\u3068\u304b","id":30033448286552064,"from_user_id":45692,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://yubitter.com/" rel="nofollow">yubitter</a>"},{"from_user_id_str":"27605","profile_image_url":"http://a2.twimg.com/profile_images/15826632/meron_normal.jpg","created_at":"Tue, 25 Jan 2011 22:44:23 +0000","from_user":"celeron1ghz","id_str":"30033268761956352","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @necocen: Haskell\u306e\u30df\u30b5\u30ef\u3001\u3068\u3044\u3046\u3082\u306e\u3092\u8003\u3048\u3066\u307f\u3066\u3071\u3063\u3068\u3057\u306a\u3044","id":30033268761956352,"from_user_id":27605,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"12901","profile_image_url":"http://a1.twimg.com/profile_images/56091349/haruhi_nagato-Y_normal.jpg","created_at":"Tue, 25 Jan 2011 22:43:30 +0000","from_user":"necocen","id_str":"30033044035346432","metadata":{"result_type":"recent"},"to_user_id":null,"text":"\u307e\u3042Haskell\u77e5\u3089\u3093\u3057\u306d","id":30033044035346432,"from_user_id":12901,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"12901","profile_image_url":"http://a1.twimg.com/profile_images/56091349/haruhi_nagato-Y_normal.jpg","created_at":"Tue, 25 Jan 2011 22:42:54 +0000","from_user":"necocen","id_str":"30032894856531968","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell\u306e\u30df\u30b5\u30ef\u3001\u3068\u3044\u3046\u3082\u306e\u3092\u8003\u3048\u3066\u307f\u3066\u3071\u3063\u3068\u3057\u306a\u3044","id":30032894856531968,"from_user_id":12901,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"10821270","profile_image_url":"http://a0.twimg.com/profile_images/1195474259/Salto_Marlon_normal.jpg","created_at":"Tue, 25 Jan 2011 22:35:09 +0000","from_user":"jjedMoriAnktah","id_str":"30030942106025984","metadata":{"result_type":"recent"},"to_user_id":null,"text":""A Haskell program that outputs a Python program that outputs a Ruby program that outputs the original Haskell program" http://is.gd/E6Julu","id":30030942106025984,"from_user_id":10821270,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"7554762","profile_image_url":"http://a0.twimg.com/profile_images/100515212/ajay-photo_normal.jpg","created_at":"Tue, 25 Jan 2011 22:34:30 +0000","from_user":"comatose_kid","id_str":"30030780205899776","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @bumptech: Bump Dev Blog - Why we use Haskell at Bump http://devblog.bu.mp/haskell-at-bump","id":30030780205899776,"from_user_id":7554762,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"148474705","profile_image_url":"http://a0.twimg.com/profile_images/1119234716/fur_hat_-_gilbeys_vodka_-_life_-_11-30-1962_normal.JPG","created_at":"Tue, 25 Jan 2011 22:29:19 +0000","from_user":"landmvintage","id_str":"30029476003840000","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @faerymoongodess: Magnificent Miriam Haskell Baroque Pearl Necklace by @MercyMadge http://etsy.me/hqRl51","id":30029476003840000,"from_user_id":148474705,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"37715508","profile_image_url":"http://a1.twimg.com/profile_images/1207891411/ballerina_normal.jpg","created_at":"Tue, 25 Jan 2011 22:24:52 +0000","from_user":"faerymoongodess","id_str":"30028356326002688","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Magnificent Miriam Haskell Baroque Pearl Necklace by @MercyMadge http://etsy.me/hqRl51","id":30028356326002688,"from_user_id":37715508,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"17671137","profile_image_url":"http://a2.twimg.com/profile_images/290264834/Haskell-logo-outer-glow_normal.png","created_at":"Tue, 25 Jan 2011 22:17:16 +0000","from_user":"Hackage","id_str":"30026442456694784","metadata":{"result_type":"recent"},"to_user_id":null,"text":"base16-bytestring 0.1.0.0, added by BryanOSullivan: Fast base16 (hex) encoding and deconding for ByteStrings http://bit.ly/eu75TN","id":30026442456694784,"from_user_id":17671137,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"199750997","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Tue, 25 Jan 2011 22:12:07 +0000","from_user":"benreads","id_str":"30025146991382528","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Writing Systems Software in a Functional Language -- brief, but fun. I want to see how well they can make Systems Haskell perform at scale.","id":30025146991382528,"from_user_id":199750997,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"35359797","profile_image_url":"http://a1.twimg.com/profile_images/1173453785/48893_521140819_1896062_q_normal.jpg","created_at":"Tue, 25 Jan 2011 22:09:45 +0000","from_user":"jcawthorne1","id_str":"30024549265309696","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Just saw Jeff Haskell give the middle finger!! Lol awesome","id":30024549265309696,"from_user_id":35359797,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"13540930","profile_image_url":"http://a1.twimg.com/profile_images/1205312219/23467_350321383101_821143101_5114147_3010041_n_normal.jpg","created_at":"Tue, 25 Jan 2011 22:06:44 +0000","from_user":"goodfox","id_str":"30023790381498369","metadata":{"result_type":"recent"},"to_user_id":null,"text":"At the Haskell Convocation. (@ Haskell Indian Nations U Auditorium) http://4sq.com/eKKXyn","id":30023790381498369,"from_user_id":13540930,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://foursquare.com" rel="nofollow">foursquare</a>"},{"from_user_id_str":"14674418","profile_image_url":"http://a2.twimg.com/profile_images/238230125/IMG_1030-1_normal.jpg","created_at":"Tue, 25 Jan 2011 22:02:31 +0000","from_user":"sanityinc","id_str":"30022731919523840","metadata":{"result_type":"recent"},"to_user_id":371289,"text":"@xshay Haskell's great, but Clojure's similarly lazy in all the ways that matter, and is more practical for day-to-day use.","id":30022731919523840,"from_user_id":14674418,"to_user":"xshay","geo":null,"iso_language_code":"en","to_user_id_str":"371289","source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"371289","profile_image_url":"http://a2.twimg.com/profile_images/1113482439/me-brisbane_normal.jpg","created_at":"Tue, 25 Jan 2011 21:58:29 +0000","from_user":"xshay","id_str":"30021714444292096","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Just made a lazy sequence of prime numbers in haskell. I'm smitten.","id":30021714444292096,"from_user_id":371289,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"199453873","profile_image_url":"http://a3.twimg.com/a/1294785484/images/default_profile_3_normal.png","created_at":"Tue, 25 Jan 2011 21:48:40 +0000","from_user":"stackfeed","id_str":"30019243982454784","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Practical Scala reference manual, for searching things like method names: Hello, \n\nInspired by\nHaskell API Searc... http://bit.ly/g4zWZQ","id":30019243982454784,"from_user_id":199453873,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"17489366","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Tue, 25 Jan 2011 21:45:32 +0000","from_user":"aapnoot","id_str":"30018455189065728","metadata":{"result_type":"recent"},"to_user_id":null,"text":"download 0.3.1, added by MagnusTherning: High-level file download based on URLs http://bit.ly/i8mYvi","id":30018455189065728,"from_user_id":17489366,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"17489366","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Tue, 25 Jan 2011 21:45:31 +0000","from_user":"aapnoot","id_str":"30018452601180160","metadata":{"result_type":"recent"},"to_user_id":null,"text":"download 0.3.1.1, added by MagnusTherning: High-level file download based on URLs http://bit.ly/eHfiJB","id":30018452601180160,"from_user_id":17489366,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"17671137","profile_image_url":"http://a2.twimg.com/profile_images/290264834/Haskell-logo-outer-glow_normal.png","created_at":"Tue, 25 Jan 2011 21:45:31 +0000","from_user":"Hackage","id_str":"30018451867176960","metadata":{"result_type":"recent"},"to_user_id":null,"text":"download 0.3.1, added by MagnusTherning: High-level file download based on URLs http://bit.ly/i8mYvi","id":30018451867176960,"from_user_id":17671137,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"138502705","profile_image_url":"http://a1.twimg.com/profile_images/1083845614/yclogo_normal.gif","created_at":"Tue, 25 Jan 2011 21:45:04 +0000","from_user":"newsyc100","id_str":"30018340839755777","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell improves log processing 4x over Python http://devblog.bu.mp/haskell-at-bump (http://bit.ly/gQxxR8)","id":30018340839755777,"from_user_id":138502705,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://news.ycombinator.com" rel="nofollow">newsyc</a>"},{"from_user_id_str":"1578246","profile_image_url":"http://a0.twimg.com/profile_images/59312315/avatar_simpson_small_normal.jpg","created_at":"Tue, 25 Jan 2011 21:43:32 +0000","from_user":"magthe","id_str":"30017953801969665","metadata":{"result_type":"recent"},"to_user_id":null,"text":"New version of download uploaded to #hackage #haskell","id":30017953801969665,"from_user_id":1578246,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://api.supertweet.net" rel="nofollow">MyAuth API Proxy</a>"},{"from_user_id_str":"135838970","profile_image_url":"http://a2.twimg.com/profile_images/1079929891/logo_normal.png","created_at":"Tue, 25 Jan 2011 21:37:51 +0000","from_user":"reward999","id_str":"30016525180084224","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Found Great Dane (Main & Haskell- Dallas): We found a great dane. 214-712-0000 http://bit.ly/fQ8iBw","id":30016525180084224,"from_user_id":135838970,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"137719265","profile_image_url":"http://a2.twimg.com/profile_images/1092224079/8__4__normal.jpg","created_at":"Tue, 25 Jan 2011 21:34:22 +0000","from_user":"WeiMatas","id_str":"30015646020411392","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Fourth day Rez party Eddie Haskell County in second life \u2013 which took place in cabaret Tadd","id":30015646020411392,"from_user_id":137719265,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://dlvr.it" rel="nofollow">dlvr.it</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Tue, 25 Jan 2011 21:33:21 +0000","from_user":"listwarenet","id_str":"30015392571195392","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-cafe/83889-haskell-cafe-gpl-license-of-h-matrix-and-prelude-numeric.html Haskell-cafe -","id":30015392571195392,"from_user_id":144546280,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"}],"max_id":30121530767708160,"since_id":0,"refresh_url":"?since_id=30121530767708160&q=haskell","next_page":"?page=2&max_id=30121530767708160&rpp=100&q=haskell","results_per_page":100,"page":1,"completed_in":1.195569,"since_id_str":"0","max_id_str":"30121530767708160","query":"haskell"} aeson-1.4.2.0/benchmarks/json-data/twitter20.json0000755000000000000000000002744400000000000017662 0ustar0000000000000000{"results":[{"from_user_id_str":"166199691","profile_image_url":"http://a2.twimg.com/profile_images/1252958188/38_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:26 +0000","from_user":"_classicc","id_str":"41191052790603776","metadata":{"result_type":"recent"},"to_user_id":null,"text":"my twitter is actin slow today.","id":41191052790603776,"from_user_id":166199691,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"138835410","profile_image_url":"http://a1.twimg.com/profile_images/1250985094/243321801_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:26 +0000","from_user":"amereronday","id_str":"41191050307567616","metadata":{"result_type":"recent"},"to_user_id":null,"text":"twitter jail, here i come.","id":41191050307567616,"from_user_id":138835410,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"359548","profile_image_url":"http://a2.twimg.com/profile_images/53612334/don_otvos_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:26 +0000","from_user":"donnyo","id_str":"41191050110451712","metadata":{"result_type":"recent"},"to_user_id":7074534,"text":"@stlsmallbiz I see there is currently a Twitter promo too....tempting....","id":41191050110451712,"from_user_id":359548,"to_user":"stlsmallbiz","geo":null,"iso_language_code":"en","place":{"id":"82b7b2f97b12261d","type_":"poi","full_name":"Yammer Inc, San Francisco"},"to_user_id_str":"7074534","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"122523770","profile_image_url":"http://a0.twimg.com/profile_images/1073533262/11646_1076222405045_1810798478_156114_3663737_n_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:26 +0000","from_user":"msBreChan","id_str":"41191049720238080","metadata":{"result_type":"recent"},"to_user_id":null,"text":"so twitter gt spam now -_-","id":41191049720238080,"from_user_id":122523770,"geo":{"type_":"Point","coordinates":[35.2213,-80.8276]},"iso_language_code":"en","place":{"id":"4d5ed95f830e9b41","type_":"neighborhood","full_name":"Elizabeth, Charlotte"},"to_user_id_str":null,"source":"<a href="http://mobile.twitter.com" rel="nofollow">Twitter for Android</a>"},{"from_user_id_str":"229024950","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_6_normal.png","created_at":"Fri, 25 Feb 2011 17:41:25 +0000","from_user":"NinaMaechik","id_str":"41191047853912064","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Glad I can remember my twitter password! LOL! Hugs to Nick from his aunties...","id":41191047853912064,"from_user_id":229024950,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"215545822","profile_image_url":"http://a2.twimg.com/profile_images/1239909540/RTL_normal.png","created_at":"Fri, 25 Feb 2011 17:41:25 +0000","from_user":"RightToLaugh","id_str":"41191047371558912","metadata":{"result_type":"recent"},"to_user_id":null,"text":"#Bacon wrapped dates http://bit.ly/hUxVC9 Just like my grandma used to make http://twitter.com/#","id":41191047371558912,"from_user_id":215545822,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"217845526","profile_image_url":"http://a0.twimg.com/sticky/default_profile_images/default_profile_3_normal.png","created_at":"Fri, 25 Feb 2011 17:41:25 +0000","from_user":"TheShoeLooker","id_str":"41191047052804096","metadata":{"result_type":"recent"},"to_user_id":38033240,"text":"@ShoeDazzle love love love to twitter or blog about your deals and shoes!\ntheshoelooker.blogspot.com","id":41191047052804096,"from_user_id":217845526,"to_user":"shoedazzle","geo":null,"iso_language_code":"en","to_user_id_str":"38033240","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"24953438","profile_image_url":"http://a3.twimg.com/profile_images/1181252763/76820_10150100014748783_677998782_7386695_4377006_n_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:25 +0000","from_user":"liljermaine32","id_str":"41191046025056256","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Twitter fam I gotta question 4 ya is texas south or midwest #arguments","id":41191046025056256,"from_user_id":24953438,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://mobile.twitter.com" rel="nofollow">Twitter for Android</a>"},{"from_user_id_str":"122451024","profile_image_url":"http://a2.twimg.com/profile_images/1143400129/100706-ETCanada_201134_1__normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:25 +0000","from_user":"Kim_DEon","id_str":"41191045161164801","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Help @CARE @EvaLongoria and ME use Twitter to change the lives of girls in poverty across the world! Ready? Go to http://TwitChange.com NOW!","id":41191045161164801,"from_user_id":122451024,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"128351479","profile_image_url":"http://a3.twimg.com/profile_images/1150198829/Kirby_Photo__edit__normal.JPG","created_at":"Fri, 25 Feb 2011 17:41:24 +0000","from_user":"TheDaveKirby","id_str":"41191043894493184","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Maybe its time to clean house...MY HOUSE http://bit.ly/ejG22P","id":41191043894493184,"from_user_id":128351479,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"87512773","profile_image_url":"http://a0.twimg.com/profile_images/1252511106/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:24 +0000","from_user":"supportthehood","id_str":"41191043206610946","metadata":{"result_type":"recent"},"to_user_id":2467330,"text":"@eastcoastmp3 #FF it's the way twitter works !!!","id":41191043206610946,"from_user_id":87512773,"to_user":"eastcoastmp3","geo":null,"iso_language_code":"en","to_user_id_str":"2467330","source":"<a href="http://twitter.com/" rel="nofollow">Twitter for iPhone</a>"},{"from_user_id_str":"149894545","profile_image_url":"http://a0.twimg.com/profile_images/1219334400/patrick_camo_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:24 +0000","from_user":"suburbpat","id_str":"41191040912330752","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I havent had a rib session on twitter in a while.......I wanna Rib with a nigga with alot followers lol","id":41191040912330752,"from_user_id":149894545,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"97749622","profile_image_url":"http://a0.twimg.com/profile_images/1254640781/IMG1633A_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:24 +0000","from_user":"jrricardosantos","id_str":"41191040547430400","metadata":{"result_type":"recent"},"to_user_id":101017476,"text":"@yofzs pq tirou o CAPS LOCK? kkkk tava bem legal...hehehe eu estou no t\u00e9dio...kkk tbm estou no twitter e msn..aff!!","id":41191040547430400,"from_user_id":97749622,"to_user":"yofzs","geo":null,"iso_language_code":"en","to_user_id_str":"101017476","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"94381536","profile_image_url":"http://a1.twimg.com/profile_images/1174777929/41509_100001699300415_3521888_n_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:23 +0000","from_user":"DonNieves","id_str":"41191038978752512","metadata":{"result_type":"recent"},"to_user_id":151926400,"text":"@TiiH13 cheira meu ovo, no email, no orkut, no msn, no facebook, no twitter, no skype, no spark, no ICQ e no google talk","id":41191038978752512,"from_user_id":94381536,"to_user":"TiiH13","geo":null,"iso_language_code":"en","to_user_id_str":"151926400","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"211858432","profile_image_url":"http://a3.twimg.com/profile_images/1231906180/JonasBrothers_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:23 +0000","from_user":"OriginalJBfans","id_str":"41191038328651776","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I literally forgot about this twitter... so whats occuring followers?","id":41191038328651776,"from_user_id":211858432,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"90317132","profile_image_url":"http://a3.twimg.com/profile_images/1230085056/254101635_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:23 +0000","from_user":"Just2smooth","id_str":"41191036936126464","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Wassup twitter","id":41191036936126464,"from_user_id":90317132,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://ubersocial.com" rel="nofollow">\u00dcberSocial</a>"},{"from_user_id_str":"144771504","profile_image_url":"http://a1.twimg.com/profile_images/1243343836/image_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:23 +0000","from_user":"ima_b_b_badman","id_str":"41191036638339072","metadata":{"result_type":"recent"},"to_user_id":null,"text":"i been M.I.A. all day twitter my bad","id":41191036638339072,"from_user_id":144771504,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"207922664","profile_image_url":"http://a2.twimg.com/profile_images/1237106108/258356167_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:22 +0000","from_user":"itsthecarter_","id_str":"41191036013391873","metadata":{"result_type":"recent"},"to_user_id":null,"text":"twitter is a stupid addiction.","id":41191036013391873,"from_user_id":207922664,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://ubersocial.com" rel="nofollow">\u00dcberSocial</a>"},{"from_user_id_str":"150000649","profile_image_url":"http://a0.twimg.com/profile_images/1237789059/belllaa_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:22 +0000","from_user":"angelicabrvo","id_str":"41191035707207680","metadata":{"result_type":"recent"},"to_user_id":null,"text":"que hubo twitter? huy que feoxd","id":41191035707207680,"from_user_id":150000649,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://blackberry.com/twitter" rel="nofollow">Twitter for BlackBerry\u00ae</a>"},{"from_user_id_str":"185713003","profile_image_url":"http://a2.twimg.com/profile_images/1191421540/163229_177015295661467_154687431227587_492170_2147500_n_normal.jpg","created_at":"Fri, 25 Feb 2011 17:41:22 +0000","from_user":"downbytheshores","id_str":"41191033945595905","metadata":{"result_type":"recent"},"to_user_id":null,"text":"follow us on twitter\nwww.twitter.com/downbytheshores http://fb.me/DhDS915e","id":41191033945595905,"from_user_id":185713003,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.facebook.com/twitter" rel="nofollow">Facebook</a>"}],"max_id":41191052790603776,"since_id":38643906774044672,"refresh_url":"?since_id=41191052790603776&q=twitter","next_page":"?page=2&max_id=41191052790603776&rpp=20&lang=en&q=twitter","results_per_page":20,"page":1,"completed_in":0.128719,"warning":"adjusted since_id to 38643906774044672 (), requested since_id was older than allowed -- since_id removed for pagination.","since_id_str":"38643906774044672","max_id_str":"41191052790603776","query":"twitter"} aeson-1.4.2.0/benchmarks/json-data/twitter50.json0000755000000000000000000007631500000000000017666 0ustar0000000000000000{"results":[{"from_user_id_str":"207858021","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Wed, 26 Jan 2011 04:30:38 +0000","from_user":"pboudarga","id_str":"30120402839666689","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I'm at Rolla Sushi Grill (27737 Bouquet Canyon Road, #106, Btw Haskell Canyon and Rosedell Drive, Saugus) http://4sq.com/gqqdhs","id":30120402839666689,"from_user_id":207858021,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://foursquare.com" rel="nofollow">foursquare</a>"},{"from_user_id_str":"69988683","profile_image_url":"http://a0.twimg.com/profile_images/1211955817/avatar_7888_normal.gif","created_at":"Wed, 26 Jan 2011 04:25:23 +0000","from_user":"YNK33","id_str":"30119083059978240","metadata":{"result_type":"recent"},"to_user_id":null,"text":"hsndfile 0.5.0: Free and open source Haskell bindings for libsndfile http://bit.ly/gHaBWG Mac Os","id":30119083059978240,"from_user_id":69988683,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"81492","profile_image_url":"http://a1.twimg.com/profile_images/423894208/Picture_7_normal.jpg","created_at":"Wed, 26 Jan 2011 04:24:28 +0000","from_user":"satzz","id_str":"30118851488251904","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Emacs\u306e\u30e2\u30fc\u30c9\u8868\u793a\u304c\u4eca(Ruby Controller Outputz RoR Flymake REl hs)\u3068\u306a\u3063\u3066\u3066\u3088\u304f\u308f\u304b\u3089\u306a\u3044\u3093\u3060\u3051\u3069\u6700\u5f8c\u306eREl\u3068\u304bhs\u3063\u3066\u4f55\u3060\u308d\u3046\u2026haskell\u3068\u304b2\u5e74\u4ee5\u4e0a\u66f8\u3044\u3066\u306a\u3044\u3051\u3069\u2026","id":30118851488251904,"from_user_id":81492,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://www.hootsuite.com" rel="nofollow">HootSuite</a>"},{"from_user_id_str":"9518356","profile_image_url":"http://a2.twimg.com/profile_images/119165723/ocaml-icon_normal.png","created_at":"Wed, 26 Jan 2011 04:19:19 +0000","from_user":"planet_ocaml","id_str":"30117557788741632","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I so miss #haskell type classes in #ocaml - i want to do something like refinement. Also why does ocaml not have... http://bit.ly/geYRwt","id":30117557788741632,"from_user_id":9518356,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"218059","profile_image_url":"http://a1.twimg.com/profile_images/1053837723/twitter-icon9_normal.jpg","created_at":"Wed, 26 Jan 2011 04:16:32 +0000","from_user":"aprikip","id_str":"30116854940835840","metadata":{"result_type":"recent"},"to_user_id":null,"text":"yatex-mode\u3084haskell-mode\u306e\u3053\u3068\u3067\u3059\u306d\u3001\u308f\u304b\u308a\u307e\u3059\u3002","id":30116854940835840,"from_user_id":218059,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://sites.google.com/site/yorufukurou/" rel="nofollow">YoruFukurou</a>"},{"from_user_id_str":"216363","profile_image_url":"http://a1.twimg.com/profile_images/72454310/Tim-Avatar_normal.png","created_at":"Wed, 26 Jan 2011 04:15:30 +0000","from_user":"dysinger","id_str":"30116594684264448","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell in Hawaii tonight for me... #fun","id":30116594684264448,"from_user_id":216363,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.nambu.com/" rel="nofollow">Nambu</a>"},{"from_user_id_str":"1774820","profile_image_url":"http://a2.twimg.com/profile_images/61169291/dan_desert_thumb_normal.jpg","created_at":"Wed, 26 Jan 2011 04:13:36 +0000","from_user":"DanMil","id_str":"30116117682851840","metadata":{"result_type":"recent"},"to_user_id":1594784,"text":"@ojrac @chewedwire @tomheon Haskell isn't a language, it's a belief system. A seductive one...","id":30116117682851840,"from_user_id":1774820,"to_user":"ojrac","geo":null,"iso_language_code":"en","to_user_id_str":"1594784","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"659256","profile_image_url":"http://a0.twimg.com/profile_images/746976711/angular-final_normal.jpg","created_at":"Wed, 26 Jan 2011 04:11:06 +0000","from_user":"djspiewak","id_str":"30115488931520512","metadata":{"result_type":"recent"},"to_user_id":null,"text":"One of the very nice things about Haskell as opposed to SML is the reduced proliferation of identifiers (e.g. andb, orb, etc). #typeclasses","id":30115488931520512,"from_user_id":659256,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Wed, 26 Jan 2011 04:06:12 +0000","from_user":"listwarenet","id_str":"30114255890026496","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-cafe/84752-re-haskell-cafe-gpl-license-of-h-matrix-and-prelude-numeric.html Re: Haskell-c","id":30114255890026496,"from_user_id":144546280,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"},{"from_user_id_str":"1594784","profile_image_url":"http://a2.twimg.com/profile_images/378515773/square-profile_normal.jpg","created_at":"Wed, 26 Jan 2011 04:01:29 +0000","from_user":"ojrac","id_str":"30113067333324800","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @tomheon: @ojrac @chewedwire Don't worry, learning Haskell will not give you any clear idea what monad means.","id":30113067333324800,"from_user_id":1594784,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"207589736","profile_image_url":"http://a3.twimg.com/profile_images/1225527428/headshot_1_normal.jpg","created_at":"Wed, 26 Jan 2011 04:00:13 +0000","from_user":"ashleevelazq101","id_str":"30112747555397632","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Federal investigation finds safety violations at The Acadia Hospital: By Meg Haskell, BDN Staff The investigatio... http://bit.ly/dONnpn","id":30112747555397632,"from_user_id":207589736,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"17671137","profile_image_url":"http://a2.twimg.com/profile_images/290264834/Haskell-logo-outer-glow_normal.png","created_at":"Wed, 26 Jan 2011 03:58:00 +0000","from_user":"Hackage","id_str":"30112192346984448","metadata":{"result_type":"recent"},"to_user_id":null,"text":"streams 0.4, added by EdwardKmett: Various Haskell 2010 stream comonads http://bit.ly/idBkPe","id":30112192346984448,"from_user_id":17671137,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"17489366","profile_image_url":"http://a3.twimg.com/sticky/default_profile_images/default_profile_2_normal.png","created_at":"Wed, 26 Jan 2011 03:58:00 +0000","from_user":"aapnoot","id_str":"30112191881420800","metadata":{"result_type":"recent"},"to_user_id":null,"text":"streams 0.4, added by EdwardKmett: Various Haskell 2010 stream comonads http://bit.ly/idBkPe","id":30112191881420800,"from_user_id":17489366,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"8530482","profile_image_url":"http://a2.twimg.com/profile_images/137867266/n608671563_7396_normal.jpg","created_at":"Wed, 26 Jan 2011 03:50:12 +0000","from_user":"jeffmclamb","id_str":"30110229207187456","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Angel - daemon to run and monitor processes like daemontools or god, written in Haskell http://ff.im/-wNyLk","id":30110229207187456,"from_user_id":8530482,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://friendfeed.com" rel="nofollow">FriendFeed</a>"},{"from_user_id_str":"177539201","profile_image_url":"http://a0.twimg.com/profile_images/1178368800/img_normal.jpeg","created_at":"Wed, 26 Jan 2011 03:46:01 +0000","from_user":"tomheon","id_str":"30109174645919744","metadata":{"result_type":"recent"},"to_user_id":1594784,"text":"@ojrac @chewedwire Don't worry, learning Haskell will not give you any clear idea what monad means.","id":30109174645919744,"from_user_id":177539201,"to_user":"ojrac","geo":null,"iso_language_code":"en","to_user_id_str":"1594784","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"1594784","profile_image_url":"http://a2.twimg.com/profile_images/378515773/square-profile_normal.jpg","created_at":"Wed, 26 Jan 2011 03:44:34 +0000","from_user":"ojrac","id_str":"30108808684503040","metadata":{"result_type":"recent"},"to_user_id":128028225,"text":"@chewedwire @tomheon Why are you making me curious about Haskell? I LIKE not knowing what monad means!!","id":30108808684503040,"from_user_id":1594784,"to_user":"chewedwire","geo":null,"iso_language_code":"en","to_user_id_str":"128028225","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"23750094","profile_image_url":"http://a0.twimg.com/profile_images/951373780/Moeinthecar_normal.jpg","created_at":"Wed, 26 Jan 2011 03:41:54 +0000","from_user":"shokalshab","id_str":"30108140443795456","metadata":{"result_type":"recent"},"to_user_id":null,"text":"I'm at Magnitude Cheer @ Gymnastics Olympica USA (7735 Haskell Ave., btw Saticoy & Strathern, Van Nuys) http://4sq.com/gmXfaL","id":30108140443795456,"from_user_id":23750094,"geo":null,"iso_language_code":"en","place":{"id":"4e4a2a2f86cb2946","type_":"poi","full_name":"Gymnastics Olympica USA, Van Nuys"},"to_user_id_str":null,"source":"<a href="http://foursquare.com" rel="nofollow">foursquare</a>"},{"from_user_id_str":"8135112","profile_image_url":"http://a0.twimg.com/profile_images/1165240350/LIMITED_normal.jpg","created_at":"Wed, 26 Jan 2011 03:41:35 +0000","from_user":"Claricei","id_str":"30108059208515584","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @kristenmchugh22: @KeithOlbermann Ryan looks like Jughead w/o the hat. And sounds as mealy-mouthed as Eddie Haskell.","id":30108059208515584,"from_user_id":8135112,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"128028225","profile_image_url":"http://a1.twimg.com/profile_images/1224994593/Coding_Drunk_normal.jpg","created_at":"Wed, 26 Jan 2011 03:40:02 +0000","from_user":"chewedwire","id_str":"30107670367182848","metadata":{"result_type":"recent"},"to_user_id":177539201,"text":"@tomheon Cool, I'll take a look. I feel like I should mention this: http://bit.ly/hVstDM","id":30107670367182848,"from_user_id":128028225,"to_user":"tomheon","geo":null,"iso_language_code":"en","to_user_id_str":"177539201","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"8679778","profile_image_url":"http://a3.twimg.com/profile_images/1195318056/me_nyc_12_18_10_icon_normal.jpg","created_at":"Wed, 26 Jan 2011 03:38:42 +0000","from_user":"kristenmchugh22","id_str":"30107332381777920","metadata":{"result_type":"recent"},"to_user_id":756269,"text":"@KeithOlbermann Ryan looks like Jughead w/o the hat. And sounds as mealy-mouthed as Eddie Haskell.","id":30107332381777920,"from_user_id":8679778,"to_user":"KeithOlbermann","geo":null,"iso_language_code":"en","to_user_id_str":"756269","source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"103316559","profile_image_url":"http://a1.twimg.com/profile_images/1179458751/bc3beab4-d59d-4e78-b13b-50747986cfa2_normal.png","created_at":"Wed, 26 Jan 2011 03:36:15 +0000","from_user":"cityslikr","id_str":"30106719153557504","metadata":{"result_type":"recent"},"to_user_id":null,"text":""Social safety net into a hammock." So says Eddie Haskell with the GOP response. #SOTU","id":30106719153557504,"from_user_id":103316559,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://blackberry.com/twitter" rel="nofollow">Twitter for BlackBerry\u00ae</a>"},{"from_user_id_str":"169063143","profile_image_url":"http://a0.twimg.com/profile_images/1160506212/9697_1_normal.gif","created_at":"Wed, 26 Jan 2011 03:31:52 +0000","from_user":"wrkforce_safety","id_str":"30105614919143424","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Federal investigation finds safety violations at The Acadia Hospital: By Meg Haskell, BDN Staff The investigatio... http://bit.ly/gA60C1","id":30105614919143424,"from_user_id":169063143,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"177539201","profile_image_url":"http://a0.twimg.com/profile_images/1178368800/img_normal.jpeg","created_at":"Wed, 26 Jan 2011 03:29:40 +0000","from_user":"tomheon","id_str":"30105060960632832","metadata":{"result_type":"recent"},"to_user_id":128028225,"text":"@chewedwire Great book on Haskell: http://oreilly.com/catalog/9780596514983","id":30105060960632832,"from_user_id":177539201,"to_user":"chewedwire","geo":null,"iso_language_code":"en","to_user_id_str":"128028225","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"782692","profile_image_url":"http://a0.twimg.com/profile_images/1031304589/Profile.2007.1_normal.jpg","created_at":"Wed, 26 Jan 2011 03:29:19 +0000","from_user":"turnageb","id_str":"30104974591533057","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @ovillalon: Paul Ryan solves the mystery of whatever happened to Eddie Haskell. #sotu","id":30104974591533057,"from_user_id":782692,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"128028225","profile_image_url":"http://a1.twimg.com/profile_images/1224994593/Coding_Drunk_normal.jpg","created_at":"Wed, 26 Jan 2011 03:28:04 +0000","from_user":"chewedwire","id_str":"30104657267265536","metadata":{"result_type":"recent"},"to_user_id":177539201,"text":"@tomheon I always loved the pattern matching in SML and it looks like Haskell is MUCH better at it. I'm messing around now at tryhaskell.org","id":30104657267265536,"from_user_id":128028225,"to_user":"tomheon","geo":null,"iso_language_code":"en","to_user_id_str":"177539201","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"12834082","profile_image_url":"http://a3.twimg.com/profile_images/1083036140/mugshot_normal.png","created_at":"Wed, 26 Jan 2011 03:28:01 +0000","from_user":"ovillalon","id_str":"30104647213518848","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Paul Ryan solves the mystery of whatever happened to Eddie Haskell. #sotu","id":30104647213518848,"from_user_id":12834082,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"13540930","profile_image_url":"http://a1.twimg.com/profile_images/1205312219/23467_350321383101_821143101_5114147_3010041_n_normal.jpg","created_at":"Wed, 26 Jan 2011 03:26:02 +0000","from_user":"goodfox","id_str":"30104146455560192","metadata":{"result_type":"recent"},"to_user_id":10226179,"text":"@billykeene22 Bordeaux is one of my heroes. I was so excited when he accepted the invitation to campus. He's been a great friend to Haskell.","id":30104146455560192,"from_user_id":13540930,"to_user":"billykeene22","geo":null,"iso_language_code":"en","to_user_id_str":"10226179","source":"<a href="http://www.ubertwitter.com/bb/download.php" rel="nofollow">\u00dcberTwitter</a>"},{"from_user_id_str":"18616016","profile_image_url":"http://a2.twimg.com/profile_images/1173522726/214397343_normal.jpg","created_at":"Wed, 26 Jan 2011 03:25:18 +0000","from_user":"josej30","id_str":"30103962313031681","metadata":{"result_type":"recent"},"to_user_id":14870909,"text":"@cris7ian Ahh bueno multiparadigma ya es respetable :) Empezar\u00e9 a explotar la parte funcional de los lenguajes ahora #Haskell","id":30103962313031681,"from_user_id":18616016,"to_user":"Cris7ian","geo":null,"iso_language_code":"es","to_user_id_str":"14870909","source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"14870909","profile_image_url":"http://a2.twimg.com/profile_images/1176930429/oso_yo_normal.png","created_at":"Wed, 26 Jan 2011 03:23:43 +0000","from_user":"Cris7ian","id_str":"30103562360983553","metadata":{"result_type":"recent"},"to_user_id":18616016,"text":"@josej30 hahaha no, es multiparadigma y es bastante lazy. Nothing like haskell, pero s\u00ed, el de Flash","id":30103562360983553,"from_user_id":14870909,"to_user":"josej30","geo":null,"iso_language_code":"es","to_user_id_str":"18616016","source":"<a href="http://www.echofon.com/" rel="nofollow">Echofon</a>"},{"from_user_id_str":"2421643","profile_image_url":"http://a0.twimg.com/profile_images/1190361665/ernestgrumbles-17_normal.jpg","created_at":"Wed, 26 Jan 2011 03:20:24 +0000","from_user":"ernestgrumbles","id_str":"30102730756333568","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Wow... WolframAlpha did not know who Eddie Haskell is. Guess I'll never use that "knowledge engine" again.","id":30102730756333568,"from_user_id":2421643,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"128028225","profile_image_url":"http://a1.twimg.com/profile_images/1224994593/Coding_Drunk_normal.jpg","created_at":"Wed, 26 Jan 2011 03:14:21 +0000","from_user":"chewedwire","id_str":"30101204428132352","metadata":{"result_type":"recent"},"to_user_id":177539201,"text":"@tomheon How is Haskell better/different from CL or Scheme? I honestly don't know, although I'm becoming more curious.","id":30101204428132352,"from_user_id":128028225,"to_user":"tomheon","geo":null,"iso_language_code":"en","to_user_id_str":"177539201","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"13540930","profile_image_url":"http://a1.twimg.com/profile_images/1205312219/23467_350321383101_821143101_5114147_3010041_n_normal.jpg","created_at":"Wed, 26 Jan 2011 03:06:54 +0000","from_user":"goodfox","id_str":"30099329809129473","metadata":{"result_type":"recent"},"to_user_id":null,"text":"A day of vision & speeches. #SOTU now. And a wonderful Haskell Convocation address earlier today by Sinte Gleske President Lionel Bordeaux.","id":30099329809129473,"from_user_id":13540930,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.ubertwitter.com/bb/download.php" rel="nofollow">\u00dcberTwitter</a>"},{"from_user_id_str":"119185220","profile_image_url":"http://a0.twimg.com/profile_images/1089027228/dfg_normal.jpg","created_at":"Wed, 26 Jan 2011 03:03:38 +0000","from_user":"LaLiciouz_03","id_str":"30098510623805440","metadata":{"result_type":"recent"},"to_user_id":null,"text":"The Game with the girl room 330 Haskell follow us...","id":30098510623805440,"from_user_id":119185220,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"18616016","profile_image_url":"http://a2.twimg.com/profile_images/1173522726/214397343_normal.jpg","created_at":"Wed, 26 Jan 2011 02:57:25 +0000","from_user":"josej30","id_str":"30096946144215040","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Voy a extra\u00f1ar Haskell cuando regrese al mundo imperativo. Hay alg\u00fan lenguaje imperativo que tenga este poder funcional? #ci3661","id":30096946144215040,"from_user_id":18616016,"geo":null,"iso_language_code":"es","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"17671137","profile_image_url":"http://a2.twimg.com/profile_images/290264834/Haskell-logo-outer-glow_normal.png","created_at":"Wed, 26 Jan 2011 02:55:32 +0000","from_user":"Hackage","id_str":"30096471814574080","metadata":{"result_type":"recent"},"to_user_id":null,"text":"comonad-transformers 0.9.0, added by EdwardKmett: Haskell 98 comonad transformers http://bit.ly/h6xIsf","id":30096471814574080,"from_user_id":17671137,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://twitterfeed.com" rel="nofollow">twitterfeed</a>"},{"from_user_id_str":"177539201","profile_image_url":"http://a0.twimg.com/profile_images/1178368800/img_normal.jpeg","created_at":"Wed, 26 Jan 2011 02:48:12 +0000","from_user":"tomheon","id_str":"30094626920603649","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Every time I look at Haskell I love it more.","id":30094626920603649,"from_user_id":177539201,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"60792568","profile_image_url":"http://a0.twimg.com/profile_images/1203647517/glenda-flash_normal.jpg","created_at":"Wed, 26 Jan 2011 02:40:42 +0000","from_user":"r_takaishi","id_str":"30092735935422464","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell\u3088\u308aD\u8a00\u8a9e\u304c\u4e0a\u3068\u306f\u601d\u308f\u306a\u304b\u3063\u305f\uff0e http://www.tiobe.com/index.php/content/paperinfo/tpci/index.html","id":30092735935422464,"from_user_id":60792568,"geo":null,"iso_language_code":"ja","to_user_id_str":null,"source":"<a href="http://twmode.sf.net/" rel="nofollow">twmode</a>"},{"from_user_id_str":"160145510","profile_image_url":"http://a0.twimg.com/profile_images/1218108166/going_galt_normal.jpg","created_at":"Wed, 26 Jan 2011 02:39:31 +0000","from_user":"wtp1787","id_str":"30092439653974018","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @KLSouth: Eddie Haskell Goes to Washington... "You look really nice tonight, Ms Cleaver"","id":30092439653974018,"from_user_id":160145510,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"96616016","profile_image_url":"http://a1.twimg.com/profile_images/1196978169/Picture0002_normal.jpg","created_at":"Wed, 26 Jan 2011 02:39:20 +0000","from_user":"MelissaRNMBA","id_str":"30092392203816960","metadata":{"result_type":"recent"},"to_user_id":14862975,"text":"@KLSouth At least Eddie Haskell was entertaining.","id":30092392203816960,"from_user_id":96616016,"to_user":"KLSouth","geo":null,"iso_language_code":"en","to_user_id_str":"14862975","source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"14862975","profile_image_url":"http://a0.twimg.com/profile_images/421596393/kls_4_normal.JPG","created_at":"Wed, 26 Jan 2011 02:38:29 +0000","from_user":"KLSouth","id_str":"30092178327871489","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Eddie Haskell Goes to Washington... "You look really nice tonight, Ms Cleaver"","id":30092178327871489,"from_user_id":14862975,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.tweetdeck.com" rel="nofollow">TweetDeck</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Wed, 26 Jan 2011 02:36:17 +0000","from_user":"listwarenet","id_str":"30091626869161984","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-beginners/84641-haskell-beginners-wildcards-in-expressions.html Haskell-beginners - Wild","id":30091626869161984,"from_user_id":144546280,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"},{"from_user_id_str":"24538048","profile_image_url":"http://a2.twimg.com/profile_images/1117267605/rope_normal.jpg","created_at":"Wed, 26 Jan 2011 02:23:14 +0000","from_user":"dbph","id_str":"30088341030440960","metadata":{"result_type":"recent"},"to_user_id":null,"text":"RT @dnene: Skilled Calisthenics. Haskell code that outputs python which spits ruby which emits the haskell source. http://j.mp/YlQUL via @mfeathers","id":30088341030440960,"from_user_id":24538048,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"},{"from_user_id_str":"158951567","profile_image_url":"http://a3.twimg.com/profile_images/962721419/Logo_3_normal.jpg","created_at":"Wed, 26 Jan 2011 01:58:31 +0000","from_user":"YubaVetTech","id_str":"30082124207886336","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Dr. Haskell has just been awarded the prestigious Hayward Award for \u2018Excellence in Education\u2019. This award honors... http://fb.me/QgQCxd74","id":30082124207886336,"from_user_id":158951567,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.facebook.com/twitter" rel="nofollow">Facebook</a>"},{"from_user_id_str":"158951567","profile_image_url":"http://a3.twimg.com/profile_images/962721419/Logo_3_normal.jpg","created_at":"Wed, 26 Jan 2011 01:56:04 +0000","from_user":"YubaVetTech","id_str":"30081505476743168","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Dr. Haskell has just been awarded the prestigous Haward Award for Excellence in Education. This award honors... http://fb.me/PC9mYmCR","id":30081505476743168,"from_user_id":158951567,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://www.facebook.com/twitter" rel="nofollow">Facebook</a>"},{"from_user_id_str":"2331498","profile_image_url":"http://a3.twimg.com/profile_images/494632120/me_normal.jpg","created_at":"Wed, 26 Jan 2011 01:43:50 +0000","from_user":"Verus","id_str":"30078427155406848","metadata":{"result_type":"recent"},"to_user_id":79273052,"text":"@kami_joe \u3044\u3084\uff0c\u8ab2\u984c\u306f\u89e3\u6c7a\u5bfe\u8c61(\u30d1\u30ba\u30eb\u3068\u304b)\u3092\u4e0e\u3048\u3089\u308c\u3066\uff0c\u554f\u984c\u5b9a\u7fa9\u3068\u30d7\u30ed\u30b0\u30e9\u30df\u30f3\u30b0(\u6307\u5b9a\u8a00\u8a9e\u306fC++\u3082\u3057\u304f\u306fJava)\u3068\u3044\u3046\u3044\u308f\u3070\u666e\u901a\u306a\u8ab2\u984c\u3067\u306f\u3042\u308b\u3093\u3060\u3051\u3069\uff0e\u95a2\u6570\u578b\u8a00\u8a9e\u306fHaskell\u306e\u6388\u696d\u304c\u307e\u305f\u5225\u306b\u3042\u308b\u306e\uff0e","id":30078427155406848,"from_user_id":2331498,"to_user":"kami_joe","geo":null,"iso_language_code":"ja","to_user_id_str":"79273052","source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"79151233","profile_image_url":"http://a2.twimg.com/a/1295051201/images/default_profile_2_normal.png","created_at":"Wed, 26 Jan 2011 01:40:37 +0000","from_user":"cz_newdrafts","id_str":"30077617361125376","metadata":{"result_type":"recent"},"to_user_id":null,"text":"Haskell programming language http://bit.ly/gpPAwB","id":30077617361125376,"from_user_id":79151233,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://tommorris.org/" rel="nofollow">tommorris' hacksample</a>"},{"from_user_id_str":"2331498","profile_image_url":"http://a3.twimg.com/profile_images/494632120/me_normal.jpg","created_at":"Wed, 26 Jan 2011 01:02:57 +0000","from_user":"Verus","id_str":"30068139416879104","metadata":{"result_type":"recent"},"to_user_id":9252720,"text":"@shukukei Java\u3068C\u306f\u3042\u308b\u7a0b\u5ea6\u66f8\u3051\u3066\u3042\u305f\u308a\u307e\u3048\u306a\u3068\u3053\u308d\u304c\u3042\u308b\u304b\u3089\u306a\u30fc\uff0ePython\u306f\u500b\u4eba\u7684\u306b\u611f\u899a\u304c\u5408\u308f\u306a\u3044\uff0e\u611f\u899a\u306a\u306e\u3067\uff0c\u3082\u3046\u3069\u3046\u3057\u3088\u3046\u3082\u306a\u3044\uff57 \u3044\u307e\u306fScala\u3068Haskell\u3092\u3082\u3063\u3068\u6975\u3081\u305f\u3044\u3068\u3053\u308d\uff0e","id":30068139416879104,"from_user_id":2331498,"to_user":"shukukei","geo":null,"iso_language_code":"ja","to_user_id_str":"9252720","source":"<a href="http://itunes.apple.com/us/app/twitter/id409789998?mt=12" rel="nofollow">Twitter for Mac</a>"},{"from_user_id_str":"2781460","profile_image_url":"http://a0.twimg.com/profile_images/82526625/.joeyicon_normal.jpg","created_at":"Wed, 26 Jan 2011 01:02:35 +0000","from_user":"joeyhess","id_str":"30068046538219520","metadata":{"result_type":"recent"},"to_user_id":null,"text":"just figured out that I can use parameterized types to remove a dependency loop in git-annex's type definitions. whee #haskell","id":30068046538219520,"from_user_id":2781460,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://identi.ca" rel="nofollow">identica</a>"},{"from_user_id_str":"144546280","profile_image_url":"http://a1.twimg.com/a/1295051201/images/default_profile_1_normal.png","created_at":"Wed, 26 Jan 2011 00:54:22 +0000","from_user":"listwarenet","id_str":"30065977920061440","metadata":{"result_type":"recent"},"to_user_id":null,"text":"http://www.listware.net/201101/haskell-beginners/84466-haskell-beginners-bytestring-question.html Haskell-beginners - Bytestrin","id":30065977920061440,"from_user_id":144546280,"geo":null,"iso_language_code":"no","to_user_id_str":null,"source":"<a href="http://1e10.org/cloud/" rel="nofollow">1e10</a>"},{"from_user_id_str":"1291845","profile_image_url":"http://a0.twimg.com/profile_images/1225743404/ThinOxygen-small-opaque-solidarity_normal.png","created_at":"Wed, 26 Jan 2011 00:52:07 +0000","from_user":"_aaron_","id_str":"30065412242669568","metadata":{"result_type":"recent"},"to_user_id":null,"text":"wanted: librly licensed high level native compiled lang with min runtime (otherwise cobra/mono would be perfect) for win. lua? haskell? ooc?","id":30065412242669568,"from_user_id":1291845,"geo":null,"iso_language_code":"en","to_user_id_str":null,"source":"<a href="http://twitter.com/">web</a>"}],"max_id":30120402839666689,"since_id":0,"refresh_url":"?since_id=30120402839666689&q=haskell","next_page":"?page=2&max_id=30120402839666689&rpp=50&q=haskell","results_per_page":50,"page":1,"completed_in":0.291696,"since_id_str":"0","max_id_str":"30120402839666689","query":"haskell"} aeson-1.4.2.0/benchmarks/parse.py0000755000000000000000000000074500000000000014722 0ustar0000000000000000#!/usr/bin/env python import json, sys, time def isint(x): try: int(x) return True except: return False if len(sys.argv) > 2 and isint(sys.argv[1]) and isint(sys.argv[2]): sys.argv.pop(1) count = int(sys.argv[1]) for n in sys.argv[2:]: print '%s:' % n start = time.time() fp = open(n) for i in xrange(count): fp.seek(0) val = json.load(fp) end = time.time() print ' %d good, %gs' % (count, end - start) aeson-1.4.2.0/cbits/0000755000000000000000000000000000000000000012214 5ustar0000000000000000aeson-1.4.2.0/cbits/unescape_string.c0000644000000000000000000001116000000000000015550 0ustar0000000000000000// Copyright (c) 2008-2009 Bjoern Hoehrmann // Copyright (c) 2015, Ondrej Palkovsky // Copyright (c) 2016, Winterland #include #include #include #define UTF8_ACCEPT 0 #define UTF8_REJECT 12 static const uint8_t utf8d[] = { // The first part of the table maps bytes to character classes that // to reduce the size of the transition table and create bitmasks. 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1, 9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9, 7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7, 7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7, 8,8,2,2,2,2,2,2,2,2,2,2,2,2,2,2, 2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2, 10,3,3,3,3,3,3,3,3,3,3,3,3,4,3,3, 11,6,6,6,5,8,8,8,8,8,8,8,8,8,8,8, // The second part is a transition table that maps a combination // of a state of the automaton and a character class to a state. 0,12,24,36,60,96,84,12,12,12,48,72, 12,12,12,12,12,12,12,12,12,12,12,12, 12, 0,12,12,12,12,12, 0,12, 0,12,12, 12,24,12,12,12,12,12,24,12,24,12,12, 12,12,12,12,12,12,12,24,12,12,12,12, 12,24,12,12,12,12,12,12,12,24,12,12, 12,12,12,12,12,12,12,36,12,36,12,12, 12,36,12,12,12,12,12,36,12,36,12,12, 12,36,12,12,12,12,12,12,12,12,12,12, }; static inline uint32_t decode(uint32_t* state, uint32_t* codep, uint32_t byte) { uint32_t type = utf8d[byte]; *codep = (*state != UTF8_ACCEPT) ? (byte & 0x3fu) | (*codep << 6) : (0xff >> type) & (byte); *state = utf8d[256 + *state + type]; return *state; } static inline uint16_t decode_hex(uint32_t c) { if (c >= '0' && c <= '9') return c - '0'; else if (c >= 'a' && c <= 'f') return c - 'a' + 10; else if (c >= 'A' && c <= 'F') return c - 'A' + 10; return 0xFFFF; // Should not happen } // Decode, return non-zero value on error int _js_decode_string(uint16_t *const dest, size_t *destoff, const uint8_t *s, const uint8_t *const srcend) { uint16_t *d = dest + *destoff; uint32_t state = 0; uint32_t codepoint; uint8_t surrogate = 0; uint16_t temp_hex = 0; uint16_t unidata; // Optimized version of dispatch when just an ASCII char is expected #define DISPATCH_ASCII(label) {\ if (s >= srcend) {\ return -1;\ }\ codepoint = *s++;\ goto label;\ } standard: // Test end of stream while (s < srcend) { if (decode(&state, &codepoint, *s++) != UTF8_ACCEPT) { if (state == UTF8_REJECT) { return -1; } continue; } if (codepoint == '\\') DISPATCH_ASCII(backslash) else if (codepoint <= 0xffff) *d++ = (uint16_t) codepoint; else { *d++ = (uint16_t) (0xD7C0 + (codepoint >> 10)); *d++ = (uint16_t) (0xDC00 + (codepoint & 0x3FF)); } } *destoff = d - dest; // Exit point return (state != UTF8_ACCEPT); backslash: switch (codepoint) { case '"': case '\\': case '/': *d++ = (uint16_t) codepoint; goto standard; break; case 'b': *d++ = '\b';goto standard; case 'f': *d++ = '\f';goto standard; case 'n': *d++ = '\n';goto standard; case 'r': *d++ = '\r';goto standard; case 't': *d++ = '\t';goto standard; case 'u': DISPATCH_ASCII(unicode1);;break; default: return -1; } unicode1: temp_hex = decode_hex(codepoint); if (temp_hex == 0xFFFF) { return -1; } else unidata = temp_hex << 12; DISPATCH_ASCII(unicode2); unicode2: temp_hex = decode_hex(codepoint); if (temp_hex == 0xFFFF) { return -1; } else unidata |= temp_hex << 8; DISPATCH_ASCII(unicode3); unicode3: temp_hex = decode_hex(codepoint); if (temp_hex == 0xFFFF) { return -1; } else unidata |= temp_hex << 4; DISPATCH_ASCII(unicode4); unicode4: temp_hex = decode_hex(codepoint); if (temp_hex == 0xFFFF) { return -1; } else unidata |= temp_hex; *d++ = (uint16_t) unidata; if (surrogate) { if (unidata < 0xDC00 || unidata > 0xDFFF) // is not low surrogate return -1; surrogate = 0; } else if (unidata >= 0xD800 && unidata <= 0xDBFF ) { // is high surrogate surrogate = 1; DISPATCH_ASCII(surrogate1); } else if (unidata >= 0xDC00 && unidata <= 0xDFFF) { // is low surrogate return -1; } goto standard; surrogate1: if (codepoint != '\\') { return -1; } DISPATCH_ASCII(surrogate2) surrogate2: if (codepoint != 'u') { return -1; } DISPATCH_ASCII(unicode1) } aeson-1.4.2.0/cbits/unescape_string.c0000755000000000000000000001116000000000000015553 0ustar0000000000000000// Copyright (c) 2008-2009 Bjoern Hoehrmann // Copyright (c) 2015, Ondrej Palkovsky // Copyright (c) 2016, Winterland #include #include #include #define UTF8_ACCEPT 0 #define UTF8_REJECT 12 static const uint8_t utf8d[] = { // The first part of the table maps bytes to character classes that // to reduce the size of the transition table and create bitmasks. 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1, 9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9, 7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7, 7,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7, 8,8,2,2,2,2,2,2,2,2,2,2,2,2,2,2, 2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2, 10,3,3,3,3,3,3,3,3,3,3,3,3,4,3,3, 11,6,6,6,5,8,8,8,8,8,8,8,8,8,8,8, // The second part is a transition table that maps a combination // of a state of the automaton and a character class to a state. 0,12,24,36,60,96,84,12,12,12,48,72, 12,12,12,12,12,12,12,12,12,12,12,12, 12, 0,12,12,12,12,12, 0,12, 0,12,12, 12,24,12,12,12,12,12,24,12,24,12,12, 12,12,12,12,12,12,12,24,12,12,12,12, 12,24,12,12,12,12,12,12,12,24,12,12, 12,12,12,12,12,12,12,36,12,36,12,12, 12,36,12,12,12,12,12,36,12,36,12,12, 12,36,12,12,12,12,12,12,12,12,12,12, }; static inline uint32_t decode(uint32_t* state, uint32_t* codep, uint32_t byte) { uint32_t type = utf8d[byte]; *codep = (*state != UTF8_ACCEPT) ? (byte & 0x3fu) | (*codep << 6) : (0xff >> type) & (byte); *state = utf8d[256 + *state + type]; return *state; } static inline uint16_t decode_hex(uint32_t c) { if (c >= '0' && c <= '9') return c - '0'; else if (c >= 'a' && c <= 'f') return c - 'a' + 10; else if (c >= 'A' && c <= 'F') return c - 'A' + 10; return 0xFFFF; // Should not happen } // Decode, return non-zero value on error int _js_decode_string(uint16_t *const dest, size_t *destoff, const uint8_t *s, const uint8_t *const srcend) { uint16_t *d = dest + *destoff; uint32_t state = 0; uint32_t codepoint; uint8_t surrogate = 0; uint16_t temp_hex = 0; uint16_t unidata; // Optimized version of dispatch when just an ASCII char is expected #define DISPATCH_ASCII(label) {\ if (s >= srcend) {\ return -1;\ }\ codepoint = *s++;\ goto label;\ } standard: // Test end of stream while (s < srcend) { if (decode(&state, &codepoint, *s++) != UTF8_ACCEPT) { if (state == UTF8_REJECT) { return -1; } continue; } if (codepoint == '\\') DISPATCH_ASCII(backslash) else if (codepoint <= 0xffff) *d++ = (uint16_t) codepoint; else { *d++ = (uint16_t) (0xD7C0 + (codepoint >> 10)); *d++ = (uint16_t) (0xDC00 + (codepoint & 0x3FF)); } } *destoff = d - dest; // Exit point return (state != UTF8_ACCEPT); backslash: switch (codepoint) { case '"': case '\\': case '/': *d++ = (uint16_t) codepoint; goto standard; break; case 'b': *d++ = '\b';goto standard; case 'f': *d++ = '\f';goto standard; case 'n': *d++ = '\n';goto standard; case 'r': *d++ = '\r';goto standard; case 't': *d++ = '\t';goto standard; case 'u': DISPATCH_ASCII(unicode1);;break; default: return -1; } unicode1: temp_hex = decode_hex(codepoint); if (temp_hex == 0xFFFF) { return -1; } else unidata = temp_hex << 12; DISPATCH_ASCII(unicode2); unicode2: temp_hex = decode_hex(codepoint); if (temp_hex == 0xFFFF) { return -1; } else unidata |= temp_hex << 8; DISPATCH_ASCII(unicode3); unicode3: temp_hex = decode_hex(codepoint); if (temp_hex == 0xFFFF) { return -1; } else unidata |= temp_hex << 4; DISPATCH_ASCII(unicode4); unicode4: temp_hex = decode_hex(codepoint); if (temp_hex == 0xFFFF) { return -1; } else unidata |= temp_hex; *d++ = (uint16_t) unidata; if (surrogate) { if (unidata < 0xDC00 || unidata > 0xDFFF) // is not low surrogate return -1; surrogate = 0; } else if (unidata >= 0xD800 && unidata <= 0xDBFF ) { // is high surrogate surrogate = 1; DISPATCH_ASCII(surrogate1); } else if (unidata >= 0xDC00 && unidata <= 0xDFFF) { // is low surrogate return -1; } goto standard; surrogate1: if (codepoint != '\\') { return -1; } DISPATCH_ASCII(surrogate2) surrogate2: if (codepoint != 'u') { return -1; } DISPATCH_ASCII(unicode1) } aeson-1.4.2.0/changelog.md0000755000000000000000000005541000000000000013371 0ustar0000000000000000For the latest version of this document, please see [https://github.com/bos/aeson/blob/master/changelog.md](https://github.com/bos/aeson/blob/master/changelog.md). ### 1.4.2.0 * Add `Data.Aeson.QQ.Simple` which is a simpler version of the `aeson-qq` package, it does not support interpolation, thanks to Oleg Grenrus. * Add `Contravariant ToJSONKeyFunction` instance, thanks to Oleg Grenrus. * Add `KeyValue Object` instance, thanks to Robert Hensing * Improved performance when parsing large numbers, thanks to Oleg Grenrus. ### 1.4.1.0 * Optimizations of generics, thanks to Rémy Oudompheng, here are some numbers for GHC 8.4: * Compilation time: G/BigProduct.hs is 25% faster, G/BigRecord.hs is 2x faster. * Runtime performance: BigRecord/toJSON/generic and BigProduct/encode/generic are more than 2x faster. * Added To/FromJSON instances for `Void` and Generics's `V1`, thanks to Will Yager * Added To/FromJSON instances for `primitive`'s `Array`, `SmallArray`, `PrimArray` and `UnliftedArray`, thanks to Andrew Thad. * Fixes handling of `UTCTime` wrt. leap seconds , thanks to Adam Schønemann * Warning and documentation fixes thanks to tom-bop, Gabor Greif, Ian Jeffries, and Mateusz Curyło. ## 1.4.0.0 This release introduces bounds on the size of `Scientific` numbers when they are converted to other arbitrary precision types that do not represent them efficiently in memory. This means that trying to decode a number such as `1e1000000000` into an `Integer` will now fail instead of using a lot of memory. If you need to represent large numbers you can add a newtype (preferably over `Scientific`) and providing a parser using `withScientific`. The following instances are affected by this: * `FromJSON Natural` * `FromJSONKey Natural` * `FromJSON Integer` * `FromJSONKey Integer` * `FromJSON NominalDiffTime` For the same reasons the following instances & functions have been removed: * Remove `FromJSON Data.Attoparsec.Number` instance. Note that `Data.Attoparsec.Number` is deprecated. * Remove deprecated `withNumber`, use `withScientific` instead. Finally, encoding integral values with large exponents now uses scientific notation, this saves space for large numbers. #### 1.3.1.1 * Catch 0 denominators when parsing Ratio ### 1.3.1.0 * Fix bug in generically derived `FromJSON` instances that are using `unwrapUnaryRecords`, thanks to Xia Li-yao * Allow base-compat 0.10.*, thanks to Oleg Grenrus ## 1.3.0.0 Breaking changes: * `GKeyValue` has been renamed to `KeyValuePair`, thanks to Xia Li-yao * Removed unused `FromJSON` constraint in `withEmbeddedJson`, thanks to Tristan Seligmann Other improvements: * Optimizations of TH toEncoding, thanks to Xia Li-yao * Optimizations of hex decoding when using the default/pure unescape implementation, thanks to Xia Li-yao * Improved error message on `Day` parse failures, thanks to Gershom Bazerman * Add `encodeFile` as well as `decodeFile*` variants, thanks to Markus Hauck * Documentation fixes, thanks to Lennart Spitzner * CPP cleanup, thanks to Ryan Scott ### 1.2.4.0 * Add `Ord` instance for `JSONPathElement`, thanks to Simon Hengel. ### 1.2.3.0 * Added `withEmbeddedJSON` to help parse JSON embedded inside a JSON string, thanks to Jesse Kempf. * Memory usage improvements to the default (pure) parser, thanks to Jonathan Paugh. Also thanks to Neil Mitchell & Oleg Grenrus for contributing a benchmark. * `omitNothingFields` now works for the `Option` newtype, thanks to Xia Li-yao. * Some documentation fixes, thanks to Jonathan Paug & Philippe Crama. ### 1.2.2.0 * Add `FromJSON` and `ToJSON` instances for * `DiffTime`, thanks to Víctor López Juan. * `CTime`, thanks to Daniel Díaz. * Fix handling of fractions when parsing Natural, thanks to Yuriy Syrovetskiy. * Change text in error messages for Integral types to make them follow the common pattern, thanks to Yuriy Syrovetskiy. * Add missing `INCOHERENT` pragma for `RecordToPair`, thanks to Xia Li-yao. * Everything related to `Options` is now exported from `Data.Aeson`, thanks to Xia Li-yao. * Optimizations to not escape text in clear cases, thanks to Oleg Grenrus. * Some documentation fixes, thanks to Phil de Joux & Xia Li-yao. ### 1.2.1.0 * Add `parserThrowError` and `parserCatchError` combinators, thanks to Oleg Grenrus. * Add `Generic` instance for `Value`, thanks to Xia Li-yao. * Fix a mistake in the 1.2.0.0 changelog, the `cffi` flag is disabled by default! Thanks to dbaynard. ## 1.2.0.0 * `tagSingleConstructors`, an option to encode single-constructor types as tagged sums was added to `Options`. It is disabled by default for backward compatibility. * The `cffi` flag is now turned off (`False`) by default, this means C FFI code is no longer used by default. You can flip the flag to get C implementation. * The `Options` constructor is no longer exposed to prevent new options from being breaking changes, use `defaultOptions` instead. * The contents of `GToJSON` and `GToEncoding` are no longer exposed. * Some INLINE pragmas were removed to avoid GHC running out of simplifier ticks. ### 1.1.2.0 * Fix an accidental change in the format of `deriveJSON`. Thanks to Xia Li-yao! * Documentation improvements regarding `ToJSON`, `FromJSON`, and `SumEncoding`. Thanks to Xia Li-yao and Lennart Spitzner! ### 1.1.1.0 * Added a pure implementation of the C FFI code, the C FFI code. If you wish to use the pure haskell version set the `cffi` flag to `False`. This should make aeson compile when C isn't available, such as for GHCJS. Thanks to James Parker & Marcin Tolysz! * Using the `fast` flag can no longer cause a test case to fail. As far as we know this didn't affect any users of the library itself. Thanks to Xia Li-yao! ## 1.1.0.0 * Added instances for `UUID`. * The operators for parsing fields now have named aliases: - `.:` => `parseField` - `.:?` => `parseFieldMaybe` - `.:!` => `parseFieldMaybe'` - These functions now also have variants with explicit parser functions: `explicitParseField`, `explicitParseFieldMaybe`, "explicitParseFieldMaybe'` Thanks to Oleg Grenrus. * `ToJSONKey (Identity a)` and `FromJSONKey (Identity a)` no longer require the unnecessary `FromJSON a` constraint. Thanks to Oleg Grenrus. * Added `Data.Aeson.Encoding.pair'` which is a more general version of `Data.Aeson.Encoding.pair`. Thanks to Andrew Martin. * `Day`s BCE are properly encoded and `+` is now a valid prefix for `Day`s CE. Thanks to Matt Parsons. * Some commonly used ToJSON instances are now specialized in order to improve compile time. Thanks to Bartosz Nitka. [JSONTestSuite](https://github.com/nst/JSONTestSuite) cleanups, all motivated by tighter RFC 7159 compliance: * The parser now rejects numbers for which [the integer portion contains a leading zero](https://github.com/bos/aeson/commit/3fb7c155f2255482b1b9566ec5c1eaf9895d630e). * The parser now rejects numbers for which [a decimal point is not followed by at least one digit](https://github.com/bos/aeson/commit/ecfca35a45286dbe2bbaf5f62354be393bc59b66), * The parser now rejects documents that contain [whitespace outside the set {space, newline, carriage return, tab}](https://github.com/bos/aeson/commit/8ef622c2ad8d4a109884e17c2792238a2a320e44). Over 90% of JSONTestSuite tests currently pass. The remainder can be categorised as follows: * The string parser is strict with Unicode compliance where the RFC leaves room for implementation-defined behaviour (tests prefixed with "`i_string_`". (This is necessary because the `text` library cannot accommodate invalid Unicode.) * The parser does not (and will not) support UTF-16, UTF-32, or byte order marks (BOM). * The parser accepts unescaped control characters, even though the RFC states that control characters must be escaped. (This may change at some point, but doesn't seem important.) #### 1.0.2.1 * Fixes a regression where a bunch of valid characters caused an "Invalid UTF8-Stream" error when decoding. Thanks to Vladimir Shabanov who investigated and fixed this. ### 1.0.2.0 * Fixes a regression where it was no longer possible to derive instances for types such as `data T a = T { f1 :: a, f2 :: Maybe a }`. Thanks to Sean Leather for fixing this, and to Ryan Scott for helping out. ### 1.0.1.0 * Decoding performance has been significantly improved (see https://github.com/bos/aeson/pull/452). Thanks to @winterland1989. * Add `ToJSON`/`FromJSON` instances for newtypes from `Data.Semigroup`: `Min`, `Max`, `First`, `Last`, `WrappedMonoid`, `Option`. Thanks to Lennart Spitzner. * Make the documentation for `.:!` more accurate. Thanks to Ian Jeffries. # 1.0.0.0 Major enhancements: * Introduced new `FromJSONKey` and `ToJSONKey` type classes that are used to encode maps without going through HashMap. This also allows arbitrary serialization of keys where a string-like key will encode into an object and other keys will encode into an array of key-value tuples. * Added higher rank classes: `ToJSON1`, `ToJSON2`, `FromJSON1`, and `FromJSON2`. * Added `Data.Aeson.Encoding` with functions to safely write `ToJSON` instances using `toEncoding`. Other enhancements: * A Cabal `fast` flag was added to disable building with optimizations. This drastically speeds up compiling both aeson ***and*** libraries using aeson so it is recommended to enable it during development. With cabal-install you can `cabal install aeson -ffast` and with stack you can add a flag section to your stack.yaml: ``` flags: aeson: fast: true ``` * Added list specific members to `ToJSON` and `FromJSON` classes. In the same way `Read` and `Show` handle lists specifically. This removes need for overlapping instances to handle `String`. * Added a new `sumEncoding` option `UntaggedValue` which prevents objects from being tagged with the constructor name. * JSONPaths are now tracked in instances derived with template-haskell and generics. * Get rid of redundancy of JSONPath error messages in nested records. `eitherDecode "{\"x\":{\"a\": [1,2,true]}}" :: Either String Y` previously yielded `Error in $.x.a[2]: failed to parse field" x: failed to parse field a: expected Int, encountered Boolean` and now yields `Error in $.x.a[2]: expected Int, encountered Boolean"`. Some users might prefer to insert `modifyFailure` themselves to customize error messages, which previously prevented the use of `(.:)`. * Backwards compatibility with `bytestring-0.9` using the `bytestring-builder` compatibility package. * Export `decodeWith`, `decodeStrictWith`, `eitherDecodeWith`, and `eitherDecodeStrictWith` from `Data.Aeson.Parser`. This allows decoding using explicit parsers instead of using `FromJSON` instances. * Un-orphan internal instances to render them in haddocks. Other changes: * Integral `FromJSON` instances now only accept integral values. E.g. parsing `3.14` to `Int` fails instead of succeeding with the value `3`. * Over/underflows are now caught for bounded numeric types. * Remove the `contents` field encoding with `allNullaryToStringTag = False`, giving us `{ "tag" : "c1" }` instead of `{ "tag" : "c1", contents : [] }`. The contents field is optional when parsing so this is only a breaking change for ToJSON instances. * Fix a bug where `genericToEncoding` with `unwrapUnaryRecords = True` would produce an invalid encoding: `"unwrap\":""`. * `ToJSON` instances using `genericToEncoding` and `omitNothingFields` no longer produce invalid JSON. * Added instances for `DList`, `Compose`, `Product`, `Sum`. ### 0.11.2.0 * Enable `PolyKinds` to generalize `Proxy`, `Tagged`, and `Const` instances. * Add `unsafeToEncoding` in `Data.Aeson.Types`, use with care! #### 0.11.1.4 * Fix build with `base >= 4.8` and `unordered-containers < 0.2.6`. #### 0.11.1.3 * Fix build on TH-less GHCs #### 0.11.1.2 * Fix build with `base < 4.8` and `unordered-containers < 0.2.6`. * Add missing field in docs for `defaultOptions`. #### 0.11.1.1 * Fixes a bug where the hashes of equal values could differ. ### 0.11.1.0 The only changes are added instances. These are new: * `ToJSON a => ToJSON (NonEmpty a)` * `FromJSON a => FromJSON (NonEmpty a)` * `ToJSON (Proxy a)` * `FromJSON (Proxy a)` * `ToJSON b => ToJSON (Tagged a b)` * `FromJSON b => FromJSON (Tagged a b)` * `ToJSON a => ToJSON (Const a b)` * `FromJSON a => FromJSON (Const a b)` These are now available for older GHCs: * `ToJSON Natural` * `FromJSON Natural` # 0.11.0.0 This release should be close to backwards compatible with aeson 0.9. If you are upgrading from aeson 0.10 it might be easier to go back in history to the point you were still using 0.9. **Breaking changes**: * Revert `.:?` to behave like it did in 0.9. If you want the 0.10 behavior use `.:!` instead. * Revert JSON format of `Either` to 0.9, `Left` and `Right` are now serialized with an initial uppercase letter. If you want the names in lowercase you can add a newtype with an instance. * All `ToJSON` and `FromJSON` instances except for `[a]` are no longer `OVERLAPPABLE`. Mark your instance as `OVERLAPPING` if it overlaps any of the other aeson instances. * All `ToJSON` and `FromJSON` instances except for `[Char]` are no longer incoherent, this means you may need to replace your incoherent instances with a newtyped instance. **Additions**: * Introduce `.:!` that behaves like `.:?` did in 0.10. * Allow `HH:MM` format for `ZonedTime` and `UTCTime`. This is one of the formats allowed by [ISO 8601](https://en.wikipedia.org/wiki/ISO_8601#Times). * Added `ToJSON` and `FromJSON` instances for the `Version`, `Ordering`, and `Natural` types. **Bug fixes**: * JSONPath identifiers are now escaped if they contain invalid characters. * Fixed JSONPath messages for Seq to include indices. * Fixed JSONPath messages for Either to include `left`/`right`. * Fix missing quotes surrounding time encodings. * Fix #293: Type error in TH when using `omitNothingFields = True`. **Compatibility**: * Various updates to support GHC 8. # 0.10.0.0 ## Performance improvements * Direct encoding via the new `toEncoding` method is over 2x faster than `toJSON`. (You must write or code-gen a `toEncoding` implementation to unlock this speedup. See below for details.) * Improved string decoding gives a 12% speed win in parsing string-heavy JSON payloads (very common). * Encoding and decoding of time-related types are 10x faster (!!) as a result of bypassing `Data.Time.Format` and the arbitrary-precision `Integer` type. * When using `toEncoding`, `[Char]` can be encoded without a conversion to `Text`. This is fast and efficient. * Parsing into an `Object` is now 5% faster and more allocation-efficient. ## SUBTLE API CHANGES, READ CAREFULLY With the exception of long-deprecated code, the API changes below **should be upwards compatible** from older versions of `aeson`. If you run into upgrade problems, please file an issue with details. * The `ToJSON` class has a new method, `toEncoding`, that allows direct encoding from a Haskell value to a lazy bytestring without construction of an intermediate `Value`. The performance benefits of direct encoding are significant: more than 2x faster than before, with less than 1/3 the memory usage. To preserve API compatibility across upgrades from older versions of this library, the default implementation of `toEncoding` uses `toJSON`. You will *not* see any performance improvement unless you write an implementation of `toEncoding`, which can be very simple: ```haskell instance ToJSON Coord where toEncoding = genericToEncoding defaultOptions ``` (Behind the scenes, the `encode` function uses `toEncoding` now, so if you implement `toEncoding` for your types, you should see a speedup immediately.) If you use Template Haskell or GHC Generics to auto-generate your `ToJSON` instances, you'll benefit from fast toEncoding implementations for free! * When converting from a `Value` to a target Haskell type, `FromJSON` instances now provide much better error messages, including a complete JSON path from the root of the object to the offending element. This greatly eases debugging. * It is now possible to use Template Haskell to generate `FromJSON` and `ToJSON` instances for types in data families. * If you use Template Haskell or generics, and used to use the `camelTo` function to rename fields, the new `camelTo2` function is smarter. For example, `camelTo` will rename `CamelAPICase` to `camelapi_case` (ugh!), while `camelTo2` will map it to `camel_api_case` (yay!). * New `ToJSON` and `FromJSON` instances for the following time-related types: `Day`, `LocalTime`. * `FromJSON` `UTCTime` parser accepts the same values as for `ZonedTime`, but converts any time zone offset into a UTC time. * The `Result` type is now an instance of `Foldable` and `Traversable`. * The `Data.Aeson.Generic` module has been removed. It was deprecated in late 2013. * GHC 7.2 and older are no longer supported. * The instance of `Monad` for the `Result` type lacked an implementation of `fail` (oops). This has been corrected. * Semantics of `(.:?)` operator are changed. It's doesn't anymore accept present `Null` value. * Added `(Foldable t, ToJSON a) => ToJSON (t a)` overlappable instance. You might see `No instance for (Foldable YourPolymorphicType) arising from a use of ‘.=’` -errors due this change. # 0.9.0.1 * A stray export of `encodeToBuilder` got away! # 0.9.0.0 * The `json` and `json'` parsers are now synonyms for `value` and `value'`, in conformance with the looser semantics of RFC 7159. * Renamed `encodeToByteStringBuilder` to the more compact `encodeToBuilder`. # 0.8.1.1 * The dependency on the `unordered-containers` package was too lax, and has been corrected. # 0.8.1.0 * Encoding a `Scientific` value with a huge exponent is now handled efficiently. (This would previously allocate a huge arbitrary-precision integer, potentially leading to a denial of service.) * Handling of strings that contain backslash escape sequences is greatly improved. For a pathological string containing almost a megabyte of consecutive backslashes, the new implementation is 27x faster and uses 42x less memory. * The `ToJSON` instance for `UTCTime` is rendered with higher (picosecond) resolution. * The `value` parser now correctly handles leading whitespace. * New instances of `ToJSON` and `FromJSON` for `Data.Sequence` and `Data.Functor.Identity`. The `Value` type now has a `Read` instance. * `ZonedTime` parser ordering now favours the standard `JSON` format, increasing efficiency in the common case. * Encoding to a `Text.Builder` now escapes `'<'` and `'>'` characters, to reduce XSS risk. # 0.8.0.2 * Fix `ToJSON` instance for 15-tuples (see #223). # 0.8.0.1 * Support `time-1.5`. # 0.8.0.0 * Add `ToJSON` and `FromJSON` instances for tuples of up to 15 elements. # 0.7.1.0 * Major compiler and library compatibility changes: we have dropped support for GHC older than 7.4, `text` older than 1.1, and `bytestring` older than 0.10.4.0. Supporting the older versions had become increasingly difficult, to the point where it was no longer worth it. # 0.7.0.0 * The performance of encoding to and decoding of bytestrings have both improved by up to 2x, while also using less memory. * New dependency: the `scientific` package lets us parse floating point numbers more quickly and accurately. * `eitherDecode`, `decodeStrictWith`: fixed bugs. * Added `FromJSON` and `ToJSON` instances for `Tree` and `Scientific`. * Fixed the `ToJSON` instances for `UTCTime` and `ZonedTime`. # 0.6 series * Much improved documentation. * Angle brackets are now escaped in JSON strings, to help avoid XSS attacks. * Fixed up handling of nullary constructors when using generic encoding. * Added `ToJSON`/`FromJSON` instances for: * The `Fixed` class * ISO-8601 dates: `UTCTime`, `ZonedTime`, and `TimeZone` * Added accessor functions for inspecting `Value`s. * Added `eitherDecode` function that returns an error message if decoding fails. # 0.5 to 0.6 * This release introduces a slightly obscure, but backwards-incompatible, change. In the generic APIs of versions 0.4 and 0.5, fields whose names began with a `"_"` character would have this character removed. This no longer occurs, as it was both buggy and surprising (https://github.com/bos/aeson/issues/53). * Fixed a bug in generic decoding of nullary constructors (https://github.com/bos/aeson/issues/62). # 0.4 to 0.5 * When used with the UTF-8 encoding performance improvements introduced in version 0.11.1.12 of the `text` package, this release improves `aeson`'s JSON encoding performance by 33% relative to `aeson` 0.4. As part of achieving this improvement, an API change was necessary. The `fromValue` function in the `Data.Aeson.Encode` module now uses the `text` package's `Builder` type instead of the `blaze-builder` package's `Builder` type. # 0.3 to 0.4 * The new `decode` function complements the longstanding `encode` function, and makes the API simpler. * New examples make it easier to learn to use the package (https://github.com/bos/aeson/tree/master/examples). * Generics support `aeson`'s support for data-type generic programming makes it possible to use JSON encodings of most data types without writing any boilerplate instances. Thanks to Bas Van Dijk, `aeson` now supports the two major schemes for doing datatype-generic programming: * the modern mechanism, built into GHC itself (http://www.haskell.org/ghc/docs/latest/html/users_guide/generic-programming.html) * the older mechanism, based on SYB (aka "scrap your boilerplate") The modern GHC-based generic mechanism is fast and terse: in fact, its performance is generally comparable in performance to hand-written and TH-derived `ToJSON` and `FromJSON` instances. To see how to use GHC generics, refer to `examples/Generic.hs`. The SYB-based generics support lives in `Data.Aeson.Generic` and is provided mainly for users of GHC older than 7.2. SYB is far slower (by about 10x) than the more modern generic mechanism. To see how to use SYB generics, refer to `examples/GenericSYB.hs`. * We switched the intermediate representation of JSON objects from `Data.Map` to `Data.HashMap` which has improved type conversion performance. * Instances of `ToJSON` and `FromJSON` for tuples are between 45% and 70% faster than in 0.3. * Evaluation control This version of aeson makes explicit the decoupling between *identifying* an element of a JSON document and *converting* it to Haskell. See the `Data.Aeson.Parser` documentation for details. The normal `aeson` `decode` function performs identification strictly, but defers conversion until needed. This can result in improved performance (e.g. if the results of some conversions are never needed), but at a cost in increased memory consumption. The new `decode'` function performs identification and conversion immediately. This incurs an up-front cost in CPU cycles, but reduces reduce memory consumption. aeson-1.4.2.0/examples/0000755000000000000000000000000000000000000012726 5ustar0000000000000000aeson-1.4.2.0/examples/Generic.hs0000755000000000000000000000220600000000000014641 0ustar0000000000000000-- This example is basically the same as in Simplest.hs, only it uses -- GHC's builtin generics instead of explicit instances of ToJSON and -- FromJSON. -- We enable the DeriveGeneric language extension so that GHC can -- automatically derive the Generic class for us. {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Prelude.Compat import Data.Aeson (FromJSON, ToJSON, decode, encode) import qualified Data.ByteString.Lazy.Char8 as BL import GHC.Generics (Generic) -- To decode or encode a value using the generic machinery, we must -- make the type an instance of the Generic class. data Coord = Coord { x :: Double, y :: Double } deriving (Show, Generic) -- While we still have to declare our type as instances of FromJSON -- and ToJSON, we do *not* need to provide bodies for the instances. -- Default versions will be supplied for us. instance FromJSON Coord instance ToJSON Coord main :: IO () main = do let req = decode "{\"x\":3.0,\"y\":-1.0}" :: Maybe Coord print req let reply = Coord { x = 123.4, y = 20 } BL.putStrLn (encode reply) aeson-1.4.2.0/examples/Simplest.hs0000755000000000000000000000202300000000000015062 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} module Main (main) where import Prelude.Compat import Control.Applicative (empty) import Data.Aeson import Data.Monoid import qualified Data.ByteString.Lazy.Char8 as BL data Coord = Coord { x :: Double, y :: Double } deriving (Show) -- A ToJSON instance allows us to encode a value as JSON. instance ToJSON Coord where toJSON (Coord xV yV) = object [ "x" .= xV, "y" .= yV ] toEncoding Coord{..} = pairs $ "x" .= x <> "y" .= y -- A FromJSON instance allows us to decode a value from JSON. This -- should match the format used by the ToJSON instance. instance FromJSON Coord where parseJSON (Object v) = Coord <$> v .: "x" <*> v .: "y" parseJSON _ = empty main :: IO () main = do let req = decode "{\"x\":3.0,\"y\":-1.0}" :: Maybe Coord print req let reply = Coord 123.4 20 BL.putStrLn (encode reply) aeson-1.4.2.0/examples/TemplateHaskell.hs0000755000000000000000000000145300000000000016347 0ustar0000000000000000-- We can use Template Haskell (TH) to generate instances of the -- FromJSON and ToJSON classes automatically. This is the fastest way -- to add JSON support for a type. {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Main (main) where import Prelude.Compat import Data.Aeson (decode, encode) import Data.Aeson.TH (deriveJSON, defaultOptions) import qualified Data.ByteString.Lazy.Char8 as BL data Coord = Coord { x :: Double, y :: Double } deriving (Show) -- This splice will derive instances of ToJSON and FromJSON for us. $(deriveJSON defaultOptions ''Coord) main :: IO () main = do let req = decode "{\"x\":3.0,\"y\":-1.0}" :: Maybe Coord print req let reply = Coord { x = 123.4, y = 20 } BL.putStrLn (encode reply) aeson-1.4.2.0/examples/Twitter.hs0000755000000000000000000000412700000000000014733 0ustar0000000000000000-- These types follow the format of Twitter search results, as can be -- found in the benchmarks/json-data directory. -- -- For uses of these types, see the Twitter subdirectory. -- -- There is one deviation for the sake of convenience: the Geo field -- named "type_" is really named "type" in Twitter's real feed. I -- renamed "type" to "type_" in the *.json files, to avoid overlap -- with a Haskell reserved keyword. {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE NoImplicitPrelude #-} module Twitter ( Metadata(..) , Geo(..) , Story(..) , Result(..) ) where import Prelude.Compat import Control.DeepSeq import Data.Data (Typeable, Data) import Data.Int (Int64) import Data.Text (Text) import GHC.Generics (Generic) {-# ANN module "Hlint: ignore Use camelCase" #-} {-# ANN module "Hlint: ignore Use newtype instead of data" #-} data Metadata = Metadata { result_type :: Text } deriving (Eq, Show, Typeable, Data, Generic) instance NFData Metadata data Geo = Geo { type_ :: Text , coordinates :: (Double, Double) } deriving (Eq, Show, Typeable, Data, Generic) instance NFData Geo data Story = Story { from_user_id_str :: Text , profile_image_url :: Text , created_at :: Text -- ZonedTime , from_user :: Text , id_str :: Text , metadata :: Metadata , to_user_id :: Maybe Int64 , text :: Text , id_ :: Int64 , from_user_id :: Int64 , geo :: Maybe Geo , iso_language_code :: Text , to_user_id_str :: Maybe Text , source :: Text } deriving (Show, Typeable, Data, Generic) instance NFData Story data Result = Result { results :: [Story] , max_id :: Int64 , since_id :: Int64 , refresh_url :: Text , next_page :: Text , results_per_page :: Int , page :: Int , completed_in :: Double , since_id_str :: Text , max_id_str :: Text , query :: Text } deriving (Show, Typeable, Data, Generic) instance NFData Result aeson-1.4.2.0/examples/Twitter/0000755000000000000000000000000000000000000014370 5ustar0000000000000000aeson-1.4.2.0/examples/Twitter/Generic.hs0000755000000000000000000000227200000000000016306 0ustar0000000000000000-- Use GHC generics to automatically generate good instances. {-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Twitter.Generic ( Metadata(..) , Geo(..) , Story(..) , Result(..) ) where import Prelude.Compat () import Twitter import Twitter.Options import Data.Aeson (ToJSON (..), FromJSON (..), genericToJSON, genericToEncoding, genericParseJSON) instance ToJSON Metadata where toJSON = genericToJSON twitterOptions toEncoding = genericToEncoding twitterOptions instance FromJSON Metadata where parseJSON = genericParseJSON twitterOptions instance ToJSON Geo where toJSON = genericToJSON twitterOptions toEncoding = genericToEncoding twitterOptions instance FromJSON Geo where parseJSON = genericParseJSON twitterOptions instance ToJSON Story where toJSON = genericToJSON twitterOptions toEncoding = genericToEncoding twitterOptions instance FromJSON Story where parseJSON = genericParseJSON twitterOptions instance ToJSON Result where toJSON = genericToJSON twitterOptions toEncoding = genericToEncoding twitterOptions instance FromJSON Result where parseJSON = genericParseJSON twitterOptions aeson-1.4.2.0/examples/Twitter/Manual.hs0000755000000000000000000000773100000000000016154 0ustar0000000000000000-- Manually write instances. {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Twitter.Manual ( Metadata(..) , Geo(..) , Story(..) , Result(..) ) where import Prelude.Compat import Control.Applicative import Data.Semigroup ((<>)) import Twitter import Data.Aeson hiding (Result) instance ToJSON Metadata where toJSON Metadata{..} = object [ "result_type" .= result_type ] toEncoding Metadata{..} = pairs $ "result_type" .= result_type instance FromJSON Metadata where parseJSON (Object v) = Metadata <$> v .: "result_type" parseJSON _ = empty instance ToJSON Geo where toJSON Geo{..} = object [ "type_" .= type_ , "coordinates" .= coordinates ] toEncoding Geo{..} = pairs $ "type_" .= type_ <> "coordinates" .= coordinates instance FromJSON Geo where parseJSON (Object v) = Geo <$> v .: "type_" <*> v .: "coordinates" parseJSON _ = empty instance ToJSON Story where toJSON Story{..} = object [ "from_user_id_str" .= from_user_id_str , "profile_image_url" .= profile_image_url , "created_at" .= created_at , "from_user" .= from_user , "id_str" .= id_str , "metadata" .= metadata , "to_user_id" .= to_user_id , "text" .= text , "id" .= id_ , "from_user_id" .= from_user_id , "geo" .= geo , "iso_language_code" .= iso_language_code , "to_user_id_str" .= to_user_id_str , "source" .= source ] toEncoding Story{..} = pairs $ "from_user_id_str" .= from_user_id_str <> "profile_image_url" .= profile_image_url <> "created_at" .= created_at <> "from_user" .= from_user <> "id_str" .= id_str <> "metadata" .= metadata <> "to_user_id" .= to_user_id <> "text" .= text <> "id" .= id_ <> "from_user_id" .= from_user_id <> "geo" .= geo <> "iso_language_code" .= iso_language_code <> "to_user_id_str" .= to_user_id_str <> "source" .= source instance FromJSON Story where parseJSON (Object v) = Story <$> v .: "from_user_id_str" <*> v .: "profile_image_url" <*> v .: "created_at" <*> v .: "from_user" <*> v .: "id_str" <*> v .: "metadata" <*> v .: "to_user_id" <*> v .: "text" <*> v .: "id" <*> v .: "from_user_id" <*> v .: "geo" <*> v .: "iso_language_code" <*> v .: "to_user_id_str" <*> v .: "source" parseJSON _ = empty instance ToJSON Result where toJSON Result{..} = object [ "results" .= results , "max_id" .= max_id , "since_id" .= since_id , "refresh_url" .= refresh_url , "next_page" .= next_page , "results_per_page" .= results_per_page , "page" .= page , "completed_in" .= completed_in , "since_id_str" .= since_id_str , "max_id_str" .= max_id_str , "query" .= query ] toEncoding Result{..} = pairs $ "results" .= results <> "max_id" .= max_id <> "since_id" .= since_id <> "refresh_url" .= refresh_url <> "next_page" .= next_page <> "results_per_page" .= results_per_page <> "page" .= page <> "completed_in" .= completed_in <> "since_id_str" .= since_id_str <> "max_id_str" .= max_id_str <> "query" .= query instance FromJSON Result where parseJSON (Object v) = Result <$> v .: "results" <*> v .: "max_id" <*> v .: "since_id" <*> v .: "refresh_url" <*> v .: "next_page" <*> v .: "results_per_page" <*> v .: "page" <*> v .: "completed_in" <*> v .: "since_id_str" <*> v .: "max_id_str" <*> v .: "query" parseJSON _ = empty aeson-1.4.2.0/examples/Twitter/Options.hs0000755000000000000000000000033600000000000016364 0ustar0000000000000000module Twitter.Options (module Twitter.Options) where import Data.Aeson twitterOptions :: Options twitterOptions = defaultOptions { fieldLabelModifier = \x -> case x of "id_" -> "id" _ -> x } aeson-1.4.2.0/examples/Twitter/TH.hs0000755000000000000000000000073400000000000015246 0ustar0000000000000000-- Use Template Haskell to generate good instances. {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Twitter.TH ( Metadata(..) , Geo(..) , Story(..) , Result(..) ) where import Twitter import Twitter.Options import Data.Aeson.TH $(deriveJSON twitterOptions ''Metadata) $(deriveJSON twitterOptions ''Geo) $(deriveJSON twitterOptions ''Story) $(deriveJSON twitterOptions ''Result) aeson-1.4.2.0/examples/aeson-examples.cabal0000755000000000000000000000110600000000000016634 0ustar0000000000000000name: aeson-examples version: 0 build-type: Simple cabal-version: >=1.8 executable aeson-example-generic main-is: Generic.hs ghc-options: -Wall build-depends: aeson >= 0.10, base, base-compat, bytestring, ghc-prim executable aeson-example-simplest main-is: Simplest.hs ghc-options: -Wall build-depends: aeson, base, base-compat, bytestring executable aeson-example-th main-is: TemplateHaskell.hs ghc-options: -Wall build-depends: aeson, base, base-compat, bytestring aeson-1.4.2.0/ffi/Data/Aeson/Parser/0000755000000000000000000000000000000000000015026 5ustar0000000000000000aeson-1.4.2.0/ffi/Data/Aeson/Parser/UnescapeFFI.hs0000644000000000000000000000351500000000000017456 0ustar0000000000000000{-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnliftedFFITypes #-} module Data.Aeson.Parser.UnescapeFFI ( unescapeText ) where import Control.Exception (evaluate, throw, try) import Control.Monad.ST.Unsafe (unsafeIOToST, unsafeSTToIO) import Data.ByteString as B import Data.ByteString.Internal as B import Data.Text.Encoding.Error (UnicodeException (..)) import Data.Text.Internal (Text (..)) import Data.Text.Internal.Private (runText) import Data.Text.Unsafe (unsafeDupablePerformIO) import Data.Word (Word8) import Foreign.C.Types (CInt (..), CSize (..)) import Foreign.ForeignPtr (withForeignPtr) import Foreign.Marshal.Utils (with) import Foreign.Ptr (Ptr, plusPtr) import Foreign.Storable (peek) import GHC.Base (MutableByteArray#) import qualified Data.Text.Array as A foreign import ccall unsafe "_js_decode_string" c_js_decode :: MutableByteArray# s -> Ptr CSize -> Ptr Word8 -> Ptr Word8 -> IO CInt unescapeText' :: ByteString -> Text unescapeText' (PS fp off len) = runText $ \done -> do let go dest = withForeignPtr fp $ \ptr -> with (0::CSize) $ \destOffPtr -> do let end = ptr `plusPtr` (off + len) loop curPtr = do res <- c_js_decode (A.maBA dest) destOffPtr curPtr end case res of 0 -> do n <- peek destOffPtr unsafeSTToIO (done dest (fromIntegral n)) _ -> throw (DecodeError desc Nothing) loop (ptr `plusPtr` off) (unsafeIOToST . go) =<< A.new len where desc = "Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream" {-# INLINE unescapeText' #-} unescapeText :: ByteString -> Either UnicodeException Text unescapeText = unsafeDupablePerformIO . try . evaluate . unescapeText' {-# INLINE unescapeText #-} aeson-1.4.2.0/ffi/Data/Aeson/Parser/UnescapeFFI.hs0000755000000000000000000000351500000000000017461 0ustar0000000000000000{-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnliftedFFITypes #-} module Data.Aeson.Parser.UnescapeFFI ( unescapeText ) where import Control.Exception (evaluate, throw, try) import Control.Monad.ST.Unsafe (unsafeIOToST, unsafeSTToIO) import Data.ByteString as B import Data.ByteString.Internal as B import Data.Text.Encoding.Error (UnicodeException (..)) import Data.Text.Internal (Text (..)) import Data.Text.Internal.Private (runText) import Data.Text.Unsafe (unsafeDupablePerformIO) import Data.Word (Word8) import Foreign.C.Types (CInt (..), CSize (..)) import Foreign.ForeignPtr (withForeignPtr) import Foreign.Marshal.Utils (with) import Foreign.Ptr (Ptr, plusPtr) import Foreign.Storable (peek) import GHC.Base (MutableByteArray#) import qualified Data.Text.Array as A foreign import ccall unsafe "_js_decode_string" c_js_decode :: MutableByteArray# s -> Ptr CSize -> Ptr Word8 -> Ptr Word8 -> IO CInt unescapeText' :: ByteString -> Text unescapeText' (PS fp off len) = runText $ \done -> do let go dest = withForeignPtr fp $ \ptr -> with (0::CSize) $ \destOffPtr -> do let end = ptr `plusPtr` (off + len) loop curPtr = do res <- c_js_decode (A.maBA dest) destOffPtr curPtr end case res of 0 -> do n <- peek destOffPtr unsafeSTToIO (done dest (fromIntegral n)) _ -> throw (DecodeError desc Nothing) loop (ptr `plusPtr` off) (unsafeIOToST . go) =<< A.new len where desc = "Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream" {-# INLINE unescapeText' #-} unescapeText :: ByteString -> Either UnicodeException Text unescapeText = unsafeDupablePerformIO . try . evaluate . unescapeText' {-# INLINE unescapeText #-} aeson-1.4.2.0/include/0000755000000000000000000000000000000000000012533 5ustar0000000000000000aeson-1.4.2.0/include/incoherent-compat.h0000755000000000000000000000030200000000000016321 0ustar0000000000000000#if __GLASGOW_HASKELL__ >= 710 #define INCOHERENT_ {-# INCOHERENT #-} #else -- This causes some type class instances to break: -- {-# LANGUAGE IncoherentInstances #-} #define INCOHERENT_ #endif aeson-1.4.2.0/include/overlapping-compat.h0000755000000000000000000000032200000000000016513 0ustar0000000000000000#if __GLASGOW_HASKELL__ >= 710 #define OVERLAPPABLE_ {-# OVERLAPPABLE #-} #define OVERLAPPING_ {-# OVERLAPPING #-} #else {-# LANGUAGE OverlappingInstances #-} #define OVERLAPPABLE_ #define OVERLAPPING_ #endif aeson-1.4.2.0/pure/Data/Aeson/Parser/0000755000000000000000000000000000000000000015235 5ustar0000000000000000aeson-1.4.2.0/pure/Data/Aeson/Parser/UnescapePure.hs0000644000000000000000000002173500000000000020200 0ustar0000000000000000-- WARNING: This file is security sensitive as it uses unsafeWrite which does -- not check bounds. Any changes should be made with care and we would love to -- get informed about them, just cc us in any PR targetting this file: @eskimor @jprider63 -- We would be happy to review the changes! -- The security check at the end (pos > length) only works if pos grows -- monotonously, if this condition does not hold, the check is flawed. module Data.Aeson.Parser.UnescapePure ( unescapeText ) where import Control.Exception (evaluate, throw, try) import Control.Monad (when) import Data.ByteString as B import Data.Bits (Bits, shiftL, shiftR, (.&.), (.|.)) import Data.Text (Text) import qualified Data.Text.Array as A import Data.Text.Encoding.Error (UnicodeException (..)) import Data.Text.Internal.Private (runText) import Data.Text.Unsafe (unsafeDupablePerformIO) import Data.Word (Word8, Word16, Word32) import GHC.ST (ST) -- Different UTF states. data Utf = UtfGround | UtfTail1 | UtfU32e0 | UtfTail2 | UtfU32ed | Utf843f0 | UtfTail3 | Utf843f4 deriving (Eq) data State = StateNone | StateUtf !Utf !Word32 | StateBackslash | StateU0 | StateU1 !Word16 | StateU2 !Word16 | StateU3 !Word16 | StateS0 | StateS1 | StateSU0 | StateSU1 !Word16 | StateSU2 !Word16 | StateSU3 !Word16 deriving (Eq) -- References: -- http://bjoern.hoehrmann.de/utf-8/decoder/dfa/ -- https://github.com/jwilm/vte/blob/master/utf8parse/src/table.rs.in setByte1 :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte1 point word = point .|. fromIntegral (word .&. 0x3f) {-# INLINE setByte1 #-} setByte2 :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte2 point word = point .|. (fromIntegral (word .&. 0x3f) `shiftL` 6) {-# INLINE setByte2 #-} setByte2Top :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte2Top point word = point .|. (fromIntegral (word .&. 0x1f) `shiftL` 6) {-# INLINE setByte2Top #-} setByte3 :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte3 point word = point .|. (fromIntegral (word .&. 0x3f) `shiftL` 12) {-# INLINE setByte3 #-} setByte3Top :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte3Top point word = point .|. (fromIntegral (word .&. 0xf) `shiftL` 12) {-# INLINE setByte3Top #-} setByte4 :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte4 point word = point .|. (fromIntegral (word .&. 0x7) `shiftL` 18) {-# INLINE setByte4 #-} decode :: Utf -> Word32 -> Word8 -> (Utf, Word32) decode UtfGround point word = case word of w | 0x00 <= w && w <= 0x7f -> (UtfGround, fromIntegral word) w | 0xc2 <= w && w <= 0xdf -> (UtfTail1, setByte2Top point word) 0xe0 -> (UtfU32e0, setByte3Top point word) w | 0xe1 <= w && w <= 0xec -> (UtfTail2, setByte3Top point word) 0xed -> (UtfU32ed, setByte3Top point word) w | 0xee <= w && w <= 0xef -> (UtfTail2, setByte3Top point word) 0xf0 -> (Utf843f0, setByte4 point word) w | 0xf1 <= w && w <= 0xf3 -> (UtfTail3, setByte4 point word) 0xf4 -> (Utf843f4, setByte4 point word) _ -> throwDecodeError decode UtfU32e0 point word = case word of w | 0xa0 <= w && w <= 0xbf -> (UtfTail1, setByte2 point word) _ -> throwDecodeError decode UtfU32ed point word = case word of w | 0x80 <= w && w <= 0x9f -> (UtfTail1, setByte2 point word) _ -> throwDecodeError decode Utf843f0 point word = case word of w | 0x90 <= w && w <= 0xbf -> (UtfTail2, setByte3 point word) _ -> throwDecodeError decode Utf843f4 point word = case word of w | 0x80 <= w && w <= 0x8f -> (UtfTail2, setByte3 point word) _ -> throwDecodeError decode UtfTail3 point word = case word of w | 0x80 <= w && w <= 0xbf -> (UtfTail2, setByte3 point word) _ -> throwDecodeError decode UtfTail2 point word = case word of w | 0x80 <= w && w <= 0xbf -> (UtfTail1, setByte2 point word) _ -> throwDecodeError decode UtfTail1 point word = case word of w | 0x80 <= w && w <= 0xbf -> (UtfGround, setByte1 point word) _ -> throwDecodeError decodeHex :: Word8 -> Word16 decodeHex x | 48 <= x && x <= 57 = fromIntegral x - 48 -- 0-9 | 65 <= x && x <= 70 = fromIntegral x - 55 -- A-F | 97 <= x && x <= 102 = fromIntegral x - 87 -- a-f | otherwise = throwDecodeError unescapeText' :: ByteString -> Text unescapeText' bs = runText $ \done -> do dest <- A.new len (pos, finalState) <- loop dest (0, StateNone) 0 -- Check final state. Currently pos gets only increased over time, so this check should catch overflows. when ( finalState /= StateNone || pos > len) throwDecodeError done dest pos -- TODO: pos, pos-1??? XXX where len = B.length bs runUtf dest pos st point c = case decode st point c of (UtfGround, 92) -> -- Backslash return (pos, StateBackslash) (UtfGround, w) | w <= 0xffff -> writeAndReturn dest pos (fromIntegral w) StateNone (UtfGround, w) -> do write dest pos (0xd7c0 + fromIntegral (w `shiftR` 10)) writeAndReturn dest (pos + 1) (0xdc00 + fromIntegral (w .&. 0x3ff)) StateNone (st', p) -> return (pos, StateUtf st' p) loop :: A.MArray s -> (Int, State) -> Int -> ST s (Int, State) loop _ ps i | i >= len = return ps loop dest ps i = do let c = B.index bs i -- JP: We can use unsafe index once we prove bounds with Liquid Haskell. ps' <- f dest ps c loop dest ps' $ i+1 -- No pending state. f dest (pos, StateNone) c = runUtf dest pos UtfGround 0 c -- In the middle of parsing a UTF string. f dest (pos, StateUtf st point) c = runUtf dest pos st point c -- In the middle of escaping a backslash. f dest (pos, StateBackslash) 34 = writeAndReturn dest pos 34 StateNone -- " f dest (pos, StateBackslash) 92 = writeAndReturn dest pos 92 StateNone -- Backslash f dest (pos, StateBackslash) 47 = writeAndReturn dest pos 47 StateNone -- / f dest (pos, StateBackslash) 98 = writeAndReturn dest pos 8 StateNone -- b f dest (pos, StateBackslash) 102 = writeAndReturn dest pos 12 StateNone -- f f dest (pos, StateBackslash) 110 = writeAndReturn dest pos 10 StateNone -- n f dest (pos, StateBackslash) 114 = writeAndReturn dest pos 13 StateNone -- r f dest (pos, StateBackslash) 116 = writeAndReturn dest pos 9 StateNone -- t f _ (pos, StateBackslash) 117 = return (pos, StateU0) -- u f _ ( _, StateBackslash) _ = throwDecodeError -- Processing '\u'. f _ (pos, StateU0) c = let w = decodeHex c in return (pos, StateU1 (w `shiftL` 12)) f _ (pos, StateU1 w') c = let w = decodeHex c in return (pos, StateU2 (w' .|. (w `shiftL` 8))) f _ (pos, StateU2 w') c = let w = decodeHex c in return (pos, StateU3 (w' .|. (w `shiftL` 4))) f dest (pos, StateU3 w') c = let w = decodeHex c in let u = w' .|. w in -- Get next state based on surrogates. let st | u >= 0xd800 && u <= 0xdbff = -- High surrogate. StateS0 | u >= 0xdc00 && u <= 0xdfff = -- Low surrogate. throwDecodeError | otherwise = StateNone in writeAndReturn dest pos u st -- Handle surrogates. f _ (pos, StateS0) 92 = return (pos, StateS1) -- Backslash f _ ( _, StateS0) _ = throwDecodeError f _ (pos, StateS1) 117 = return (pos, StateSU0) -- u f _ ( _, StateS1) _ = throwDecodeError f _ (pos, StateSU0) c = let w = decodeHex c in return (pos, StateSU1 (w `shiftL` 12)) f _ (pos, StateSU1 w') c = let w = decodeHex c in return (pos, StateSU2 (w' .|. (w `shiftL` 8))) f _ (pos, StateSU2 w') c = let w = decodeHex c in return (pos, StateSU3 (w' .|. (w `shiftL` 4))) f dest (pos, StateSU3 w') c = let w = decodeHex c in let u = w' .|. w in -- Check if not low surrogate. if u < 0xdc00 || u > 0xdfff then throwDecodeError else writeAndReturn dest pos u StateNone write :: A.MArray s -> Int -> Word16 -> ST s () write dest pos char = A.unsafeWrite dest pos char {-# INLINE write #-} writeAndReturn :: A.MArray s -> Int -> Word16 -> t -> ST s (Int, t) writeAndReturn dest pos char res = do write dest pos char return (pos + 1, res) {-# INLINE writeAndReturn #-} throwDecodeError :: a throwDecodeError = let desc = "Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream" in throw (DecodeError desc Nothing) unescapeText :: ByteString -> Either UnicodeException Text unescapeText = unsafeDupablePerformIO . try . evaluate . unescapeText' aeson-1.4.2.0/pure/Data/Aeson/Parser/UnescapePure.hs0000755000000000000000000002173500000000000020203 0ustar0000000000000000-- WARNING: This file is security sensitive as it uses unsafeWrite which does -- not check bounds. Any changes should be made with care and we would love to -- get informed about them, just cc us in any PR targetting this file: @eskimor @jprider63 -- We would be happy to review the changes! -- The security check at the end (pos > length) only works if pos grows -- monotonously, if this condition does not hold, the check is flawed. module Data.Aeson.Parser.UnescapePure ( unescapeText ) where import Control.Exception (evaluate, throw, try) import Control.Monad (when) import Data.ByteString as B import Data.Bits (Bits, shiftL, shiftR, (.&.), (.|.)) import Data.Text (Text) import qualified Data.Text.Array as A import Data.Text.Encoding.Error (UnicodeException (..)) import Data.Text.Internal.Private (runText) import Data.Text.Unsafe (unsafeDupablePerformIO) import Data.Word (Word8, Word16, Word32) import GHC.ST (ST) -- Different UTF states. data Utf = UtfGround | UtfTail1 | UtfU32e0 | UtfTail2 | UtfU32ed | Utf843f0 | UtfTail3 | Utf843f4 deriving (Eq) data State = StateNone | StateUtf !Utf !Word32 | StateBackslash | StateU0 | StateU1 !Word16 | StateU2 !Word16 | StateU3 !Word16 | StateS0 | StateS1 | StateSU0 | StateSU1 !Word16 | StateSU2 !Word16 | StateSU3 !Word16 deriving (Eq) -- References: -- http://bjoern.hoehrmann.de/utf-8/decoder/dfa/ -- https://github.com/jwilm/vte/blob/master/utf8parse/src/table.rs.in setByte1 :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte1 point word = point .|. fromIntegral (word .&. 0x3f) {-# INLINE setByte1 #-} setByte2 :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte2 point word = point .|. (fromIntegral (word .&. 0x3f) `shiftL` 6) {-# INLINE setByte2 #-} setByte2Top :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte2Top point word = point .|. (fromIntegral (word .&. 0x1f) `shiftL` 6) {-# INLINE setByte2Top #-} setByte3 :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte3 point word = point .|. (fromIntegral (word .&. 0x3f) `shiftL` 12) {-# INLINE setByte3 #-} setByte3Top :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte3Top point word = point .|. (fromIntegral (word .&. 0xf) `shiftL` 12) {-# INLINE setByte3Top #-} setByte4 :: (Num a, Bits b, Bits a, Integral b) => a -> b -> a setByte4 point word = point .|. (fromIntegral (word .&. 0x7) `shiftL` 18) {-# INLINE setByte4 #-} decode :: Utf -> Word32 -> Word8 -> (Utf, Word32) decode UtfGround point word = case word of w | 0x00 <= w && w <= 0x7f -> (UtfGround, fromIntegral word) w | 0xc2 <= w && w <= 0xdf -> (UtfTail1, setByte2Top point word) 0xe0 -> (UtfU32e0, setByte3Top point word) w | 0xe1 <= w && w <= 0xec -> (UtfTail2, setByte3Top point word) 0xed -> (UtfU32ed, setByte3Top point word) w | 0xee <= w && w <= 0xef -> (UtfTail2, setByte3Top point word) 0xf0 -> (Utf843f0, setByte4 point word) w | 0xf1 <= w && w <= 0xf3 -> (UtfTail3, setByte4 point word) 0xf4 -> (Utf843f4, setByte4 point word) _ -> throwDecodeError decode UtfU32e0 point word = case word of w | 0xa0 <= w && w <= 0xbf -> (UtfTail1, setByte2 point word) _ -> throwDecodeError decode UtfU32ed point word = case word of w | 0x80 <= w && w <= 0x9f -> (UtfTail1, setByte2 point word) _ -> throwDecodeError decode Utf843f0 point word = case word of w | 0x90 <= w && w <= 0xbf -> (UtfTail2, setByte3 point word) _ -> throwDecodeError decode Utf843f4 point word = case word of w | 0x80 <= w && w <= 0x8f -> (UtfTail2, setByte3 point word) _ -> throwDecodeError decode UtfTail3 point word = case word of w | 0x80 <= w && w <= 0xbf -> (UtfTail2, setByte3 point word) _ -> throwDecodeError decode UtfTail2 point word = case word of w | 0x80 <= w && w <= 0xbf -> (UtfTail1, setByte2 point word) _ -> throwDecodeError decode UtfTail1 point word = case word of w | 0x80 <= w && w <= 0xbf -> (UtfGround, setByte1 point word) _ -> throwDecodeError decodeHex :: Word8 -> Word16 decodeHex x | 48 <= x && x <= 57 = fromIntegral x - 48 -- 0-9 | 65 <= x && x <= 70 = fromIntegral x - 55 -- A-F | 97 <= x && x <= 102 = fromIntegral x - 87 -- a-f | otherwise = throwDecodeError unescapeText' :: ByteString -> Text unescapeText' bs = runText $ \done -> do dest <- A.new len (pos, finalState) <- loop dest (0, StateNone) 0 -- Check final state. Currently pos gets only increased over time, so this check should catch overflows. when ( finalState /= StateNone || pos > len) throwDecodeError done dest pos -- TODO: pos, pos-1??? XXX where len = B.length bs runUtf dest pos st point c = case decode st point c of (UtfGround, 92) -> -- Backslash return (pos, StateBackslash) (UtfGround, w) | w <= 0xffff -> writeAndReturn dest pos (fromIntegral w) StateNone (UtfGround, w) -> do write dest pos (0xd7c0 + fromIntegral (w `shiftR` 10)) writeAndReturn dest (pos + 1) (0xdc00 + fromIntegral (w .&. 0x3ff)) StateNone (st', p) -> return (pos, StateUtf st' p) loop :: A.MArray s -> (Int, State) -> Int -> ST s (Int, State) loop _ ps i | i >= len = return ps loop dest ps i = do let c = B.index bs i -- JP: We can use unsafe index once we prove bounds with Liquid Haskell. ps' <- f dest ps c loop dest ps' $ i+1 -- No pending state. f dest (pos, StateNone) c = runUtf dest pos UtfGround 0 c -- In the middle of parsing a UTF string. f dest (pos, StateUtf st point) c = runUtf dest pos st point c -- In the middle of escaping a backslash. f dest (pos, StateBackslash) 34 = writeAndReturn dest pos 34 StateNone -- " f dest (pos, StateBackslash) 92 = writeAndReturn dest pos 92 StateNone -- Backslash f dest (pos, StateBackslash) 47 = writeAndReturn dest pos 47 StateNone -- / f dest (pos, StateBackslash) 98 = writeAndReturn dest pos 8 StateNone -- b f dest (pos, StateBackslash) 102 = writeAndReturn dest pos 12 StateNone -- f f dest (pos, StateBackslash) 110 = writeAndReturn dest pos 10 StateNone -- n f dest (pos, StateBackslash) 114 = writeAndReturn dest pos 13 StateNone -- r f dest (pos, StateBackslash) 116 = writeAndReturn dest pos 9 StateNone -- t f _ (pos, StateBackslash) 117 = return (pos, StateU0) -- u f _ ( _, StateBackslash) _ = throwDecodeError -- Processing '\u'. f _ (pos, StateU0) c = let w = decodeHex c in return (pos, StateU1 (w `shiftL` 12)) f _ (pos, StateU1 w') c = let w = decodeHex c in return (pos, StateU2 (w' .|. (w `shiftL` 8))) f _ (pos, StateU2 w') c = let w = decodeHex c in return (pos, StateU3 (w' .|. (w `shiftL` 4))) f dest (pos, StateU3 w') c = let w = decodeHex c in let u = w' .|. w in -- Get next state based on surrogates. let st | u >= 0xd800 && u <= 0xdbff = -- High surrogate. StateS0 | u >= 0xdc00 && u <= 0xdfff = -- Low surrogate. throwDecodeError | otherwise = StateNone in writeAndReturn dest pos u st -- Handle surrogates. f _ (pos, StateS0) 92 = return (pos, StateS1) -- Backslash f _ ( _, StateS0) _ = throwDecodeError f _ (pos, StateS1) 117 = return (pos, StateSU0) -- u f _ ( _, StateS1) _ = throwDecodeError f _ (pos, StateSU0) c = let w = decodeHex c in return (pos, StateSU1 (w `shiftL` 12)) f _ (pos, StateSU1 w') c = let w = decodeHex c in return (pos, StateSU2 (w' .|. (w `shiftL` 8))) f _ (pos, StateSU2 w') c = let w = decodeHex c in return (pos, StateSU3 (w' .|. (w `shiftL` 4))) f dest (pos, StateSU3 w') c = let w = decodeHex c in let u = w' .|. w in -- Check if not low surrogate. if u < 0xdc00 || u > 0xdfff then throwDecodeError else writeAndReturn dest pos u StateNone write :: A.MArray s -> Int -> Word16 -> ST s () write dest pos char = A.unsafeWrite dest pos char {-# INLINE write #-} writeAndReturn :: A.MArray s -> Int -> Word16 -> t -> ST s (Int, t) writeAndReturn dest pos char res = do write dest pos char return (pos + 1, res) {-# INLINE writeAndReturn #-} throwDecodeError :: a throwDecodeError = let desc = "Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream" in throw (DecodeError desc Nothing) unescapeText :: ByteString -> Either UnicodeException Text unescapeText = unsafeDupablePerformIO . try . evaluate . unescapeText' aeson-1.4.2.0/stack-bench.yaml0000755000000000000000000000041700000000000014163 0ustar0000000000000000resolver: lts-12.10 # We use aeson in the snapshot to # - avoid recompilation of criterion # - compare against it # - '.' # # Also we use separate working directory to avoid "unregistering aeson" # caused recompilations work-dir: .stack-work-bench packages: - benchmarks aeson-1.4.2.0/stack-ffi-unescape.yaml0000755000000000000000000000016600000000000015452 0ustar0000000000000000resolver: lts-12.10 packages: - '.' flags: aeson: fast: true cffi: true extra-deps: - hashable-time-0.2.0.1 aeson-1.4.2.0/stack-lts12.yaml0000755000000000000000000000021300000000000014043 0ustar0000000000000000resolver: lts-12.10 packages: - '.' - attoparsec-iso8601 flags: aeson: fast: true cffi: true extra-deps: - hashable-time-0.2.0.1 aeson-1.4.2.0/stack-nightly.yaml0000755000000000000000000000020600000000000014556 0ustar0000000000000000resolver: nightly-2018-09-26 packages: - '.' - attoparsec-iso8601 flags: aeson: fast: true attoparsec-iso8601: fast: true aeson-1.4.2.0/tests/DataFamilies/0000755000000000000000000000000000000000000014575 5ustar0000000000000000aeson-1.4.2.0/tests/DataFamilies/Encoders.hs0000644000000000000000000002146000000000000016676 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module DataFamilies.Encoders (module DataFamilies.Encoders) where import Prelude.Compat import Data.Aeson.TH import Data.Aeson.Types import DataFamilies.Types import Options -------------------------------------------------------------------------------- -- Nullary encoders/decoders -------------------------------------------------------------------------------- thNullaryToJSONString :: Nullary Int -> Value thNullaryToJSONString = $(mkToJSON defaultOptions 'C1) thNullaryToEncodingString :: Nullary Int -> Encoding thNullaryToEncodingString = $(mkToEncoding defaultOptions 'C2) thNullaryParseJSONString :: Value -> Parser (Nullary Int) thNullaryParseJSONString = $(mkParseJSON defaultOptions 'C3) thNullaryToJSON2ElemArray :: Nullary Int -> Value thNullaryToJSON2ElemArray = $(mkToJSON opts2ElemArray 'C1) thNullaryToEncoding2ElemArray :: Nullary Int -> Encoding thNullaryToEncoding2ElemArray = $(mkToEncoding opts2ElemArray 'C2) thNullaryParseJSON2ElemArray :: Value -> Parser (Nullary Int) thNullaryParseJSON2ElemArray = $(mkParseJSON opts2ElemArray 'C3) thNullaryToJSONTaggedObject :: Nullary Int -> Value thNullaryToJSONTaggedObject = $(mkToJSON optsTaggedObject 'C1) thNullaryToEncodingTaggedObject :: Nullary Int -> Encoding thNullaryToEncodingTaggedObject = $(mkToEncoding optsTaggedObject 'C2) thNullaryParseJSONTaggedObject :: Value -> Parser (Nullary Int) thNullaryParseJSONTaggedObject = $(mkParseJSON optsTaggedObject 'C3) thNullaryToJSONObjectWithSingleField :: Nullary Int -> Value thNullaryToJSONObjectWithSingleField = $(mkToJSON optsObjectWithSingleField 'C1) thNullaryToEncodingObjectWithSingleField :: Nullary Int -> Encoding thNullaryToEncodingObjectWithSingleField = $(mkToEncoding optsObjectWithSingleField 'C2) thNullaryParseJSONObjectWithSingleField :: Value -> Parser (Nullary Int) thNullaryParseJSONObjectWithSingleField = $(mkParseJSON optsObjectWithSingleField 'C3) -------------------------------------------------------------------------------- -- SomeType encoders/decoders -------------------------------------------------------------------------------- thSomeTypeToJSON2ElemArray :: SomeType c () Int -> Value thSomeTypeToJSON2ElemArray = $(mkToJSON opts2ElemArray 'Nullary) thSomeTypeToEncoding2ElemArray :: SomeType c () Int -> Encoding thSomeTypeToEncoding2ElemArray = $(mkToEncoding opts2ElemArray 'Unary) thSomeTypeParseJSON2ElemArray :: Value -> Parser (SomeType c () Int) thSomeTypeParseJSON2ElemArray = $(mkParseJSON opts2ElemArray 'Product) thSomeTypeToJSONTaggedObject :: SomeType c () Int -> Value thSomeTypeToJSONTaggedObject = $(mkToJSON optsTaggedObject 'Record) thSomeTypeToEncodingTaggedObject :: SomeType c () Int -> Encoding thSomeTypeToEncodingTaggedObject = $(mkToEncoding optsTaggedObject 'Nullary) thSomeTypeParseJSONTaggedObject :: Value -> Parser (SomeType c () Int) thSomeTypeParseJSONTaggedObject = $(mkParseJSON optsTaggedObject 'Unary) thSomeTypeToJSONObjectWithSingleField :: SomeType c () Int -> Value thSomeTypeToJSONObjectWithSingleField = $(mkToJSON optsObjectWithSingleField 'Product) thSomeTypeToEncodingObjectWithSingleField :: SomeType c () Int -> Encoding thSomeTypeToEncodingObjectWithSingleField = $(mkToEncoding optsObjectWithSingleField 'Record) thSomeTypeParseJSONObjectWithSingleField :: Value -> Parser (SomeType c () Int) thSomeTypeParseJSONObjectWithSingleField = $(mkParseJSON optsObjectWithSingleField 'Nullary) -------------------------------------------------------------------------------- -- Approx encoders/decoders -------------------------------------------------------------------------------- thApproxToJSONUnwrap :: Approx String -> Value thApproxToJSONUnwrap = $(mkToJSON optsUnwrapUnaryRecords 'Approx) thApproxToEncodingUnwrap :: Approx String -> Encoding thApproxToEncodingUnwrap = $(mkToEncoding optsUnwrapUnaryRecords 'Approx) thApproxParseJSONUnwrap :: Value -> Parser (Approx String) thApproxParseJSONUnwrap = $(mkParseJSON optsUnwrapUnaryRecords 'Approx) thApproxToJSONDefault :: Approx String -> Value thApproxToJSONDefault = $(mkToJSON defaultOptions 'Approx) thApproxToEncodingDefault :: Approx String -> Encoding thApproxToEncodingDefault = $(mkToEncoding defaultOptions 'Approx) thApproxParseJSONDefault :: Value -> Parser (Approx String) thApproxParseJSONDefault = $(mkParseJSON defaultOptions 'Approx) -------------------------------------------------------------------------------- -- GADT encoders/decoders -------------------------------------------------------------------------------- thGADTToJSONUnwrap :: GADT String -> Value thGADTToJSONUnwrap = $(mkToJSON optsUnwrapUnaryRecords 'GADT) thGADTToEncodingUnwrap :: GADT String -> Encoding thGADTToEncodingUnwrap = $(mkToEncoding optsUnwrapUnaryRecords 'GADT) thGADTParseJSONUnwrap :: Value -> Parser (GADT String) thGADTParseJSONUnwrap = $(mkParseJSON optsUnwrapUnaryRecords 'GADT) thGADTToJSONDefault :: GADT String -> Value thGADTToJSONDefault = $(mkToJSON defaultOptions 'GADT) thGADTToEncodingDefault :: GADT String -> Encoding thGADTToEncodingDefault = $(mkToEncoding defaultOptions 'GADT) thGADTParseJSONDefault :: Value -> Parser (GADT String) thGADTParseJSONDefault = $(mkParseJSON defaultOptions 'GADT) -------------------------------------------------------------------------------- -- Generic encoders/decoders -------------------------------------------------------------------------------- -- Nullary gNullaryToJSONString :: Nullary Int -> Value gNullaryToJSONString = genericToJSON defaultOptions gNullaryToEncodingString :: Nullary Int -> Encoding gNullaryToEncodingString = genericToEncoding defaultOptions gNullaryParseJSONString :: Value -> Parser (Nullary Int) gNullaryParseJSONString = genericParseJSON defaultOptions gNullaryToJSON2ElemArray :: Nullary Int -> Value gNullaryToJSON2ElemArray = genericToJSON opts2ElemArray gNullaryToEncoding2ElemArray :: Nullary Int -> Encoding gNullaryToEncoding2ElemArray = genericToEncoding opts2ElemArray gNullaryParseJSON2ElemArray :: Value -> Parser (Nullary Int) gNullaryParseJSON2ElemArray = genericParseJSON opts2ElemArray gNullaryToJSONTaggedObject :: Nullary Int -> Value gNullaryToJSONTaggedObject = genericToJSON optsTaggedObject gNullaryToEncodingTaggedObject :: Nullary Int -> Encoding gNullaryToEncodingTaggedObject = genericToEncoding optsTaggedObject gNullaryParseJSONTaggedObject :: Value -> Parser (Nullary Int) gNullaryParseJSONTaggedObject = genericParseJSON optsTaggedObject gNullaryToJSONObjectWithSingleField :: Nullary Int -> Value gNullaryToJSONObjectWithSingleField = genericToJSON optsObjectWithSingleField gNullaryToEncodingObjectWithSingleField :: Nullary Int -> Encoding gNullaryToEncodingObjectWithSingleField = genericToEncoding optsObjectWithSingleField gNullaryParseJSONObjectWithSingleField :: Value -> Parser (Nullary Int) gNullaryParseJSONObjectWithSingleField = genericParseJSON optsObjectWithSingleField -- SomeType gSomeTypeToJSON2ElemArray :: SomeType c () Int -> Value gSomeTypeToJSON2ElemArray = genericToJSON opts2ElemArray gSomeTypeToEncoding2ElemArray :: SomeType c () Int -> Encoding gSomeTypeToEncoding2ElemArray = genericToEncoding opts2ElemArray gSomeTypeParseJSON2ElemArray :: Value -> Parser (SomeType c () Int) gSomeTypeParseJSON2ElemArray = genericParseJSON opts2ElemArray gSomeTypeToJSONTaggedObject :: SomeType c () Int -> Value gSomeTypeToJSONTaggedObject = genericToJSON optsTaggedObject gSomeTypeToEncodingTaggedObject :: SomeType c () Int -> Encoding gSomeTypeToEncodingTaggedObject = genericToEncoding optsTaggedObject gSomeTypeParseJSONTaggedObject :: Value -> Parser (SomeType c () Int) gSomeTypeParseJSONTaggedObject = genericParseJSON optsTaggedObject gSomeTypeToJSONObjectWithSingleField :: SomeType c () Int -> Value gSomeTypeToJSONObjectWithSingleField = genericToJSON optsObjectWithSingleField gSomeTypeToEncodingObjectWithSingleField :: SomeType c () Int -> Encoding gSomeTypeToEncodingObjectWithSingleField = genericToEncoding optsObjectWithSingleField gSomeTypeParseJSONObjectWithSingleField :: Value -> Parser (SomeType c () Int) gSomeTypeParseJSONObjectWithSingleField = genericParseJSON optsObjectWithSingleField -- Approx gApproxToJSONUnwrap :: Approx String -> Value gApproxToJSONUnwrap = genericToJSON optsUnwrapUnaryRecords gApproxToEncodingUnwrap :: Approx String -> Encoding gApproxToEncodingUnwrap = genericToEncoding optsUnwrapUnaryRecords gApproxParseJSONUnwrap :: Value -> Parser (Approx String) gApproxParseJSONUnwrap = genericParseJSON optsUnwrapUnaryRecords gApproxToJSONDefault :: Approx String -> Value gApproxToJSONDefault = genericToJSON defaultOptions gApproxToEncodingDefault :: Approx String -> Encoding gApproxToEncodingDefault = genericToEncoding defaultOptions gApproxParseJSONDefault :: Value -> Parser (Approx String) gApproxParseJSONDefault = genericParseJSON defaultOptions aeson-1.4.2.0/tests/DataFamilies/Instances.hs0000644000000000000000000000245300000000000017064 0ustar0000000000000000{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module DataFamilies.Instances () where import Prelude.Compat import Data.Aeson.TH import Data.Aeson.Types (FromJSON(..)) import DataFamilies.Types import Test.QuickCheck (Arbitrary(..), elements, oneof) instance (Arbitrary a) => Arbitrary (Approx a) where arbitrary = Approx <$> arbitrary instance Arbitrary (Nullary Int) where arbitrary = elements [C1, C2, C3] instance Arbitrary a => Arbitrary (SomeType c () a) where arbitrary = oneof [ pure Nullary , Unary <$> arbitrary , Product <$> arbitrary <*> arbitrary <*> arbitrary , Record <$> arbitrary <*> arbitrary <*> arbitrary , List <$> arbitrary ] instance Arbitrary (GADT String) where arbitrary = GADT <$> arbitrary deriveJSON defaultOptions 'C1 deriveJSON defaultOptions 'Nullary deriveJSON defaultOptions 'Approx deriveToJSON defaultOptions 'GADT -- We must write the FromJSON instance head ourselves -- due to the refined GADT return type instance FromJSON (GADT String) where parseJSON = $(mkParseJSON defaultOptions 'GADT) aeson-1.4.2.0/tests/DataFamilies/Properties.hs0000644000000000000000000001666400000000000017302 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE NoImplicitPrelude #-} module DataFamilies.Properties (tests) where import Prelude.Compat import DataFamilies.Encoders import DataFamilies.Instances () import Properties hiding (tests) import Test.Tasty (TestTree, testGroup) import Test.Tasty.QuickCheck (testProperty) -------------------------------------------------------------------------------- tests :: TestTree tests = testGroup "data families" [ testGroup "template-haskell" [ testGroup "toJSON" [ testGroup "Nullary" [ testProperty "string" (isString . thNullaryToJSONString) , testProperty "2ElemArray" (is2ElemArray . thNullaryToJSON2ElemArray) , testProperty "TaggedObject" (isNullaryTaggedObject . thNullaryToJSONTaggedObject) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . thNullaryToJSONObjectWithSingleField) , testGroup "roundTrip" [ testProperty "string" (toParseJSON thNullaryParseJSONString thNullaryToJSONString) , testProperty "2ElemArray" (toParseJSON thNullaryParseJSON2ElemArray thNullaryToJSON2ElemArray) , testProperty "TaggedObject" (toParseJSON thNullaryParseJSONTaggedObject thNullaryToJSONTaggedObject) , testProperty "ObjectWithSingleField" (toParseJSON thNullaryParseJSONObjectWithSingleField thNullaryToJSONObjectWithSingleField) ] ] , testGroup "SomeType" [ testProperty "2ElemArray" (is2ElemArray . thSomeTypeToJSON2ElemArray) , testProperty "TaggedObject" (isTaggedObject . thSomeTypeToJSONTaggedObject) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . thSomeTypeToJSONObjectWithSingleField) , testGroup "roundTrip" [ testProperty "2ElemArray" (toParseJSON thSomeTypeParseJSON2ElemArray thSomeTypeToJSON2ElemArray) , testProperty "TaggedObject" (toParseJSON thSomeTypeParseJSONTaggedObject thSomeTypeToJSONTaggedObject) , testProperty "ObjectWithSingleField" (toParseJSON thSomeTypeParseJSONObjectWithSingleField thSomeTypeToJSONObjectWithSingleField) ] ] , testGroup "Approx" [ testProperty "string" (isString . thApproxToJSONUnwrap) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . thApproxToJSONDefault) , testGroup "roundTrip" [ testProperty "string" (toParseJSON thApproxParseJSONUnwrap thApproxToJSONUnwrap) , testProperty "ObjectWithSingleField" (toParseJSON thApproxParseJSONDefault thApproxToJSONDefault) ] ] , testGroup "GADT" [ testProperty "string" (isString . thGADTToJSONUnwrap) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . thGADTToJSONDefault) , testGroup "roundTrip" [ testProperty "string" (toParseJSON thGADTParseJSONUnwrap thGADTToJSONUnwrap) , testProperty "ObjectWithSingleField" (toParseJSON thGADTParseJSONDefault thGADTToJSONDefault) ] ] ] , testGroup "toEncoding" [ testProperty "NullaryString" $ thNullaryToJSONString `sameAs` thNullaryToEncodingString , testProperty "Nullary2ElemArray" $ thNullaryToJSON2ElemArray `sameAs` thNullaryToEncoding2ElemArray , testProperty "NullaryTaggedObject" $ thNullaryToJSONTaggedObject `sameAs` thNullaryToEncodingTaggedObject , testProperty "NullaryObjectWithSingleField" $ thNullaryToJSONObjectWithSingleField `sameAs` thNullaryToEncodingObjectWithSingleField , testProperty "ApproxUnwrap" $ thApproxToJSONUnwrap `sameAs` thApproxToEncodingUnwrap , testProperty "ApproxDefault" $ thApproxToJSONDefault `sameAs` thApproxToEncodingDefault , testProperty "SomeType2ElemArray" $ thSomeTypeToJSON2ElemArray `sameAs` thSomeTypeToEncoding2ElemArray , testProperty "SomeTypeTaggedObject" $ thSomeTypeToJSONTaggedObject `sameAs` thSomeTypeToEncodingTaggedObject , testProperty "SomeTypeObjectWithSingleField" $ thSomeTypeToJSONObjectWithSingleField `sameAs` thSomeTypeToEncodingObjectWithSingleField ] ] , testGroup "generics" [ testGroup "toJSON" [ testGroup "Nullary" [ testProperty "string" (isString . gNullaryToJSONString) , testProperty "2ElemArray" (is2ElemArray . gNullaryToJSON2ElemArray) , testProperty "TaggedObject" (isNullaryTaggedObject . gNullaryToJSONTaggedObject) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . gNullaryToJSONObjectWithSingleField) , testGroup "roundTrip" [ testProperty "string" (toParseJSON gNullaryParseJSONString gNullaryToJSONString) , testProperty "2ElemArray" (toParseJSON gNullaryParseJSON2ElemArray gNullaryToJSON2ElemArray) , testProperty "TaggedObject" (toParseJSON gNullaryParseJSONTaggedObject gNullaryToJSONTaggedObject) , testProperty "ObjectWithSingleField" (toParseJSON gNullaryParseJSONObjectWithSingleField gNullaryToJSONObjectWithSingleField) ] ] , testGroup "SomeType" [ testProperty "2ElemArray" (is2ElemArray . gSomeTypeToJSON2ElemArray) , testProperty "TaggedObject" (isTaggedObject . gSomeTypeToJSONTaggedObject) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . gSomeTypeToJSONObjectWithSingleField) , testGroup "roundTrip" [ testProperty "2ElemArray" (toParseJSON gSomeTypeParseJSON2ElemArray gSomeTypeToJSON2ElemArray) , testProperty "TaggedObject" (toParseJSON gSomeTypeParseJSONTaggedObject gSomeTypeToJSONTaggedObject) , testProperty "ObjectWithSingleField" (toParseJSON gSomeTypeParseJSONObjectWithSingleField gSomeTypeToJSONObjectWithSingleField) ] ] , testGroup "Approx" [ testProperty "string" (isString . gApproxToJSONUnwrap) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . gApproxToJSONDefault) , testGroup "roundTrip" [ testProperty "string" (toParseJSON gApproxParseJSONUnwrap gApproxToJSONUnwrap) , testProperty "ObjectWithSingleField" (toParseJSON gApproxParseJSONDefault gApproxToJSONDefault) ] ] ] , testGroup "toEncoding" [ testProperty "NullaryString" $ gNullaryToJSONString `sameAs` gNullaryToEncodingString , testProperty "Nullary2ElemArray" $ gNullaryToJSON2ElemArray `sameAs` gNullaryToEncoding2ElemArray , testProperty "NullaryTaggedObject" $ gNullaryToJSONTaggedObject `sameAs` gNullaryToEncodingTaggedObject , testProperty "NullaryObjectWithSingleField" $ gNullaryToJSONObjectWithSingleField `sameAs` gNullaryToEncodingObjectWithSingleField , testProperty "ApproxUnwrap" $ gApproxToJSONUnwrap `sameAs` gApproxToEncodingUnwrap , testProperty "ApproxDefault" $ gApproxToJSONDefault `sameAs` gApproxToEncodingDefault , testProperty "SomeType2ElemArray" $ gSomeTypeToJSON2ElemArray `sameAs` gSomeTypeToEncoding2ElemArray , testProperty "SomeTypeTaggedObject" $ gSomeTypeToJSONTaggedObject `sameAs` gSomeTypeToEncodingTaggedObject , testProperty "SomeTypeObjectWithSingleField" $ gSomeTypeToJSONObjectWithSingleField `sameAs` gSomeTypeToEncodingObjectWithSingleField ] ] ] aeson-1.4.2.0/tests/DataFamilies/Types.hs0000644000000000000000000000315600000000000016242 0ustar0000000000000000-- DataKinds is needed for deriveAll0 calls on GHC 8 {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} module DataFamilies.Types (module DataFamilies.Types) where import Prelude.Compat import Generics.Deriving.TH (deriveAll0) import Types (ApproxEq(..)) data family Nullary a data instance Nullary Int = C1 | C2 | C3 deriving (Eq, Show) data instance Nullary Char = C4 deriving (Eq, Show) data family SomeType a b c data instance SomeType c () a = Nullary | Unary Int | Product String (Maybe Char) a | Record { testOne :: Double , testTwo :: Maybe Bool , testThree :: Maybe a } | List [a] deriving (Eq, Show) data family Approx a newtype instance Approx a = Approx { fromApprox :: a } deriving (Show, ApproxEq, Num) instance (ApproxEq a) => Eq (Approx a) where Approx a == Approx b = a =~ b data family GADT a data instance GADT a where GADT :: { gadt :: String } -> GADT String deriving instance Eq (GADT a) deriving instance Show (GADT a) -- We use generic-deriving to be able to derive Generic instances for -- data families on GHC 7.4. $(deriveAll0 'C1) $(deriveAll0 'C4) $(deriveAll0 'Approx) $(deriveAll0 'Nullary) aeson-1.4.2.0/tests/0000755000000000000000000000000000000000000012252 5ustar0000000000000000aeson-1.4.2.0/tests/Encoders.hs0000644000000000000000000004126600000000000014361 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module Encoders (module Encoders) where import Prelude.Compat import Data.Aeson.TH import Data.Aeson.Types import Options import Types -------------------------------------------------------------------------------- -- Nullary encoders/decoders -------------------------------------------------------------------------------- thNullaryToJSONString :: Nullary -> Value thNullaryToJSONString = $(mkToJSON defaultOptions ''Nullary) thNullaryToEncodingString :: Nullary -> Encoding thNullaryToEncodingString = $(mkToEncoding defaultOptions ''Nullary) thNullaryParseJSONString :: Value -> Parser Nullary thNullaryParseJSONString = $(mkParseJSON defaultOptions ''Nullary) thNullaryToJSON2ElemArray :: Nullary -> Value thNullaryToJSON2ElemArray = $(mkToJSON opts2ElemArray ''Nullary) thNullaryToEncoding2ElemArray :: Nullary -> Encoding thNullaryToEncoding2ElemArray = $(mkToEncoding opts2ElemArray ''Nullary) thNullaryParseJSON2ElemArray :: Value -> Parser Nullary thNullaryParseJSON2ElemArray = $(mkParseJSON opts2ElemArray ''Nullary) thNullaryToJSONTaggedObject :: Nullary -> Value thNullaryToJSONTaggedObject = $(mkToJSON optsTaggedObject ''Nullary) thNullaryToEncodingTaggedObject :: Nullary -> Encoding thNullaryToEncodingTaggedObject = $(mkToEncoding optsTaggedObject ''Nullary) thNullaryParseJSONTaggedObject :: Value -> Parser Nullary thNullaryParseJSONTaggedObject = $(mkParseJSON optsTaggedObject ''Nullary) thNullaryToJSONObjectWithSingleField :: Nullary -> Value thNullaryToJSONObjectWithSingleField = $(mkToJSON optsObjectWithSingleField ''Nullary) thNullaryToEncodingObjectWithSingleField :: Nullary -> Encoding thNullaryToEncodingObjectWithSingleField = $(mkToEncoding optsObjectWithSingleField ''Nullary) thNullaryParseJSONObjectWithSingleField :: Value -> Parser Nullary thNullaryParseJSONObjectWithSingleField = $(mkParseJSON optsObjectWithSingleField ''Nullary) gNullaryToJSONString :: Nullary -> Value gNullaryToJSONString = genericToJSON defaultOptions gNullaryToEncodingString :: Nullary -> Encoding gNullaryToEncodingString = genericToEncoding defaultOptions gNullaryParseJSONString :: Value -> Parser Nullary gNullaryParseJSONString = genericParseJSON defaultOptions gNullaryToJSON2ElemArray :: Nullary -> Value gNullaryToJSON2ElemArray = genericToJSON opts2ElemArray gNullaryToEncoding2ElemArray :: Nullary -> Encoding gNullaryToEncoding2ElemArray = genericToEncoding opts2ElemArray gNullaryParseJSON2ElemArray :: Value -> Parser Nullary gNullaryParseJSON2ElemArray = genericParseJSON opts2ElemArray gNullaryToJSONTaggedObject :: Nullary -> Value gNullaryToJSONTaggedObject = genericToJSON optsTaggedObject gNullaryToEncodingTaggedObject :: Nullary -> Encoding gNullaryToEncodingTaggedObject = genericToEncoding optsTaggedObject gNullaryParseJSONTaggedObject :: Value -> Parser Nullary gNullaryParseJSONTaggedObject = genericParseJSON optsTaggedObject gNullaryToJSONObjectWithSingleField :: Nullary -> Value gNullaryToJSONObjectWithSingleField = genericToJSON optsObjectWithSingleField gNullaryToEncodingObjectWithSingleField :: Nullary -> Encoding gNullaryToEncodingObjectWithSingleField = genericToEncoding optsObjectWithSingleField gNullaryParseJSONObjectWithSingleField :: Value -> Parser Nullary gNullaryParseJSONObjectWithSingleField = genericParseJSON optsObjectWithSingleField -------------------------------------------------------------------------------- -- SomeType encoders/decoders -------------------------------------------------------------------------------- -- Unary types type LiftToJSON f a = (a -> Value) -> ([a] -> Value) -> f a -> Value type LiftToEncoding f a = (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding type LiftParseJSON f a = (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) thSomeTypeToJSON2ElemArray :: SomeType Int -> Value thSomeTypeToJSON2ElemArray = $(mkToJSON opts2ElemArray ''SomeType) thSomeTypeToEncoding2ElemArray :: SomeType Int -> Encoding thSomeTypeToEncoding2ElemArray = $(mkToEncoding opts2ElemArray ''SomeType) thSomeTypeLiftToJSON2ElemArray :: LiftToJSON SomeType a thSomeTypeLiftToJSON2ElemArray = $(mkLiftToJSON opts2ElemArray ''SomeType) thSomeTypeLiftToEncoding2ElemArray :: LiftToEncoding SomeType a thSomeTypeLiftToEncoding2ElemArray = $(mkLiftToEncoding opts2ElemArray ''SomeType) thSomeTypeParseJSON2ElemArray :: Value -> Parser (SomeType Int) thSomeTypeParseJSON2ElemArray = $(mkParseJSON opts2ElemArray ''SomeType) thSomeTypeLiftParseJSON2ElemArray :: LiftParseJSON SomeType a thSomeTypeLiftParseJSON2ElemArray = $(mkLiftParseJSON opts2ElemArray ''SomeType) thSomeTypeToJSONTaggedObject :: SomeType Int -> Value thSomeTypeToJSONTaggedObject = $(mkToJSON optsTaggedObject ''SomeType) thSomeTypeToEncodingTaggedObject :: SomeType Int -> Encoding thSomeTypeToEncodingTaggedObject = $(mkToEncoding optsTaggedObject ''SomeType) thSomeTypeLiftToJSONTaggedObject :: LiftToJSON SomeType a thSomeTypeLiftToJSONTaggedObject = $(mkLiftToJSON optsTaggedObject ''SomeType) thSomeTypeLiftToEncodingTaggedObject :: LiftToEncoding SomeType a thSomeTypeLiftToEncodingTaggedObject = $(mkLiftToEncoding optsTaggedObject ''SomeType) thSomeTypeParseJSONTaggedObject :: Value -> Parser (SomeType Int) thSomeTypeParseJSONTaggedObject = $(mkParseJSON optsTaggedObject ''SomeType) thSomeTypeLiftParseJSONTaggedObject :: LiftParseJSON SomeType a thSomeTypeLiftParseJSONTaggedObject = $(mkLiftParseJSON optsTaggedObject ''SomeType) thSomeTypeToJSONObjectWithSingleField :: SomeType Int -> Value thSomeTypeToJSONObjectWithSingleField = $(mkToJSON optsObjectWithSingleField ''SomeType) thSomeTypeToEncodingObjectWithSingleField :: SomeType Int -> Encoding thSomeTypeToEncodingObjectWithSingleField = $(mkToEncoding optsObjectWithSingleField ''SomeType) thSomeTypeLiftToJSONObjectWithSingleField :: LiftToJSON SomeType a thSomeTypeLiftToJSONObjectWithSingleField = $(mkLiftToJSON optsObjectWithSingleField ''SomeType) thSomeTypeLiftToEncodingObjectWithSingleField :: LiftToEncoding SomeType a thSomeTypeLiftToEncodingObjectWithSingleField = $(mkLiftToEncoding optsObjectWithSingleField ''SomeType) thSomeTypeParseJSONObjectWithSingleField :: Value -> Parser (SomeType Int) thSomeTypeParseJSONObjectWithSingleField = $(mkParseJSON optsObjectWithSingleField ''SomeType) thSomeTypeLiftParseJSONObjectWithSingleField :: LiftParseJSON SomeType a thSomeTypeLiftParseJSONObjectWithSingleField = $(mkLiftParseJSON optsObjectWithSingleField ''SomeType) gSomeTypeToJSON2ElemArray :: SomeType Int -> Value gSomeTypeToJSON2ElemArray = genericToJSON opts2ElemArray gSomeTypeToEncoding2ElemArray :: SomeType Int -> Encoding gSomeTypeToEncoding2ElemArray = genericToEncoding opts2ElemArray gSomeTypeParseJSON2ElemArray :: Value -> Parser (SomeType Int) gSomeTypeParseJSON2ElemArray = genericParseJSON opts2ElemArray #if __GLASGOW_HASKELL__ >= 706 gSomeTypeLiftToEncoding2ElemArray :: LiftToEncoding SomeType a gSomeTypeLiftToEncoding2ElemArray = genericLiftToEncoding opts2ElemArray gSomeTypeLiftToJSON2ElemArray :: LiftToJSON SomeType a gSomeTypeLiftToJSON2ElemArray = genericLiftToJSON opts2ElemArray gSomeTypeLiftParseJSON2ElemArray :: LiftParseJSON SomeType a gSomeTypeLiftParseJSON2ElemArray = genericLiftParseJSON opts2ElemArray #endif gSomeTypeToJSONTaggedObject :: SomeType Int -> Value gSomeTypeToJSONTaggedObject = genericToJSON optsTaggedObject gSomeTypeToEncodingTaggedObject :: SomeType Int -> Encoding gSomeTypeToEncodingTaggedObject = genericToEncoding optsTaggedObject gSomeTypeParseJSONTaggedObject :: Value -> Parser (SomeType Int) gSomeTypeParseJSONTaggedObject = genericParseJSON optsTaggedObject #if __GLASGOW_HASKELL__ >= 706 gSomeTypeLiftToEncodingTaggedObject :: LiftToEncoding SomeType a gSomeTypeLiftToEncodingTaggedObject = genericLiftToEncoding optsTaggedObject gSomeTypeLiftToJSONTaggedObject :: LiftToJSON SomeType a gSomeTypeLiftToJSONTaggedObject = genericLiftToJSON optsTaggedObject gSomeTypeLiftParseJSONTaggedObject :: LiftParseJSON SomeType a gSomeTypeLiftParseJSONTaggedObject = genericLiftParseJSON optsTaggedObject #endif gSomeTypeToJSONObjectWithSingleField :: SomeType Int -> Value gSomeTypeToJSONObjectWithSingleField = genericToJSON optsObjectWithSingleField gSomeTypeToEncodingObjectWithSingleField :: SomeType Int -> Encoding gSomeTypeToEncodingObjectWithSingleField = genericToEncoding optsObjectWithSingleField gSomeTypeParseJSONObjectWithSingleField :: Value -> Parser (SomeType Int) gSomeTypeParseJSONObjectWithSingleField = genericParseJSON optsObjectWithSingleField #if __GLASGOW_HASKELL__ >= 706 gSomeTypeLiftToEncodingObjectWithSingleField :: LiftToEncoding SomeType a gSomeTypeLiftToEncodingObjectWithSingleField = genericLiftToEncoding optsObjectWithSingleField gSomeTypeLiftToJSONObjectWithSingleField :: LiftToJSON SomeType a gSomeTypeLiftToJSONObjectWithSingleField = genericLiftToJSON optsObjectWithSingleField gSomeTypeLiftParseJSONObjectWithSingleField :: LiftParseJSON SomeType a gSomeTypeLiftParseJSONObjectWithSingleField = genericLiftParseJSON optsObjectWithSingleField #endif gSomeTypeToJSONOmitNothingFields :: SomeType Int -> Value gSomeTypeToJSONOmitNothingFields = genericToJSON optsOmitNothingFields gSomeTypeToEncodingOmitNothingFields :: SomeType Int -> Encoding gSomeTypeToEncodingOmitNothingFields = genericToEncoding optsOmitNothingFields -------------------------------------------------------------------------------- -- Option fields -------------------------------------------------------------------------------- thOptionFieldToJSON :: OptionField -> Value thOptionFieldToJSON = $(mkToJSON optsOptionField 'OptionField) thOptionFieldToEncoding :: OptionField -> Encoding thOptionFieldToEncoding = $(mkToEncoding optsOptionField 'OptionField) thOptionFieldParseJSON :: Value -> Parser OptionField thOptionFieldParseJSON = $(mkParseJSON optsOptionField 'OptionField) gOptionFieldToJSON :: OptionField -> Value gOptionFieldToJSON = genericToJSON optsOptionField gOptionFieldToEncoding :: OptionField -> Encoding gOptionFieldToEncoding = genericToEncoding optsOptionField gOptionFieldParseJSON :: Value -> Parser OptionField gOptionFieldParseJSON = genericParseJSON optsOptionField thMaybeFieldToJSON :: MaybeField -> Value thMaybeFieldToJSON = $(mkToJSON optsOptionField 'MaybeField) -------------------------------------------------------------------------------- -- IncoherentInstancesNeeded -------------------------------------------------------------------------------- -- | This test demonstrates the need for IncoherentInstances. See the definition -- of 'IncoherentInstancesNeeded' for a discussion of the issue. -- -- NOTE 1: We only need to compile this test. We do not need to run it. -- -- NOTE 2: We actually only use the INCOHERENT pragma on specific instances -- instead of the IncoherentInstances language extension. Therefore, this is -- only supported on GHC versions >= 7.10. #if __GLASGOW_HASKELL__ >= 710 incoherentInstancesNeededParseJSONString :: FromJSON a => Value -> Parser (IncoherentInstancesNeeded a) incoherentInstancesNeededParseJSONString = case () of _ | True -> $(mkParseJSON defaultOptions ''IncoherentInstancesNeeded) | False -> genericParseJSON defaultOptions incoherentInstancesNeededToJSON :: ToJSON a => IncoherentInstancesNeeded a -> Value incoherentInstancesNeededToJSON = case () of _ | True -> $(mkToJSON defaultOptions ''IncoherentInstancesNeeded) | False -> genericToJSON defaultOptions #endif ------------------------------------------------------------------------------- -- EitherTextInt encoders/decodes ------------------------------------------------------------------------------- thEitherTextIntToJSONUntaggedValue :: EitherTextInt -> Value thEitherTextIntToJSONUntaggedValue = $(mkToJSON optsUntaggedValue ''EitherTextInt) thEitherTextIntToEncodingUntaggedValue :: EitherTextInt -> Encoding thEitherTextIntToEncodingUntaggedValue = $(mkToEncoding optsUntaggedValue ''EitherTextInt) thEitherTextIntParseJSONUntaggedValue :: Value -> Parser EitherTextInt thEitherTextIntParseJSONUntaggedValue = $(mkParseJSON optsUntaggedValue ''EitherTextInt) gEitherTextIntToJSONUntaggedValue :: EitherTextInt -> Value gEitherTextIntToJSONUntaggedValue = genericToJSON optsUntaggedValue gEitherTextIntToEncodingUntaggedValue :: EitherTextInt -> Encoding gEitherTextIntToEncodingUntaggedValue = genericToEncoding optsUntaggedValue gEitherTextIntParseJSONUntaggedValue :: Value -> Parser EitherTextInt gEitherTextIntParseJSONUntaggedValue = genericParseJSON optsUntaggedValue -------------------------------------------------------------------------------- -- Approx encoders/decoders -------------------------------------------------------------------------------- thApproxToJSONUnwrap :: Approx String -> Value thApproxToJSONUnwrap = $(mkToJSON optsUnwrapUnaryRecords ''Approx) thApproxToEncodingUnwrap :: Approx String -> Encoding thApproxToEncodingUnwrap = $(mkToEncoding optsUnwrapUnaryRecords ''Approx) thApproxParseJSONUnwrap :: Value -> Parser (Approx String) thApproxParseJSONUnwrap = $(mkParseJSON optsUnwrapUnaryRecords ''Approx) thApproxToJSONDefault :: Approx String -> Value thApproxToJSONDefault = $(mkToJSON defaultOptions ''Approx) thApproxToEncodingDefault :: Approx String -> Encoding thApproxToEncodingDefault = $(mkToEncoding defaultOptions ''Approx) thApproxParseJSONDefault :: Value -> Parser (Approx String) thApproxParseJSONDefault = $(mkParseJSON defaultOptions ''Approx) gApproxToJSONUnwrap :: Approx String -> Value gApproxToJSONUnwrap = genericToJSON optsUnwrapUnaryRecords gApproxToEncodingUnwrap :: Approx String -> Encoding gApproxToEncodingUnwrap = genericToEncoding optsUnwrapUnaryRecords gApproxParseJSONUnwrap :: Value -> Parser (Approx String) gApproxParseJSONUnwrap = genericParseJSON optsUnwrapUnaryRecords gApproxToJSONDefault :: Approx String -> Value gApproxToJSONDefault = genericToJSON defaultOptions gApproxToEncodingDefault :: Approx String -> Encoding gApproxToEncodingDefault = genericToEncoding defaultOptions gApproxParseJSONDefault :: Value -> Parser (Approx String) gApproxParseJSONDefault = genericParseJSON defaultOptions -------------------------------------------------------------------------------- -- GADT encoders/decoders -------------------------------------------------------------------------------- thGADTToJSONUnwrap :: GADT String -> Value thGADTToJSONUnwrap = $(mkToJSON optsUnwrapUnaryRecords ''GADT) thGADTToEncodingUnwrap :: GADT String -> Encoding thGADTToEncodingUnwrap = $(mkToEncoding optsUnwrapUnaryRecords ''GADT) thGADTParseJSONUnwrap :: Value -> Parser (GADT String) thGADTParseJSONUnwrap = $(mkParseJSON optsUnwrapUnaryRecords ''GADT) thGADTToJSONDefault :: GADT String -> Value thGADTToJSONDefault = $(mkToJSON defaultOptions ''GADT) thGADTToEncodingDefault :: GADT String -> Encoding thGADTToEncodingDefault = $(mkToEncoding defaultOptions ''GADT) thGADTParseJSONDefault :: Value -> Parser (GADT String) thGADTParseJSONDefault = $(mkParseJSON defaultOptions ''GADT) -------------------------------------------------------------------------------- -- OneConstructor encoders/decoders -------------------------------------------------------------------------------- thOneConstructorToJSONDefault :: OneConstructor -> Value thOneConstructorToJSONDefault = $(mkToJSON defaultOptions ''OneConstructor) thOneConstructorToEncodingDefault :: OneConstructor -> Encoding thOneConstructorToEncodingDefault = $(mkToEncoding defaultOptions ''OneConstructor) thOneConstructorParseJSONDefault :: Value -> Parser OneConstructor thOneConstructorParseJSONDefault = $(mkParseJSON defaultOptions ''OneConstructor) thOneConstructorToJSONTagged :: OneConstructor -> Value thOneConstructorToJSONTagged = $(mkToJSON optsTagSingleConstructors ''OneConstructor) thOneConstructorToEncodingTagged :: OneConstructor -> Encoding thOneConstructorToEncodingTagged = $(mkToEncoding optsTagSingleConstructors ''OneConstructor) thOneConstructorParseJSONTagged :: Value -> Parser OneConstructor thOneConstructorParseJSONTagged = $(mkParseJSON optsTagSingleConstructors ''OneConstructor) gOneConstructorToJSONDefault :: OneConstructor -> Value gOneConstructorToJSONDefault = genericToJSON defaultOptions gOneConstructorToEncodingDefault :: OneConstructor -> Encoding gOneConstructorToEncodingDefault = genericToEncoding defaultOptions gOneConstructorParseJSONDefault :: Value -> Parser OneConstructor gOneConstructorParseJSONDefault = genericParseJSON defaultOptions gOneConstructorToJSONTagged :: OneConstructor -> Value gOneConstructorToJSONTagged = genericToJSON optsTagSingleConstructors gOneConstructorToEncodingTagged :: OneConstructor -> Encoding gOneConstructorToEncodingTagged = genericToEncoding optsTagSingleConstructors gOneConstructorParseJSONTagged :: Value -> Parser OneConstructor gOneConstructorParseJSONTagged = genericParseJSON optsTagSingleConstructors aeson-1.4.2.0/tests/ErrorMessages.hs0000644000000000000000000000374700000000000015402 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module ErrorMessages ( tests ) where import Prelude.Compat import Data.Aeson (FromJSON(..), eitherDecode) import Data.Proxy (Proxy(..)) import Instances () import Numeric.Natural (Natural) import Test.Tasty (TestTree) import Test.Tasty.HUnit (Assertion, assertFailure, assertEqual, testCase) import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.HashMap.Strict as HM tests :: [TestTree] tests = [ testCase "Int" int , testCase "Integer" integer , testCase "Natural" natural , testCase "String" string , testCase "HashMap" hashMap ] int :: Assertion int = do let t = test (Proxy :: Proxy Int) t "\"\"" $ expected "Int" "String" t "[]" $ expected "Int" "Array" t "{}" $ expected "Int" "Object" t "null" $ expected "Int" "Null" integer :: Assertion integer = do let t = test (Proxy :: Proxy Integer) t "44.44" $ expected "Integer" "floating number 44.44" natural :: Assertion natural = do let t = test (Proxy :: Proxy Natural) t "44.44" $ expected "Natural" "floating number 44.44" t "-50" $ expected "Natural" "negative number -50" string :: Assertion string = do let t = test (Proxy :: Proxy String) t "1" $ expected "String" "Number" t "[]" $ expected "String" "Array" t "{}" $ expected "String" "Object" t "null" $ expected "String" "Null" hashMap :: Assertion hashMap = do let t = test (Proxy :: Proxy (HM.HashMap String Int)) t "\"\"" $ expected "HashMap k v" "String" t "[]" $ expected "HashMap k v" "Array" expected :: String -> String -> String expected ex enc = "Error in $: expected " ++ ex ++ ", encountered " ++ enc test :: forall a proxy . (FromJSON a, Show a) => proxy a -> L.ByteString -> String -> Assertion test _ v msg = case eitherDecode v of Left e -> assertEqual "Invalid error message" msg e Right (x :: a) -> assertFailure $ "Expected parsing to fail but it suceeded with: " ++ show x aeson-1.4.2.0/tests/Functions.hs0000644000000000000000000000067700000000000014570 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Functions ( approxEq , approxEqWith ) where import Prelude.Compat approxEq :: (Fractional a, Ord a) => a -> a -> Bool approxEq = approxEqWith 1e-15 1e-15 approxEqWith :: (Fractional a, Ord a) => a -> a -> a -> a -> Bool approxEqWith maxAbsoluteError maxRelativeError a b = a == b || d < maxAbsoluteError || d / max (abs b) (abs a) <= maxRelativeError where d = abs (a - b) aeson-1.4.2.0/tests/Instances.hs0000644000000000000000000001242500000000000014541 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Instances () where import Prelude.Compat import Control.Applicative (empty) import Control.Monad import Data.Aeson.Types import Data.Function (on) import Data.Time (ZonedTime(..), TimeZone(..)) import Data.Time.Clock (UTCTime(..)) import Functions import Test.QuickCheck (Arbitrary(..), elements, oneof) import Types import qualified Data.DList as DList import qualified Data.HashMap.Strict as HM import Data.Orphans () import Test.QuickCheck.Instances () #if MIN_VERSION_base(4,7,0) import Data.Hashable.Time () #endif -- "System" types. instance Arbitrary DotNetTime where arbitrary = DotNetTime `liftM` arbitrary shrink = map DotNetTime . shrink . fromDotNetTime -- | Compare timezone part only on 'timeZoneMinutes' instance Eq ZonedTime where ZonedTime a (TimeZone a' _ _) == ZonedTime b (TimeZone b' _ _) = a == b && a' == b' -- Compare equality to within a millisecond, allowing for rounding -- error (ECMA 262 requires milliseconds to rounded to zero, not -- rounded to nearest). instance ApproxEq UTCTime where a =~ b = ((==) `on` utctDay) a b && (approxEqWith 1 1 `on` ((* 1e3) . utctDayTime)) a b instance ApproxEq DotNetTime where (=~) = (=~) `on` fromDotNetTime instance ApproxEq Float where a =~ b | isNaN a && isNaN b = True | otherwise = approxEq a b instance ApproxEq Double where a =~ b | isNaN a && isNaN b = True | otherwise = approxEq a b instance (ApproxEq k, Eq v) => ApproxEq (HM.HashMap k v) where a =~ b = and $ zipWith eq (HM.toList a) (HM.toList b) where eq (x,y) (u,v) = x =~ u && y == v -- Test-related types. instance Arbitrary Foo where arbitrary = liftM4 Foo arbitrary arbitrary arbitrary arbitrary instance Eq Foo where a == b = fooInt a == fooInt b && fooDouble a `approxEq` fooDouble b && fooTuple a == fooTuple b instance ToJSON Foo where toJSON Foo{..} = object [ "fooInt" .= fooInt , "fooDouble" .= fooDouble , "fooTuple" .= fooTuple , "fooMap" .= fooMap ] instance FromJSON Foo where parseJSON (Object v) = Foo <$> v .: "fooInt" <*> v .: "fooDouble" <*> v .: "fooTuple" <*> v .: "fooMap" parseJSON _ = empty instance Arbitrary UFoo where arbitrary = UFoo <$> arbitrary <*> arbitrary where _ = uFooInt instance Arbitrary OneConstructor where arbitrary = return OneConstructor instance FromJSON OneConstructor instance ToJSON OneConstructor instance (Arbitrary a, Arbitrary b) => Arbitrary (Product2 a b) where arbitrary = liftM2 Product2 arbitrary arbitrary instance (FromJSON a, FromJSON b) => FromJSON (Product2 a b) instance (ToJSON a, ToJSON b) => ToJSON (Product2 a b) instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f) => Arbitrary (Product6 a b c d e f) where arbitrary = Product6 <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (Product6 a b c d e f) instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (Product6 a b c d e f) instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (Sum4 a b c d) where arbitrary = oneof [Alt1 <$> arbitrary, Alt2 <$> arbitrary, Alt3 <$> arbitrary, Alt4 <$> arbitrary] instance (FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (Sum4 a b c d) instance (ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (Sum4 a b c d) instance (Arbitrary a) => Arbitrary (Approx a) where arbitrary = Approx <$> arbitrary instance (FromJSON a) => FromJSON (Approx a) where parseJSON a = Approx <$> parseJSON a instance (ToJSON a) => ToJSON (Approx a) where toJSON = toJSON . fromApprox instance Arbitrary Nullary where arbitrary = elements [C1, C2, C3] instance Arbitrary a => Arbitrary (SomeType a) where arbitrary = oneof [ pure Nullary , Unary <$> arbitrary , Product <$> arbitrary <*> arbitrary <*> arbitrary , Record <$> arbitrary <*> arbitrary <*> arbitrary , List <$> arbitrary ] instance Arbitrary EitherTextInt where arbitrary = oneof [ LeftBool <$> arbitrary , RightInt <$> arbitrary , BothTextInt <$> arbitrary <*> arbitrary , pure NoneNullary ] instance Arbitrary (GADT String) where arbitrary = GADT <$> arbitrary instance Arbitrary OptionField where arbitrary = OptionField <$> arbitrary instance ApproxEq Char where (=~) = (==) instance (ApproxEq a) => ApproxEq [a] where a =~ b = length a == length b && all (uncurry (=~)) (zip a b) instance Arbitrary a => Arbitrary (DList.DList a) where arbitrary = DList.fromList <$> arbitrary aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/0000755000000000000000000000000000000000000017377 5ustar0000000000000000aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_object_key_lone_2nd_surrogate.json0000755000000000000000000000001400000000000026571 0ustar0000000000000000{"\uDFAA":0}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_1st_surrogate_but_2nd_missing.json0000755000000000000000000000001200000000000030134 0ustar0000000000000000["\uDADA"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_1st_valid_surrogate_2nd_invalid.json0000755000000000000000000000002000000000000030415 0ustar0000000000000000["\uD888\u1234"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_UTF-16LE_with_BOM.json0000755000000000000000000000001400000000000025021 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_UTF-8_invalid_sequence.json0000755000000000000000000000001200000000000026365 0ustar0000000000000000["日ш"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_incomplete_surrogate_and_escape_valid.json0000755000000000000000000000001400000000000031741 0ustar0000000000000000["\uD800\n"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_incomplete_surrogate_pair.json0000755000000000000000000000001300000000000027432 0ustar0000000000000000["\uDd1ea"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_incomplete_surrogates_escape_valid.json0000755000000000000000000000002200000000000031301 0ustar0000000000000000["\uD800\uD800\n"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_invalid_lonely_surrogate.json0000755000000000000000000000001200000000000027267 0ustar0000000000000000["\ud800"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_invalid_surrogate.json0000755000000000000000000000001500000000000025710 0ustar0000000000000000["\ud800abc"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_inverted_surrogates_U+1D11E.json0000755000000000000000000000002000000000000027254 0ustar0000000000000000["\uDd1e\uD834"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_lone_second_surrogate.json0000755000000000000000000000001200000000000026547 0ustar0000000000000000["\uDFAA"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_not_in_unicode_range.json0000755000000000000000000000001000000000000026332 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_truncated-utf-8.json0000755000000000000000000000000600000000000025121 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_unicode_U+10FFFE_nonchar.json0000755000000000000000000000002000000000000026450 0ustar0000000000000000["\uDBFF\uDFFE"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_unicode_U+1FFFE_nonchar.json0000755000000000000000000000002000000000000026370 0ustar0000000000000000["\uD83F\uDFFE"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_unicode_U+FDD0_nonchar.json0000755000000000000000000000001200000000000026257 0ustar0000000000000000["\uFDD0"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_string_unicode_U+FFFE_nonchar.json0000755000000000000000000000001200000000000026310 0ustar0000000000000000["\uFFFE"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_structure_500_nested_arrays.json0000755000000000000000000000175000000000000026157 0ustar0000000000000000[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/i_structure_UTF-8_BOM_empty_object.json0000755000000000000000000000000500000000000026764 0ustar0000000000000000{}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_1_true_without_comma.json0000755000000000000000000000001000000000000026135 0ustar0000000000000000[1 true]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_a_invalid_utf8.json0000755000000000000000000000000400000000000024676 0ustar0000000000000000[a]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_colon_instead_of_comma.json0000755000000000000000000000000700000000000026466 0ustar0000000000000000["": 1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_comma_after_close.json0000755000000000000000000000000500000000000025445 0ustar0000000000000000[""],aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_comma_and_number.json0000755000000000000000000000000400000000000025270 0ustar0000000000000000[,1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_double_comma.json0000755000000000000000000000000600000000000024432 0ustar0000000000000000[1,,2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_double_extra_comma.json0000755000000000000000000000000700000000000025636 0ustar0000000000000000["x",,]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_extra_close.json0000755000000000000000000000000600000000000024314 0ustar0000000000000000["x"]]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_extra_comma.json0000755000000000000000000000000500000000000024302 0ustar0000000000000000["",]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_incomplete.json0000755000000000000000000000000400000000000024141 0ustar0000000000000000["x"aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_incomplete_invalid_value.json0000755000000000000000000000000200000000000027041 0ustar0000000000000000[xaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_inner_array_no_comma.json0000755000000000000000000000000600000000000026165 0ustar0000000000000000[3[4]]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_invalid_utf8.json0000755000000000000000000000000300000000000024375 0ustar0000000000000000[]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_items_separated_by_semicolon.json0000755000000000000000000000000500000000000027716 0ustar0000000000000000[1:2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_just_comma.json0000755000000000000000000000000300000000000024142 0ustar0000000000000000[,]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_just_minus.json0000755000000000000000000000000300000000000024201 0ustar0000000000000000[-]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_missing_value.json0000755000000000000000000000001100000000000024645 0ustar0000000000000000[ , ""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_newlines_unclosed.json0000755000000000000000000000001300000000000025522 0ustar0000000000000000["a", 4 ,1,aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_number_and_comma.json0000755000000000000000000000000400000000000025270 0ustar0000000000000000[1,]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_number_and_several_commas.json0000755000000000000000000000000500000000000027175 0ustar0000000000000000[1,,]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_spaces_vertical_tab_formfeed.json0000755000000000000000000000001000000000000027643 0ustar0000000000000000[" a"\f]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_star_inside.json0000755000000000000000000000000300000000000024305 0ustar0000000000000000[*]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_unclosed.json0000755000000000000000000000000300000000000023615 0ustar0000000000000000[""aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_unclosed_trailing_comma.json0000755000000000000000000000000300000000000026662 0ustar0000000000000000[1,aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_unclosed_with_new_lines.json0000755000000000000000000000001000000000000026711 0ustar0000000000000000[1, 1 ,1aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_array_unclosed_with_object_inside.json0000755000000000000000000000000300000000000027531 0ustar0000000000000000[{}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_incomplete_false.json0000755000000000000000000000000600000000000024117 0ustar0000000000000000[fals]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_incomplete_null.json0000755000000000000000000000000500000000000023776 0ustar0000000000000000[nul]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_incomplete_true.json0000755000000000000000000000000500000000000024003 0ustar0000000000000000[tru]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_++.json0000755000000000000000000000001000000000000022356 0ustar0000000000000000[++1234]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_+1.json0000755000000000000000000000000400000000000022367 0ustar0000000000000000[+1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_+Inf.json0000755000000000000000000000000600000000000022745 0ustar0000000000000000[+Inf]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_-01.json0000755000000000000000000000000500000000000022452 0ustar0000000000000000[-01]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_-NaN.json0000755000000000000000000000000600000000000022707 0ustar0000000000000000[-NaN]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_0_capital_E+.json0000755000000000000000000000000500000000000024330 0ustar0000000000000000[0E+]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_0_capital_E.json0000755000000000000000000000000400000000000024254 0ustar0000000000000000[0E]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_0e+.json0000755000000000000000000000000500000000000022534 0ustar0000000000000000[0e+]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_0e.json0000755000000000000000000000000400000000000022460 0ustar0000000000000000[0e]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_1_000.json0000755000000000000000000000001100000000000022671 0ustar0000000000000000[1 000.0]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_1eE2.json0000755000000000000000000000000600000000000022652 0ustar0000000000000000[1eE2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_Inf.json0000755000000000000000000000000500000000000022671 0ustar0000000000000000[Inf]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_NaN.json0000755000000000000000000000000500000000000022631 0ustar0000000000000000[NaN]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_U+FF11_fullwidth_digit_one.json0000755000000000000000000000000500000000000027115 0ustar0000000000000000[1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_expression.json0000755000000000000000000000000500000000000024354 0ustar0000000000000000[1+2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_hex_1_digit.json0000755000000000000000000000000500000000000024341 0ustar0000000000000000[0x1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_hex_2_digits.json0000755000000000000000000000000600000000000024526 0ustar0000000000000000[0x42]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_infinity.json0000755000000000000000000000001200000000000024004 0ustar0000000000000000[Infinity]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_invalid+-.json0000755000000000000000000000000700000000000023735 0ustar0000000000000000[0e+-1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_invalid-negative-real.json0000755000000000000000000000001500000000000026325 0ustar0000000000000000[-123.123foo]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_invalid-utf-8-in-bigger-int.json0000755000000000000000000000000600000000000027176 0ustar0000000000000000[123]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_invalid-utf-8-in-exponent.json0000755000000000000000000000000600000000000027007 0ustar0000000000000000[1e1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_invalid-utf-8-in-int.json0000755000000000000000000000000500000000000025740 0ustar0000000000000000[0] aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_minus_infinity.json0000755000000000000000000000001300000000000025220 0ustar0000000000000000[-Infinity]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_minus_sign_with_trailing_garbage.json0000755000000000000000000000000600000000000030725 0ustar0000000000000000[-foo]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_minus_space_1.json0000755000000000000000000000000500000000000024703 0ustar0000000000000000[- 1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_neg_int_starting_with_zero.json0000755000000000000000000000000600000000000027606 0ustar0000000000000000[-012]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_neg_real_without_int_part.json0000755000000000000000000000000700000000000027416 0ustar0000000000000000[-.123]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_neg_with_garbage_at_end.json0000755000000000000000000000000500000000000026743 0ustar0000000000000000[-1x]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_real_garbage_after_e.json0000755000000000000000000000000500000000000026235 0ustar0000000000000000[1ea]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_real_with_invalid_utf8_after_e.json0000755000000000000000000000000500000000000030274 0ustar0000000000000000[1e]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_real_without_fractional_part.json0000755000000000000000000000000400000000000030112 0ustar0000000000000000[1.]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_starting_with_dot.json0000755000000000000000000000000600000000000025712 0ustar0000000000000000[.123]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_then_00.json0000755000000000000000000000000200000000000023407 0ustar00000000000000001aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_with_alpha.json0000755000000000000000000000001000000000000024271 0ustar0000000000000000[1.2a-3]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_with_alpha_char.json0000755000000000000000000000003100000000000025271 0ustar0000000000000000[1.8011670033376514H-308]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_number_with_leading_zero.json0000755000000000000000000000000500000000000025652 0ustar0000000000000000[012]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_bad_value.json0000755000000000000000000000001400000000000024055 0ustar0000000000000000["x", truth]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_bracket_key.json0000755000000000000000000000001100000000000024413 0ustar0000000000000000{[: "x"} aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_comma_instead_of_colon.json0000755000000000000000000000001300000000000026613 0ustar0000000000000000{"x", null}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_double_colon.json0000755000000000000000000000001200000000000024575 0ustar0000000000000000{"x"::"b"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_emoji.json0000755000000000000000000000001200000000000023234 0ustar0000000000000000{🇨🇭}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_garbage_at_end.json0000755000000000000000000000001500000000000025036 0ustar0000000000000000{"a":"a" 123}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_key_with_single_quotes.json0000755000000000000000000000001600000000000026721 0ustar0000000000000000{key: 'value'}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_missing_colon.json0000755000000000000000000000000700000000000025000 0ustar0000000000000000{"a" b}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_missing_key.json0000755000000000000000000000000600000000000024455 0ustar0000000000000000{:"b"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_missing_semicolon.json0000755000000000000000000000001100000000000025651 0ustar0000000000000000{"a" "b"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_missing_value.json0000755000000000000000000000000500000000000025000 0ustar0000000000000000{"a":aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_no-colon.json0000755000000000000000000000000400000000000023656 0ustar0000000000000000{"a"aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_non_string_key.json0000755000000000000000000000000500000000000025163 0ustar0000000000000000{1:1}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_non_string_key_but_huge_number_instead.json0000755000000000000000000000001500000000000032125 0ustar0000000000000000{9999E9999:1}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_pi_in_key_and_trailing_comma.json0000755000000000000000000000001200000000000027766 0ustar0000000000000000{"":"0",}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_repeated_null_null.json0000755000000000000000000000002500000000000026012 0ustar0000000000000000{null:null,null:null}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_several_trailing_commas.json0000755000000000000000000000001500000000000027025 0ustar0000000000000000{"id":0,,,,,}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_single_quote.json0000755000000000000000000000000700000000000024633 0ustar0000000000000000{'a':0}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_trailing_comma.json0000755000000000000000000000001100000000000025115 0ustar0000000000000000{"id":0,}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_trailing_comment.json0000755000000000000000000000001500000000000025467 0ustar0000000000000000{"a":"b"}/**/aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_trailing_comment_open.json0000755000000000000000000000001600000000000026511 0ustar0000000000000000{"a":"b"}/**//aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_trailing_comment_slash_open.json0000755000000000000000000000001300000000000027700 0ustar0000000000000000{"a":"b"}//aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_trailing_comment_slash_open_incomplete.json0000755000000000000000000000001200000000000032116 0ustar0000000000000000{"a":"b"}/aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_two_commas_in_a_row.json0000755000000000000000000000002200000000000026157 0ustar0000000000000000{"a":"b",,"c":"d"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_unquoted_key.json0000755000000000000000000000001000000000000024643 0ustar0000000000000000{a: "b"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_unterminated-value.json0000755000000000000000000000000700000000000025746 0ustar0000000000000000{"a":"aaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_with_single_string.json0000755000000000000000000000002600000000000026040 0ustar0000000000000000{ "foo" : "bar", "a" }aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_object_with_trailing_garbage.json0000755000000000000000000000001200000000000026445 0ustar0000000000000000{"a":"b"}#aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_single_space.json0000755000000000000000000000000100000000000023235 0ustar0000000000000000 aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_1_surrogate_then_escape u.json0000755000000000000000000000001400000000000027211 0ustar0000000000000000["\uD800\u"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_1_surrogate_then_escape u1.json0000755000000000000000000000001500000000000027273 0ustar0000000000000000["\uD800\u1"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_1_surrogate_then_escape u1x.json0000755000000000000000000000001600000000000027464 0ustar0000000000000000["\uD800\u1x"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_1_surrogate_then_escape.json0000755000000000000000000000001300000000000026763 0ustar0000000000000000["\uD800\"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_UTF8_surrogate_U+D800.json0000755000000000000000000000000700000000000025711 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_accentuated_char_no_quotes.json0000755000000000000000000000000400000000000027543 0ustar0000000000000000[é]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_backslash_00.json0000755000000000000000000000000600000000000024426 0ustar0000000000000000["\"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_escape_x.json0000755000000000000000000000001000000000000023756 0ustar0000000000000000["\x00"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_escaped_backslash_bad.json0000755000000000000000000000000700000000000026422 0ustar0000000000000000["\\\"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_escaped_ctrl_char_tab.json0000755000000000000000000000000600000000000026447 0ustar0000000000000000["\ "]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_escaped_emoji.json0000755000000000000000000000001100000000000024757 0ustar0000000000000000["\🌀"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_incomplete_escape.json0000755000000000000000000000000500000000000025652 0ustar0000000000000000["\"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_incomplete_escaped_character.json0000755000000000000000000000001100000000000030027 0ustar0000000000000000["\u00A"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_incomplete_surrogate.json0000755000000000000000000000001600000000000026427 0ustar0000000000000000["\uD834\uDd"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_incomplete_surrogate_escape_invalid.json0000755000000000000000000000002200000000000031452 0ustar0000000000000000["\uD800\uD800\x"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_invalid-utf-8-in-escape.json0000755000000000000000000000000700000000000026426 0ustar0000000000000000["\u"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_invalid_backslash_esc.json0000755000000000000000000000000600000000000026467 0ustar0000000000000000["\a"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_invalid_unicode_escape.json0000755000000000000000000000001200000000000026645 0ustar0000000000000000["\uqqqq"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_invalid_utf-8.json0000755000000000000000000000000500000000000024644 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_invalid_utf8_after_escape.json0000755000000000000000000000000600000000000027271 0ustar0000000000000000["\"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_iso_latin_1.json0000755000000000000000000000000500000000000024374 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_leading_uescaped_thinspace.json0000755000000000000000000000001500000000000027506 0ustar0000000000000000[\u0020"asd"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_lone_utf8_continuation_byte.json0000755000000000000000000000000500000000000027713 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_no_quotes_with_bad_escape.json0000755000000000000000000000000400000000000027367 0ustar0000000000000000[\n]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_overlong_sequence_2_bytes.json0000755000000000000000000000000600000000000027346 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_overlong_sequence_6_bytes.json0000755000000000000000000000001200000000000027347 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_overlong_sequence_6_bytes_null.json0000755000000000000000000000001200000000000030401 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_single_doublequote.json0000755000000000000000000000000100000000000026060 0ustar0000000000000000"aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_single_quote.json0000755000000000000000000000002000000000000024666 0ustar0000000000000000['single quote']aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_single_string_no_double_quotes.json0000755000000000000000000000000300000000000030466 0ustar0000000000000000abcaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_start_escape_unclosed.json0000755000000000000000000000000300000000000026542 0ustar0000000000000000["\aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_unescaped_crtl_char.json0000755000000000000000000000000700000000000026165 0ustar0000000000000000["aa"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_unescaped_newline.json0000755000000000000000000000001400000000000025663 0ustar0000000000000000["new line"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_unescaped_tab.json0000755000000000000000000000000500000000000024770 0ustar0000000000000000[" "]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_unicode_CapitalU.json0000755000000000000000000000001000000000000025377 0ustar0000000000000000"\UA66D"aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_string_with_trailing_garbage.json0000755000000000000000000000000300000000000026505 0ustar0000000000000000""xaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_100000_opening_arrays.json0000755000000000000000000030324000000000000026554 0ustar0000000000000000[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[[aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_U+2060_word_joined.json0000755000000000000000000000000500000000000026077 0ustar0000000000000000[⁠]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_UTF8_BOM_no_data.json0000755000000000000000000000000300000000000025633 0ustar0000000000000000aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_array_trailing_garbage.json0000755000000000000000000000000400000000000027403 0ustar0000000000000000[1]xaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_array_with_extra_array_close.json0000755000000000000000000000000400000000000030663 0ustar0000000000000000[1]]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_array_with_unclosed_string.json0000755000000000000000000000000600000000000030361 0ustar0000000000000000["asd]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_ascii-unicode-identifier.json0000755000000000000000000000000300000000000027557 0ustar0000000000000000aåaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_capitalized_True.json0000755000000000000000000000000600000000000026216 0ustar0000000000000000[True]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_close_unopened_array.json0000755000000000000000000000000200000000000027122 0ustar00000000000000001]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_comma_instead_of_closing_brace.json0000755000000000000000000000001300000000000031065 0ustar0000000000000000{"x": true,aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_double_array.json0000755000000000000000000000000400000000000025374 0ustar0000000000000000[][]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_end_array.json0000755000000000000000000000000100000000000024665 0ustar0000000000000000]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_incomplete_UTF8_BOM.json0000755000000000000000000000000400000000000026366 0ustar0000000000000000{}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_lone-invalid-utf-8.json0000755000000000000000000000000100000000000026243 0ustar0000000000000000aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_lone-open-bracket.json0000755000000000000000000000000100000000000026226 0ustar0000000000000000[aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_no_data.json0000755000000000000000000000000000000000000024325 0ustar0000000000000000aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_null-byte-outside-string.json0000755000000000000000000000000300000000000027614 0ustar0000000000000000[]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_null.json0000755000000000000000000000001000000000000023673 0ustar0000000000000000[]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_number_with_trailing_garbage.json0000755000000000000000000000000200000000000030606 0ustar00000000000000002@aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_object_followed_by_closing_object.json0000755000000000000000000000000300000000000031622 0ustar0000000000000000{}}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_object_unclosed_no_value.json0000755000000000000000000000000400000000000027756 0ustar0000000000000000{"":aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_object_with_comment.json0000755000000000000000000000002400000000000026751 0ustar0000000000000000{"a":/*comment*/"b"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_object_with_trailing_garbage.json0000755000000000000000000000001700000000000030572 0ustar0000000000000000{"a": true} "x"aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_array_apostrophe.json0000755000000000000000000000000200000000000027325 0ustar0000000000000000['aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_array_comma.json0000755000000000000000000000000200000000000026235 0ustar0000000000000000[,aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_array_object.json0000755000000000000000000075022100000000000026426 0ustar0000000000000000[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"":[{"": aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_array_open_object.json0000755000000000000000000000000200000000000027430 0ustar0000000000000000[{aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_array_open_string.json0000755000000000000000000000000300000000000027471 0ustar0000000000000000["aaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_array_string.json0000755000000000000000000000000400000000000026451 0ustar0000000000000000["a"aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_object.json0000755000000000000000000000000100000000000025210 0ustar0000000000000000{aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_object_close_array.json0000755000000000000000000000000200000000000027574 0ustar0000000000000000{]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_object_comma.json0000755000000000000000000000000200000000000026365 0ustar0000000000000000{,aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_object_open_array.json0000755000000000000000000000000200000000000027430 0ustar0000000000000000{[aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_object_open_string.json0000755000000000000000000000000300000000000027621 0ustar0000000000000000{"aaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_object_string_with_apostrophes.json0000755000000000000000000000000400000000000032263 0ustar0000000000000000{'a'aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_open_open.json0000755000000000000000000000002000000000000024704 0ustar0000000000000000["\{["\{["\{["\{aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_single_point.json0000755000000000000000000000000100000000000025413 0ustar0000000000000000aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_single_star.json0000755000000000000000000000000100000000000025233 0ustar0000000000000000*aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_trailing_#.json0000755000000000000000000000001400000000000024740 0ustar0000000000000000{"a":"b"}#{}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_uescaped_LF_before_string.json0000755000000000000000000000001200000000000030005 0ustar0000000000000000[\u000A""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_unclosed_array.json0000755000000000000000000000000200000000000025734 0ustar0000000000000000[1aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_unclosed_array_partial_null.json0000755000000000000000000000001400000000000030505 0ustar0000000000000000[ false, nulaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_unclosed_array_unfinished_false.json0000755000000000000000000000001400000000000031325 0ustar0000000000000000[ true, falsaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_unclosed_array_unfinished_true.json0000755000000000000000000000001400000000000031212 0ustar0000000000000000[ false, truaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_unclosed_object.json0000755000000000000000000000001400000000000026067 0ustar0000000000000000{"asd":"asd"aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_unicode-identifier.json0000755000000000000000000000000200000000000026470 0ustar0000000000000000åaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_whitespace_U+2060_word_joiner.json0000755000000000000000000000000500000000000030331 0ustar0000000000000000[⁠]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/n_structure_whitespace_formfeed.json0000755000000000000000000000000300000000000026726 0ustar0000000000000000[ ]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_arraysWithSpaces.json0000755000000000000000000000000700000000000025314 0ustar0000000000000000[[] ]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_empty-string.json0000755000000000000000000000000400000000000024457 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_empty.json0000755000000000000000000000000200000000000023151 0ustar0000000000000000[]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_ending_with_newline.json0000755000000000000000000000000500000000000026036 0ustar0000000000000000["a"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_false.json0000755000000000000000000000000700000000000023112 0ustar0000000000000000[false]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_heterogeneous.json0000755000000000000000000000002200000000000024671 0ustar0000000000000000[null, 1, "1", {}]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_null.json0000755000000000000000000000000600000000000022771 0ustar0000000000000000[null]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_with_1_and_newline.json0000755000000000000000000000000400000000000025553 0ustar0000000000000000[1 ]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_with_leading_space.json0000755000000000000000000000000400000000000025626 0ustar0000000000000000 [1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_with_several_null.json0000755000000000000000000000002400000000000025545 0ustar0000000000000000[1,null,null,null,2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_array_with_trailing_space.json0000755000000000000000000000000400000000000026034 0ustar0000000000000000[2] aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number.json0000755000000000000000000000001000000000000022104 0ustar0000000000000000[123e65]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_0e+1.json0000755000000000000000000000000600000000000022631 0ustar0000000000000000[0e+1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_0e1.json0000755000000000000000000000000500000000000022555 0ustar0000000000000000[0e1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_after_space.json0000755000000000000000000000000400000000000024443 0ustar0000000000000000[ 4]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_double_close_to_zero.json0000755000000000000000000000012400000000000026372 0ustar0000000000000000[-0.000000000000000000000000000000000000000000000000000000000000000000000000000001] aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_double_huge_neg_exp.json0000755000000000000000000000001600000000000026161 0ustar0000000000000000[123.456e-789]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_huge_exp.json0000755000000000000000000000021100000000000023773 0ustar0000000000000000[0.4e00669999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999999969999999006]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_int_with_exp.json0000755000000000000000000000000600000000000024672 0ustar0000000000000000[20e1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_minus_zero.json0000755000000000000000000000000400000000000024361 0ustar0000000000000000[-0]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_neg_int_huge_exp.json0000755000000000000000000000001200000000000025475 0ustar0000000000000000[-1e+9999]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_negative_int.json0000755000000000000000000000000600000000000024645 0ustar0000000000000000[-123]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_negative_one.json0000755000000000000000000000000400000000000024632 0ustar0000000000000000[-1]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_negative_zero.json0000755000000000000000000000000400000000000025030 0ustar0000000000000000[-0]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_pos_double_huge_exp.json0000755000000000000000000000001300000000000026206 0ustar0000000000000000[1.5e+9999]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_capital_e.json0000755000000000000000000000000600000000000025115 0ustar0000000000000000[1E22]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_capital_e_neg_exp.json0000755000000000000000000000000600000000000026622 0ustar0000000000000000[1E-2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_capital_e_pos_exp.json0000755000000000000000000000000600000000000026652 0ustar0000000000000000[1E+2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_exponent.json0000755000000000000000000000001000000000000025027 0ustar0000000000000000[123e45]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_fraction_exponent.json0000755000000000000000000000001400000000000026720 0ustar0000000000000000[123.456e78]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_neg_exp.json0000755000000000000000000000000600000000000024621 0ustar0000000000000000[1e-2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_neg_overflow.json0000755000000000000000000000002000000000000025664 0ustar0000000000000000[-123123e100000]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_pos_exponent.json0000755000000000000000000000000600000000000025715 0ustar0000000000000000[1e+2]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_pos_overflow.json0000755000000000000000000000001700000000000025722 0ustar0000000000000000[123123e100000]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_real_underflow.json0000755000000000000000000000001700000000000025203 0ustar0000000000000000[123e-10000000]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_simple_int.json0000755000000000000000000000000500000000000024333 0ustar0000000000000000[123]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_simple_real.json0000755000000000000000000000001400000000000024464 0ustar0000000000000000[123.456789]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_too_big_neg_int.json0000755000000000000000000000004100000000000025315 0ustar0000000000000000[-123123123123123123123123123123]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_too_big_pos_int.json0000755000000000000000000000002700000000000025351 0ustar0000000000000000[100000000000000000000]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_number_very_big_negative_int.json0000755000000000000000000000006300000000000026536 0ustar0000000000000000[-237462374673276894279832749832423479823246327846]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object.json0000755000000000000000000000003200000000000022066 0ustar0000000000000000{"asd":"sdf", "dfg":"fgh"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_basic.json0000755000000000000000000000001500000000000023230 0ustar0000000000000000{"asd":"sdf"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_duplicated_key.json0000755000000000000000000000002100000000000025132 0ustar0000000000000000{"a":"b","a":"c"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_duplicated_key_and_value.json0000755000000000000000000000002100000000000027150 0ustar0000000000000000{"a":"b","a":"b"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_empty.json0000755000000000000000000000000200000000000023301 0ustar0000000000000000{}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_empty_key.json0000755000000000000000000000000600000000000024155 0ustar0000000000000000{"":0}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_escaped_null_in_key.json0000755000000000000000000000002400000000000026143 0ustar0000000000000000{"foo\u0000bar": 42}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_extreme_numbers.json0000755000000000000000000000004400000000000025355 0ustar0000000000000000{ "min": -1.0e+28, "max": 1.0e+28 } aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_long_strings.json0000755000000000000000000000015400000000000024663 0ustar0000000000000000{"x":[{"id": "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx"}], "id": "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx"}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_simple.json0000755000000000000000000000001000000000000023433 0ustar0000000000000000{"a":[]}aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_string_unicode.json0000755000000000000000000000015600000000000025171 0ustar0000000000000000{"title":"\u041f\u043e\u043b\u0442\u043e\u0440\u0430 \u0417\u0435\u043c\u043b\u0435\u043a\u043e\u043f\u0430" }aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_object_with_newlines.json0000755000000000000000000000001400000000000025025 0ustar0000000000000000{ "a": "b" }aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_1_2_3_bytes_UTF-8_sequences.json0000755000000000000000000000002600000000000027160 0ustar0000000000000000["\u0060\u012a\u12AB"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_accepted_surrogate_pair.json0000755000000000000000000000002000000000000027061 0ustar0000000000000000["\uD801\udc37"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_accepted_surrogate_pairs.json0000755000000000000000000000003400000000000027251 0ustar0000000000000000["\ud83d\ude39\ud83d\udc8d"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_allowed_escapes.json0000755000000000000000000000002400000000000025341 0ustar0000000000000000["\"\\\/\b\f\n\r\t"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_backslash_and_u_escaped_zero.json0000755000000000000000000000001300000000000030031 0ustar0000000000000000["\\u0000"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_backslash_doublequotes.json0000755000000000000000000000000600000000000026735 0ustar0000000000000000["\""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_comments.json0000755000000000000000000000002100000000000024031 0ustar0000000000000000["a/*b*/c/*d//e"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_double_escape_a.json0000755000000000000000000000000700000000000025302 0ustar0000000000000000["\\a"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_double_escape_n.json0000755000000000000000000000000700000000000025317 0ustar0000000000000000["\\n"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_escaped_control_character.json0000755000000000000000000000001200000000000027364 0ustar0000000000000000["\u0012"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_escaped_noncharacter.json0000755000000000000000000000001200000000000026337 0ustar0000000000000000["\uFFFF"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_in_array.json0000755000000000000000000000000700000000000024014 0ustar0000000000000000["asd"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_in_array_with_leading_space.json0000755000000000000000000000001000000000000027677 0ustar0000000000000000[ "asd"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_last_surrogates_1_and_2.json0000755000000000000000000000002000000000000026707 0ustar0000000000000000["\uDBFF\uDFFF"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_newline_uescaped.json0000755000000000000000000000002100000000000025516 0ustar0000000000000000["new\u00A0line"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_nonCharacterInUTF-8_U+10FFFF.json0000755000000000000000000000001000000000000026754 0ustar0000000000000000["􏿿"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_nonCharacterInUTF-8_U+1FFFF.json0000755000000000000000000000001000000000000026674 0ustar0000000000000000["𛿿"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_nonCharacterInUTF-8_U+FFFF.json0000755000000000000000000000000700000000000026621 0ustar0000000000000000["￿"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_null_escape.json0000755000000000000000000000001200000000000024476 0ustar0000000000000000["\u0000"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_one-byte-utf-8.json0000755000000000000000000000001200000000000024667 0ustar0000000000000000["\u002c"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_pi.json0000755000000000000000000000000600000000000022617 0ustar0000000000000000["π"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_simple_ascii.json0000755000000000000000000000001000000000000024643 0ustar0000000000000000["asd "]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_space.json0000755000000000000000000000000300000000000023277 0ustar0000000000000000" "tests/JSONTestSuite/test_parsing/y_string_surrogates_U+1D11E_MUSICAL_SYMBOL_G_CLEF.json0000755000000000000000000000002000000000000030616 0ustar0000000000000000aeson-1.4.2.0["\uD834\uDd1e"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_three-byte-utf-8.json0000755000000000000000000000001200000000000025215 0ustar0000000000000000["\u0821"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_two-byte-utf-8.json0000755000000000000000000000001200000000000024717 0ustar0000000000000000["\u0123"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_u+2028_line_sep.json0000755000000000000000000000000700000000000024721 0ustar0000000000000000["
"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_u+2029_par_sep.json0000755000000000000000000000000700000000000024555 0ustar0000000000000000["
"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_uEscape.json0000755000000000000000000000003400000000000023575 0ustar0000000000000000["\u0061\u30af\u30EA\u30b9"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_unescaped_char_delete.json0000755000000000000000000000000500000000000026474 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_unicode.json0000755000000000000000000000001200000000000023632 0ustar0000000000000000["\uA66D"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_unicodeEscapedBackslash.json0000755000000000000000000000001200000000000026733 0ustar0000000000000000["\u005C"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_unicode_2.json0000755000000000000000000000001500000000000024056 0ustar0000000000000000["⍂㈴⍂"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_unicode_U+200B_ZERO_WIDTH_SPACE.json0000755000000000000000000000001200000000000027226 0ustar0000000000000000["\u200B"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_unicode_U+2064_invisible_plus.json0000755000000000000000000000001200000000000027614 0ustar0000000000000000["\u2064"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_unicode_escaped_double_quote.json0000755000000000000000000000001200000000000030065 0ustar0000000000000000["\u0022"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_utf16BE_no_BOM.json0000755000000000000000000000001200000000000024551 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_utf16LE_no_BOM.json0000755000000000000000000000001200000000000024563 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_utf8.json0000755000000000000000000000001300000000000023073 0ustar0000000000000000["€𝄞"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_string_with_del_character.json0000755000000000000000000000000700000000000026023 0ustar0000000000000000["aa"]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_lonely_false.json0000755000000000000000000000000500000000000025414 0ustar0000000000000000falseaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_lonely_int.json0000755000000000000000000000000200000000000025111 0ustar000000000000000042aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_lonely_negative_real.json0000755000000000000000000000000400000000000027126 0ustar0000000000000000-0.1aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_lonely_null.json0000755000000000000000000000000400000000000025273 0ustar0000000000000000nullaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_lonely_string.json0000755000000000000000000000000500000000000025630 0ustar0000000000000000"asd"aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_lonely_true.json0000755000000000000000000000000400000000000025300 0ustar0000000000000000trueaeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_string_empty.json0000755000000000000000000000000200000000000025461 0ustar0000000000000000""aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_trailing_newline.json0000755000000000000000000000000600000000000026273 0ustar0000000000000000["a"] aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_true_in_array.json0000755000000000000000000000000600000000000025604 0ustar0000000000000000[true]aeson-1.4.2.0/tests/JSONTestSuite/test_parsing/y_structure_whitespace_array.json0000755000000000000000000000000400000000000026271 0ustar0000000000000000 [] aeson-1.4.2.0/tests/JSONTestSuite/test_transform/0000755000000000000000000000000000000000000017747 5ustar0000000000000000aeson-1.4.2.0/tests/JSONTestSuite/test_transform/number_1000000000000000.json0000755000000000000000000000002300000000000023670 0ustar0000000000000000[1000000000000000] aeson-1.4.2.0/tests/JSONTestSuite/test_transform/number_10000000000000000999.json0000755000000000000000000000002600000000000024226 0ustar0000000000000000[10000000000000000999]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/number_1e-999.json0000755000000000000000000000001000000000000023041 0ustar0000000000000000[1E-999]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/number_1e6.json0000755000000000000000000000000500000000000022603 0ustar0000000000000000[1E6]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/object_key_nfc_nfd.json0000755000000000000000000000003000000000000024431 0ustar0000000000000000{"é":"NFC","é":"NFD"}aeson-1.4.2.0/tests/JSONTestSuite/test_transform/object_key_nfd_nfc.json0000755000000000000000000000003000000000000024431 0ustar0000000000000000{"é":"NFD","é":"NFC"}aeson-1.4.2.0/tests/JSONTestSuite/test_transform/object_same_key_different_values.json0000755000000000000000000000001500000000000027371 0ustar0000000000000000{"a":1,"a":2}aeson-1.4.2.0/tests/JSONTestSuite/test_transform/object_same_key_same_value.json0000755000000000000000000000001500000000000026165 0ustar0000000000000000{"a":1,"a":1}aeson-1.4.2.0/tests/JSONTestSuite/test_transform/object_same_key_unclear_values.json0000755000000000000000000000002000000000000027050 0ustar0000000000000000{"a":0, "a":-0} aeson-1.4.2.0/tests/JSONTestSuite/test_transform/string_1_escaped_invalid_codepoint.json0000755000000000000000000000001200000000000027622 0ustar0000000000000000["\uD800"]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/string_1_invalid_codepoint.json0000755000000000000000000000000700000000000026142 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/string_2_escaped_invalid_codepoints.json0000755000000000000000000000002000000000000030005 0ustar0000000000000000["\uD800\uD800"]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/string_2_invalid_codepoints.json0000755000000000000000000000001200000000000026322 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/string_3_escaped_invalid_codepoints.json0000755000000000000000000000002600000000000030014 0ustar0000000000000000["\uD800\uD800\uD800"]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/string_3_invalid_codepoints.json0000755000000000000000000000001500000000000026326 0ustar0000000000000000[""]aeson-1.4.2.0/tests/JSONTestSuite/test_transform/string_with_escaped_NULL.json0000755000000000000000000000001400000000000025517 0ustar0000000000000000["A\u0000B"]aeson-1.4.2.0/tests/Options.hs0000644000000000000000000000316300000000000014244 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Options (module Options) where import Prelude.Compat import Data.Aeson.Types import Data.Char optsDefault :: Options optsDefault = defaultOptions { fieldLabelModifier = map toLower , constructorTagModifier = map toLower } opts2ElemArray :: Options opts2ElemArray = optsDefault { allNullaryToStringTag = False , sumEncoding = TwoElemArray } optsUnwrapUnaryRecords :: Options optsUnwrapUnaryRecords = optsDefault { unwrapUnaryRecords = True } optsTaggedObject :: Options optsTaggedObject = optsDefault { allNullaryToStringTag = False } optsObjectWithSingleField :: Options optsObjectWithSingleField = optsDefault { allNullaryToStringTag = False , sumEncoding = ObjectWithSingleField } optsOmitNothingFields :: Options optsOmitNothingFields = optsDefault { omitNothingFields = True } optsUntaggedValue :: Options optsUntaggedValue = optsDefault { sumEncoding = UntaggedValue } optsTagSingleConstructors :: Options optsTagSingleConstructors = optsDefault { tagSingleConstructors = True , allNullaryToStringTag = False } optsOptionField :: Options optsOptionField = optsDefault { fieldLabelModifier = const "field" , omitNothingFields = True } aeson-1.4.2.0/tests/Properties.hs0000644000000000000000000006553300000000000014756 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} -- For arbitrary Compose {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} module Properties (module Properties) where import Prelude.Compat import Control.Applicative (Const) import Data.Aeson (eitherDecode, encode) import Data.Aeson.Encoding (encodingToLazyByteString) import Data.Aeson.Internal (IResult(..), formatError, ifromJSON, iparse) import qualified Data.Aeson.Internal as I import Data.Aeson.Parser (value) import Data.Aeson.Types import Data.DList (DList) import Data.Functor.Compose (Compose (..)) import Data.HashMap.Strict (HashMap) import Data.Hashable (Hashable) import Data.Int (Int8) import Data.List.NonEmpty (NonEmpty) import Data.Map (Map) import Data.Proxy (Proxy) import Data.Ratio (Ratio) import Data.Semigroup (Option(..)) import Data.Sequence (Seq) import Data.Tagged (Tagged) import Data.Time (Day, DiffTime, LocalTime, NominalDiffTime, TimeOfDay, UTCTime, ZonedTime) import Data.Version (Version) import Encoders import Instances () import Numeric.Natural (Natural) import Test.Tasty (TestTree, testGroup) import Test.Tasty.QuickCheck (testProperty) import Test.QuickCheck (Arbitrary(..), Property, Testable, (===), (.&&.), counterexample) import Types import qualified Data.Attoparsec.Lazy as L import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.HashMap.Strict as H import qualified Data.Map as Map import qualified Data.Text as T import qualified Data.Text.Lazy as LT import qualified Data.UUID.Types as UUID import qualified Data.Vector as V encodeDouble :: Double -> Double -> Property encodeDouble num denom | isInfinite d || isNaN d = encode d === "null" | otherwise = (read . L.unpack . encode) d === d where d = num / denom encodeInteger :: Integer -> Property encodeInteger i = encode i === L.pack (show i) toParseJSON :: (Eq a, Show a) => (Value -> Parser a) -> (a -> Value) -> a -> Property toParseJSON parsejson tojson x = case iparse parsejson . tojson $ x of IError path msg -> failure "parse" (formatError path msg) x ISuccess x' -> x === x' toParseJSON1 :: (Eq (f Int), Show (f Int)) => (forall a. LiftParseJSON f a) -> (forall a. LiftToJSON f a) -> f Int -> Property toParseJSON1 parsejson1 tojson1 = toParseJSON parsejson tojson where parsejson = parsejson1 parseJSON (listParser parseJSON) tojson = tojson1 toJSON (listValue toJSON) roundTripEnc :: (FromJSON a, ToJSON a, Show a) => (a -> a -> Property) -> a -> a -> Property roundTripEnc eq _ i = case fmap ifromJSON . L.parse value . encode $ i of L.Done _ (ISuccess v) -> v `eq` i L.Done _ (IError path err) -> failure "fromJSON" (formatError path err) i L.Fail _ _ err -> failure "parse" err i roundTripNoEnc :: (FromJSON a, ToJSON a, Show a) => (a -> a -> Property) -> a -> a -> Property roundTripNoEnc eq _ i = case ifromJSON . toJSON $ i of (ISuccess v) -> v `eq` i (IError path err) -> failure "fromJSON" (formatError path err) i roundTripEq :: (Eq a, FromJSON a, ToJSON a, Show a) => a -> a -> Property roundTripEq x y = roundTripEnc (===) x y .&&. roundTripNoEnc (===) x y -- We test keys by encoding HashMap and Map with it roundTripKey :: (Ord a, Hashable a, FromJSONKey a, ToJSONKey a, Show a) => a -> HashMap a Int -> Map a Int -> Property roundTripKey _ h m = roundTripEq h h .&&. roundTripEq m m infix 4 ==~ (==~) :: (ApproxEq a, Show a) => a -> a -> Property x ==~ y = counterexample (show x ++ " /= " ++ show y) (x =~ y) toFromJSON :: (Arbitrary a, Eq a, FromJSON a, ToJSON a, Show a) => a -> Property toFromJSON x = case ifromJSON (toJSON x) of IError path err -> failure "fromJSON" (formatError path err) x ISuccess x' -> x === x' modifyFailureProp :: String -> String -> Bool modifyFailureProp orig added = result == Error (added ++ orig) where parser = const $ modifyFailure (added ++) $ fail orig result :: Result () result = parse parser () parserThrowErrorProp :: String -> Property parserThrowErrorProp msg = result === Error msg where parser = const $ parserThrowError [] msg result :: Result () result = parse parser () -- | Tests (also) that we catch the JSONPath and it has elements in the right order. parserCatchErrorProp :: [String] -> String -> Property parserCatchErrorProp path msg = result === Success ([I.Key "outer", I.Key "inner"] ++ jsonPath, msg) where parser = parserCatchError outer (curry pure) outer = inner I. I.Key "outer" inner = parserThrowError jsonPath msg I. I.Key "inner" result :: Result (I.JSONPath, String) result = parse (const parser) () jsonPath = map (I.Key . T.pack) path -- | Perform a structural comparison of the results of two encoding -- methods. Compares decoded values to account for HashMap-driven -- variation in JSON object key ordering. sameAs :: (a -> Value) -> (a -> Encoding) -> a -> Property sameAs toVal toEnc v = counterexample (show s) $ eitherDecode s === Right (toVal v) where s = encodingToLazyByteString (toEnc v) sameAs1 :: (forall a. LiftToJSON f a) -> (forall a. LiftToEncoding f a) -> f Int -> Property sameAs1 toVal1 toEnc1 v = lhs === rhs where rhs = Right $ toVal1 toJSON (listValue toJSON) v lhs = eitherDecode . encodingToLazyByteString $ toEnc1 toEncoding (listEncoding toEncoding) v sameAs1Agree :: ToJSON a => (f a -> Encoding) -> (forall b. LiftToEncoding f b) -> f a -> Property sameAs1Agree toEnc toEnc1 v = rhs === lhs where rhs = encodingToLazyByteString $ toEnc v lhs = encodingToLazyByteString $ toEnc1 toEncoding (listEncoding toEncoding) v type P6 = Product6 Int Bool String (Approx Double) (Int, Approx Double) () type S4 = Sum4 Int8 ZonedTime T.Text (Map.Map String Int) -------------------------------------------------------------------------------- -- Value properties -------------------------------------------------------------------------------- -- | Add the formatted @Value@ to the printed counterexample when the property -- fails. checkValue :: Testable a => (Value -> a) -> Value -> Property checkValue prop v = counterexample (L.unpack (encode v)) (prop v) isString :: Value -> Bool isString (String _) = True isString _ = False is2ElemArray :: Value -> Bool is2ElemArray (Array v) = V.length v == 2 && isString (V.head v) is2ElemArray _ = False isTaggedObjectValue :: Value -> Bool isTaggedObjectValue (Object obj) = "tag" `H.member` obj && "contents" `H.member` obj isTaggedObjectValue _ = False isNullaryTaggedObject :: Value -> Bool isNullaryTaggedObject obj = isTaggedObject' obj && isObjectWithSingleField obj isTaggedObject :: Value -> Property isTaggedObject = checkValue isTaggedObject' isTaggedObject' :: Value -> Bool isTaggedObject' (Object obj) = "tag" `H.member` obj isTaggedObject' _ = False isObjectWithSingleField :: Value -> Bool isObjectWithSingleField (Object obj) = H.size obj == 1 isObjectWithSingleField _ = False -- | is untaggedValue of EitherTextInt isUntaggedValueETI :: Value -> Bool isUntaggedValueETI (String s) | s == "nonenullary" = True isUntaggedValueETI (Bool _) = True isUntaggedValueETI (Number _) = True isUntaggedValueETI (Array a) = length a == 2 isUntaggedValueETI _ = False isEmptyArray :: Value -> Property isEmptyArray = checkValue isEmptyArray' isEmptyArray' :: Value -> Bool isEmptyArray' = (Array mempty ==) -------------------------------------------------------------------------------- tests :: TestTree tests = testGroup "properties" [ testGroup "encode" [ testProperty "encodeDouble" encodeDouble , testProperty "encodeInteger" encodeInteger ] , testGroup "roundTrip" [ testProperty "Bool" $ roundTripEq True , testProperty "Double" $ roundTripEq (1 :: Approx Double) , testProperty "Int" $ roundTripEq (1 :: Int) , testProperty "NonEmpty Char" $ roundTripEq (undefined :: NonEmpty Char) , testProperty "Integer" $ roundTripEq (1 :: Integer) , testProperty "String" $ roundTripEq ("" :: String) , testProperty "Text" $ roundTripEq T.empty , testProperty "Lazy Text" $ roundTripEq LT.empty , testProperty "Foo" $ roundTripEq (undefined :: Foo) , testProperty "Day" $ roundTripEq (undefined :: Day) , testProperty "BCE Day" $ roundTripEq (undefined :: BCEDay) , testProperty "DotNetTime" $ roundTripEq (undefined :: Approx DotNetTime) , testProperty "LocalTime" $ roundTripEq (undefined :: LocalTime) , testProperty "TimeOfDay" $ roundTripEq (undefined :: TimeOfDay) , testProperty "UTCTime" $ roundTripEq (undefined :: UTCTime) , testProperty "ZonedTime" $ roundTripEq (undefined :: ZonedTime) , testProperty "NominalDiffTime" $ roundTripEq (undefined :: NominalDiffTime) , testProperty "DiffTime" $ roundTripEq (undefined :: DiffTime) , testProperty "Version" $ roundTripEq (undefined :: Version) , testProperty "Natural" $ roundTripEq (undefined :: Natural) , testProperty "Proxy" $ roundTripEq (undefined :: Proxy Int) , testProperty "Tagged" $ roundTripEq (undefined :: Tagged Int Char) , testProperty "Const" $ roundTripEq (undefined :: Const Int Char) , testProperty "DList" $ roundTripEq (undefined :: DList Int) , testProperty "Seq" $ roundTripEq (undefined :: Seq Int) , testProperty "Rational" $ roundTripEq (undefined :: Rational) , testProperty "Ratio Int" $ roundTripEq (undefined :: Ratio Int) , testProperty "UUID" $ roundTripEq UUID.nil , testGroup "functors" [ testProperty "Identity Char" $ roundTripEq (undefined :: I Int) , testProperty "Identity Char" $ roundTripEq (undefined :: I Char) , testProperty "Identity [Char]" $ roundTripEq (undefined :: I String) , testProperty "[Identity Char]" $ roundTripEq (undefined :: [I Char]) , testProperty "Compose I I Int" $ roundTripEq (undefined :: LogScaled (Compose I I Int)) , testProperty "Compose [] I Int" $ roundTripEq (undefined :: LogScaled (Compose [] I Int)) , testProperty "Compose I [] Int" $ roundTripEq (undefined :: LogScaled (Compose I [] Int)) , testProperty "Compose [] [] Int" $ roundTripEq (undefined :: LogScaled (Compose [] [] Int)) , testProperty "Compose I I Char" $ roundTripEq (undefined :: LogScaled (Compose I I Char)) , testProperty "Compose [] I Char" $ roundTripEq (undefined :: LogScaled (Compose [] I Char)) , testProperty "Compose I [] Char" $ roundTripEq (undefined :: LogScaled (Compose I [] Char)) , testProperty "Compose [] [] Char" $ roundTripEq (undefined :: LogScaled (Compose [] [] Char)) , testProperty "Compose3 I I I Char" $ roundTripEq (undefined :: LogScaled (Compose3 I I I Char)) , testProperty "Compose3 I [] I Char" $ roundTripEq (undefined :: LogScaled (Compose3 I [] I Char)) , testProperty "Compose3 I I [] Char" $ roundTripEq (undefined :: LogScaled (Compose3 I I [] Char)) , testProperty "Compose3 I [] [] Char" $ roundTripEq (undefined :: LogScaled (Compose3 I [] [] Char)) , testProperty "Compose3 [] I I Char" $ roundTripEq (undefined :: LogScaled (Compose3 [] I I Char)) , testProperty "Compose3 [] [] I Char" $ roundTripEq (undefined :: LogScaled (Compose3 [] [] I Char)) , testProperty "Compose3 [] I [] Char" $ roundTripEq (undefined :: LogScaled (Compose3 [] I [] Char)) , testProperty "Compose3 [] [] [] Char" $ roundTripEq (undefined :: LogScaled (Compose3 [] [] [] Char)) , testProperty "Compose3' I I I Char" $ roundTripEq (undefined :: LogScaled (Compose3' I I I Char)) , testProperty "Compose3' I [] I Char" $ roundTripEq (undefined :: LogScaled (Compose3' I [] I Char)) , testProperty "Compose3' I I [] Char" $ roundTripEq (undefined :: LogScaled (Compose3' I I [] Char)) , testProperty "Compose3' I [] [] Char" $ roundTripEq (undefined :: LogScaled (Compose3' I [] [] Char)) , testProperty "Compose3' [] I I Char" $ roundTripEq (undefined :: LogScaled (Compose3' [] I I Char)) , testProperty "Compose3' [] [] I Char" $ roundTripEq (undefined :: LogScaled (Compose3' [] [] I Char)) , testProperty "Compose3' [] I [] Char" $ roundTripEq (undefined :: LogScaled (Compose3' [] I [] Char)) , testProperty "Compose3' [] [] [] Char" $ roundTripEq (undefined :: LogScaled (Compose3' [] [] [] Char)) ] , testGroup "ghcGenerics" [ testProperty "OneConstructor" $ roundTripEq OneConstructor , testProperty "Product2" $ roundTripEq (undefined :: Product2 Int Bool) , testProperty "Product6" $ roundTripEq (undefined :: P6) , testProperty "Sum4" $ roundTripEq (undefined :: S4) ] ] , testGroup "roundTrip Key" [ testProperty "Bool" $ roundTripKey True , testProperty "Text" $ roundTripKey (undefined :: T.Text) , testProperty "String" $ roundTripKey (undefined :: String) , testProperty "Int" $ roundTripKey (undefined :: Int) , testProperty "[Text]" $ roundTripKey (undefined :: LogScaled [T.Text]) , testProperty "(Int,Char)" $ roundTripKey (undefined :: (Int,Char)) , testProperty "Integer" $ roundTripKey (undefined :: Integer) , testProperty "Natural" $ roundTripKey (undefined :: Natural) , testProperty "Float" $ roundTripKey (undefined :: Float) , testProperty "Double" $ roundTripKey (undefined :: Double) #if MIN_VERSION_base(4,7,0) , testProperty "Day" $ roundTripKey (undefined :: Day) , testProperty "LocalTime" $ roundTripKey (undefined :: LocalTime) , testProperty "TimeOfDay" $ roundTripKey (undefined :: TimeOfDay) , testProperty "UTCTime" $ roundTripKey (undefined :: UTCTime) #endif , testProperty "Version" $ roundTripKey (undefined :: Version) , testProperty "Lazy Text" $ roundTripKey (undefined :: LT.Text) , testProperty "UUID" $ roundTripKey UUID.nil ] , testGroup "toFromJSON" [ testProperty "Integer" (toFromJSON :: Integer -> Property) , testProperty "Double" (toFromJSON :: Double -> Property) , testProperty "Maybe Integer" (toFromJSON :: Maybe Integer -> Property) , testProperty "Either Integer Double" (toFromJSON :: Either Integer Double -> Property) , testProperty "Either Integer Integer" (toFromJSON :: Either Integer Integer -> Property) ] , testGroup "failure messages" [ testProperty "modify failure" modifyFailureProp , testProperty "parserThrowError" parserThrowErrorProp , testProperty "parserCatchError" parserCatchErrorProp ] , testGroup "generic" [ testGroup "toJSON" [ testGroup "Nullary" [ testProperty "string" (isString . gNullaryToJSONString) , testProperty "2ElemArray" (is2ElemArray . gNullaryToJSON2ElemArray) , testProperty "TaggedObject" (isNullaryTaggedObject . gNullaryToJSONTaggedObject) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . gNullaryToJSONObjectWithSingleField) , testGroup "roundTrip" [ testProperty "string" (toParseJSON gNullaryParseJSONString gNullaryToJSONString) , testProperty "2ElemArray" (toParseJSON gNullaryParseJSON2ElemArray gNullaryToJSON2ElemArray) , testProperty "TaggedObject" (toParseJSON gNullaryParseJSONTaggedObject gNullaryToJSONTaggedObject) , testProperty "ObjectWithSingleField" (toParseJSON gNullaryParseJSONObjectWithSingleField gNullaryToJSONObjectWithSingleField) ] ] , testGroup "EitherTextInt" [ testProperty "UntaggedValue" (isUntaggedValueETI . gEitherTextIntToJSONUntaggedValue) , testProperty "roundtrip" (toParseJSON gEitherTextIntParseJSONUntaggedValue gEitherTextIntToJSONUntaggedValue) ] , testGroup "SomeType" [ testProperty "2ElemArray" (is2ElemArray . gSomeTypeToJSON2ElemArray) , testProperty "TaggedObject" (isTaggedObject . gSomeTypeToJSONTaggedObject) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . gSomeTypeToJSONObjectWithSingleField) , testGroup "roundTrip" [ testProperty "2ElemArray" (toParseJSON gSomeTypeParseJSON2ElemArray gSomeTypeToJSON2ElemArray) , testProperty "TaggedObject" (toParseJSON gSomeTypeParseJSONTaggedObject gSomeTypeToJSONTaggedObject) , testProperty "ObjectWithSingleField" (toParseJSON gSomeTypeParseJSONObjectWithSingleField gSomeTypeToJSONObjectWithSingleField) #if __GLASGOW_HASKELL__ >= 706 , testProperty "2ElemArray unary" (toParseJSON1 gSomeTypeLiftParseJSON2ElemArray gSomeTypeLiftToJSON2ElemArray) , testProperty "TaggedObject unary" (toParseJSON1 gSomeTypeLiftParseJSONTaggedObject gSomeTypeLiftToJSONTaggedObject) , testProperty "ObjectWithSingleField unary" (toParseJSON1 gSomeTypeLiftParseJSONObjectWithSingleField gSomeTypeLiftToJSONObjectWithSingleField) #endif ] ] , testGroup "OneConstructor" [ testProperty "default" (isEmptyArray . gOneConstructorToJSONDefault) , testProperty "Tagged" (isTaggedObject . gOneConstructorToJSONTagged) , testGroup "roundTrip" [ testProperty "default" (toParseJSON gOneConstructorParseJSONDefault gOneConstructorToJSONDefault) , testProperty "Tagged" (toParseJSON gOneConstructorParseJSONTagged gOneConstructorToJSONTagged) ] ] , testGroup "OptionField" [ testProperty "like Maybe" $ \x -> gOptionFieldToJSON (OptionField (Option x)) === thMaybeFieldToJSON (MaybeField x) , testProperty "roundTrip" (toParseJSON gOptionFieldParseJSON gOptionFieldToJSON) ] ] , testGroup "toEncoding" [ testProperty "NullaryString" $ gNullaryToJSONString `sameAs` gNullaryToEncodingString , testProperty "Nullary2ElemArray" $ gNullaryToJSON2ElemArray `sameAs` gNullaryToEncoding2ElemArray , testProperty "NullaryTaggedObject" $ gNullaryToJSONTaggedObject `sameAs` gNullaryToEncodingTaggedObject , testProperty "NullaryObjectWithSingleField" $ gNullaryToJSONObjectWithSingleField `sameAs` gNullaryToEncodingObjectWithSingleField -- , testProperty "ApproxUnwrap" $ -- gApproxToJSONUnwrap `sameAs` gApproxToEncodingUnwrap , testProperty "ApproxDefault" $ gApproxToJSONDefault `sameAs` gApproxToEncodingDefault , testProperty "EitherTextInt UntaggedValue" $ gEitherTextIntToJSONUntaggedValue `sameAs` gEitherTextIntToEncodingUntaggedValue , testProperty "SomeType2ElemArray" $ gSomeTypeToJSON2ElemArray `sameAs` gSomeTypeToEncoding2ElemArray #if __GLASGOW_HASKELL__ >= 706 , testProperty "SomeType2ElemArray unary" $ gSomeTypeLiftToJSON2ElemArray `sameAs1` gSomeTypeLiftToEncoding2ElemArray , testProperty "SomeType2ElemArray unary agree" $ gSomeTypeToEncoding2ElemArray `sameAs1Agree` gSomeTypeLiftToEncoding2ElemArray #endif , testProperty "SomeTypeTaggedObject" $ gSomeTypeToJSONTaggedObject `sameAs` gSomeTypeToEncodingTaggedObject #if __GLASGOW_HASKELL__ >= 706 , testProperty "SomeTypeTaggedObject unary" $ gSomeTypeLiftToJSONTaggedObject `sameAs1` gSomeTypeLiftToEncodingTaggedObject , testProperty "SomeTypeTaggedObject unary agree" $ gSomeTypeToEncodingTaggedObject `sameAs1Agree` gSomeTypeLiftToEncodingTaggedObject #endif , testProperty "SomeTypeObjectWithSingleField" $ gSomeTypeToJSONObjectWithSingleField `sameAs` gSomeTypeToEncodingObjectWithSingleField #if __GLASGOW_HASKELL__ >= 706 , testProperty "SomeTypeObjectWithSingleField unary" $ gSomeTypeLiftToJSONObjectWithSingleField `sameAs1` gSomeTypeLiftToEncodingObjectWithSingleField , testProperty "SomeTypeObjectWithSingleField unary agree" $ gSomeTypeToEncodingObjectWithSingleField `sameAs1Agree` gSomeTypeLiftToEncodingObjectWithSingleField #endif , testProperty "SomeTypeOmitNothingFields" $ gSomeTypeToJSONOmitNothingFields `sameAs` gSomeTypeToEncodingOmitNothingFields , testProperty "OneConstructorDefault" $ gOneConstructorToJSONDefault `sameAs` gOneConstructorToEncodingDefault , testProperty "OneConstructorTagged" $ gOneConstructorToJSONTagged `sameAs` gOneConstructorToEncodingTagged , testProperty "OptionField" $ gOptionFieldToJSON `sameAs` gOptionFieldToEncoding ] ] , testGroup "template-haskell" [ testGroup "toJSON" [ testGroup "Nullary" [ testProperty "string" (isString . thNullaryToJSONString) , testProperty "2ElemArray" (is2ElemArray . thNullaryToJSON2ElemArray) , testProperty "TaggedObject" (isNullaryTaggedObject . thNullaryToJSONTaggedObject) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . thNullaryToJSONObjectWithSingleField) , testGroup "roundTrip" [ testProperty "string" (toParseJSON thNullaryParseJSONString thNullaryToJSONString) , testProperty "2ElemArray" (toParseJSON thNullaryParseJSON2ElemArray thNullaryToJSON2ElemArray) , testProperty "TaggedObject" (toParseJSON thNullaryParseJSONTaggedObject thNullaryToJSONTaggedObject) , testProperty "ObjectWithSingleField" (toParseJSON thNullaryParseJSONObjectWithSingleField thNullaryToJSONObjectWithSingleField) ] ] , testGroup "EitherTextInt" [ testProperty "UntaggedValue" (isUntaggedValueETI . thEitherTextIntToJSONUntaggedValue) , testProperty "roundtrip" (toParseJSON thEitherTextIntParseJSONUntaggedValue thEitherTextIntToJSONUntaggedValue) ] , testGroup "SomeType" [ testProperty "2ElemArray" (is2ElemArray . thSomeTypeToJSON2ElemArray) , testProperty "TaggedObject" (isTaggedObject . thSomeTypeToJSONTaggedObject) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . thSomeTypeToJSONObjectWithSingleField) , testGroup "roundTrip" [ testProperty "2ElemArray" (toParseJSON thSomeTypeParseJSON2ElemArray thSomeTypeToJSON2ElemArray) , testProperty "TaggedObject" (toParseJSON thSomeTypeParseJSONTaggedObject thSomeTypeToJSONTaggedObject) , testProperty "ObjectWithSingleField" (toParseJSON thSomeTypeParseJSONObjectWithSingleField thSomeTypeToJSONObjectWithSingleField) , testProperty "2ElemArray unary" (toParseJSON1 thSomeTypeLiftParseJSON2ElemArray thSomeTypeLiftToJSON2ElemArray) , testProperty "TaggedObject unary" (toParseJSON1 thSomeTypeLiftParseJSONTaggedObject thSomeTypeLiftToJSONTaggedObject) , testProperty "ObjectWithSingleField unary" (toParseJSON1 thSomeTypeLiftParseJSONObjectWithSingleField thSomeTypeLiftToJSONObjectWithSingleField) ] ] , testGroup "Approx" [ testProperty "string" (isString . thApproxToJSONUnwrap) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . thApproxToJSONDefault) , testGroup "roundTrip" [ testProperty "string" (toParseJSON thApproxParseJSONUnwrap thApproxToJSONUnwrap) , testProperty "ObjectWithSingleField" (toParseJSON thApproxParseJSONDefault thApproxToJSONDefault) ] ] , testGroup "GADT" [ testProperty "string" (isString . thGADTToJSONUnwrap) , testProperty "ObjectWithSingleField" (isObjectWithSingleField . thGADTToJSONDefault) , testGroup "roundTrip" [ testProperty "string" (toParseJSON thGADTParseJSONUnwrap thGADTToJSONUnwrap) , testProperty "ObjectWithSingleField" (toParseJSON thGADTParseJSONDefault thGADTToJSONDefault) ] ] , testGroup "OneConstructor" [ testProperty "default" (isEmptyArray . thOneConstructorToJSONDefault) , testProperty "Tagged" (isTaggedObject . thOneConstructorToJSONTagged) , testGroup "roundTrip" [ testProperty "default" (toParseJSON thOneConstructorParseJSONDefault thOneConstructorToJSONDefault) , testProperty "Tagged" (toParseJSON thOneConstructorParseJSONTagged thOneConstructorToJSONTagged) ] ] , testGroup "OptionField" [ testProperty "like Maybe" $ \x -> thOptionFieldToJSON (OptionField (Option x)) === thMaybeFieldToJSON (MaybeField x) , testProperty "roundTrip" (toParseJSON thOptionFieldParseJSON thOptionFieldToJSON) ] ] , testGroup "toEncoding" [ testProperty "NullaryString" $ thNullaryToJSONString `sameAs` thNullaryToEncodingString , testProperty "Nullary2ElemArray" $ thNullaryToJSON2ElemArray `sameAs` thNullaryToEncoding2ElemArray , testProperty "NullaryTaggedObject" $ thNullaryToJSONTaggedObject `sameAs` thNullaryToEncodingTaggedObject , testProperty "NullaryObjectWithSingleField" $ thNullaryToJSONObjectWithSingleField `sameAs` thNullaryToEncodingObjectWithSingleField , testProperty "ApproxUnwrap" $ thApproxToJSONUnwrap `sameAs` thApproxToEncodingUnwrap , testProperty "ApproxDefault" $ thApproxToJSONDefault `sameAs` thApproxToEncodingDefault , testProperty "EitherTextInt UntaggedValue" $ thEitherTextIntToJSONUntaggedValue `sameAs` thEitherTextIntToEncodingUntaggedValue , testProperty "SomeType2ElemArray" $ thSomeTypeToJSON2ElemArray `sameAs` thSomeTypeToEncoding2ElemArray , testProperty "SomeType2ElemArray unary" $ thSomeTypeLiftToJSON2ElemArray `sameAs1` thSomeTypeLiftToEncoding2ElemArray , testProperty "SomeType2ElemArray unary agree" $ thSomeTypeToEncoding2ElemArray `sameAs1Agree` thSomeTypeLiftToEncoding2ElemArray , testProperty "SomeTypeTaggedObject" $ thSomeTypeToJSONTaggedObject `sameAs` thSomeTypeToEncodingTaggedObject , testProperty "SomeTypeTaggedObject unary" $ thSomeTypeLiftToJSONTaggedObject `sameAs1` thSomeTypeLiftToEncodingTaggedObject , testProperty "SomeTypeTaggedObject unary agree" $ thSomeTypeToEncodingTaggedObject `sameAs1Agree` thSomeTypeLiftToEncodingTaggedObject , testProperty "SomeTypeObjectWithSingleField" $ thSomeTypeToJSONObjectWithSingleField `sameAs` thSomeTypeToEncodingObjectWithSingleField , testProperty "SomeTypeObjectWithSingleField unary" $ thSomeTypeLiftToJSONObjectWithSingleField `sameAs1` thSomeTypeLiftToEncodingObjectWithSingleField , testProperty "SomeTypeObjectWithSingleField unary agree" $ thSomeTypeToEncodingObjectWithSingleField `sameAs1Agree` thSomeTypeLiftToEncodingObjectWithSingleField , testProperty "OneConstructorDefault" $ thOneConstructorToJSONDefault `sameAs` thOneConstructorToEncodingDefault , testProperty "OneConstructorTagged" $ thOneConstructorToJSONTagged `sameAs` thOneConstructorToEncodingTagged , testProperty "OptionField" $ thOptionFieldToJSON `sameAs` thOptionFieldToEncoding ] ] ] aeson-1.4.2.0/tests/SerializationFormatSpec.hs0000644000000000000000000003136600000000000017420 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} #if __GLASGOW_HASKELL__ >= 708 {-# LANGUAGE DataKinds #-} #endif ------------------------------------------------------------------------------ -- These tests assert that the JSON serialization doesn't change by accident. ----------------------------------------------------------------------------- module SerializationFormatSpec ( tests ) where import Prelude.Compat import Control.Applicative (Const(..)) import Data.Aeson (FromJSON(..), decode, encode, genericParseJSON, genericToEncoding, genericToJSON) import Data.Aeson.Types (Options(..), SumEncoding(..), ToJSON(..), defaultOptions) import Data.Fixed (Pico) import Data.Foldable (for_, toList) import Data.Functor.Compose (Compose(..)) import Data.Functor.Identity (Identity(..)) import Data.Functor.Product (Product(..)) import Data.Functor.Sum (Sum(..)) import Data.List.NonEmpty (NonEmpty(..)) import Data.Proxy (Proxy(..)) import Data.Scientific (Scientific) import Data.Tagged (Tagged(..)) import Data.Time (fromGregorian) import Data.Word (Word8) import GHC.Generics (Generic) import Instances () import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (assertFailure, assertEqual, testCase) import Types (Approx(..), Compose3, Compose3', I) import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.DList as DList import qualified Data.HashMap.Strict as HM import qualified Data.HashSet as HashSet import qualified Data.IntMap as IntMap import qualified Data.IntSet as IntSet import qualified Data.Map as M import qualified Data.Monoid as Monoid import qualified Data.Semigroup as Semigroup import qualified Data.Sequence as Seq import qualified Data.Set as Set import qualified Data.Tree as Tree import qualified Data.UUID.Types as UUID import qualified Data.Vector as Vector tests :: [TestTree] tests = [ testGroup "To JSON representation" $ fmap assertJsonEncodingExample jsonEncodingExamples , testGroup "From JSON representation" $ fmap assertJsonExample jsonDecodingExamples , testGroup "To/From JSON representation" $ fmap assertJsonExample jsonExamples ] jsonExamples :: [Example] jsonExamples = [ example "Either Left" "{\"Left\":1}" (Left 1 :: Either Int Int) , example "Either Right" "{\"Right\":1}" (Right 1 :: Either Int Int) , example "Nothing" "null" (Nothing :: Maybe Int) , example "Just" "1" (Just 1 :: Maybe Int) , example "Proxy Int" "null" (Proxy :: Proxy Int) , example "Tagged Char Int" "1" (Tagged 1 :: Tagged Char Int) #if __GLASGOW_HASKELL__ >= 708 -- Test Tagged instance is polykinded , example "Tagged 123 Int" "1" (Tagged 1 :: Tagged 123 Int) #endif , example "Const Char Int" "\"c\"" (Const 'c' :: Const Char Int) , example "Tuple" "[1,2]" ((1, 2) :: (Int, Int)) , example "NonEmpty" "[1,2,3]" (1 :| [2, 3] :: NonEmpty Int) , example "Seq" "[1,2,3]" (Seq.fromList [1, 2, 3] :: Seq.Seq Int) , example "DList" "[1,2,3]" (DList.fromList [1, 2, 3] :: DList.DList Int) , example "()" "[]" () , Example "HashMap Int Int" [ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"] (HM.fromList [(0,1),(2,3)] :: HM.HashMap Int Int) , Example "Map Int Int" [ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"] (M.fromList [(0,1),(2,3)] :: M.Map Int Int) , Example "Map (Tagged Int Int) Int" [ "{\"0\":1,\"2\":3}", "{\"2\":3,\"0\":1}"] (M.fromList [(Tagged 0,1),(Tagged 2,3)] :: M.Map (Tagged Int Int) Int) , example "Map [Int] Int" "[[[0],1],[[2],3]]" (M.fromList [([0],1),([2],3)] :: M.Map [Int] Int) , Example "Map [Char] Int" [ "{\"ab\":1,\"cd\":3}", "{\"cd\":3,\"ab\":1}" ] (M.fromList [("ab",1),("cd",3)] :: M.Map String Int) , Example "Map [I Char] Int" [ "{\"ab\":1,\"cd\":3}", "{\"cd\":3,\"ab\":1}" ] (M.fromList [(map pure "ab",1),(map pure "cd",3)] :: M.Map [I Char] Int) , example "nan :: Double" "null" (Approx $ 0/0 :: Approx Double) , example "Ordering LT" "\"LT\"" LT , example "Ordering EQ" "\"EQ\"" EQ , example "Ordering GT" "\"GT\"" GT , example "Float" "3.14" (3.14 :: Float) , example "Pico" "3.14" (3.14 :: Pico) , example "Scientific" "3.14" (3.14 :: Scientific) , example "UUID" "\"c2cc10e1-57d6-4b6f-9899-38d972112d8c\"" $ UUID.fromWords 0xc2cc10e1 0x57d64b6f 0x989938d9 0x72112d8c , example "Set Int" "[1,2,3]" (Set.fromList [3, 2, 1] :: Set.Set Int) , example "IntSet" "[1,2,3]" (IntSet.fromList [3, 2, 1]) , example "IntMap" "[[1,2],[3,4]]" (IntMap.fromList [(3,4), (1,2)] :: IntMap.IntMap Int) , example "Vector" "[1,2,3]" (Vector.fromList [1, 2, 3] :: Vector.Vector Int) , example "HashSet Int" "[1,2,3]" (HashSet.fromList [3, 2, 1] :: HashSet.HashSet Int) , example "Tree Int" "[1,[[2,[[3,[]],[4,[]]]],[5,[]]]]" (let n = Tree.Node in n 1 [n 2 [n 3 [], n 4 []], n 5 []] :: Tree.Tree Int) -- Three separate cases, as ordering in HashMap is not defined , example "HashMap Float Int, NaN" "{\"NaN\":1}" (Approx $ HM.singleton (0/0) 1 :: Approx (HM.HashMap Float Int)) , example "HashMap Float Int, Infinity" "{\"Infinity\":1}" (HM.singleton (1/0) 1 :: HM.HashMap Float Int) , example "HashMap Float Int, +Infinity" "{\"-Infinity\":1}" (HM.singleton (negate 1/0) 1 :: HM.HashMap Float Int) -- Functors , example "Identity Int" "1" (pure 1 :: Identity Int) , example "Identity Char" "\"x\"" (pure 'x' :: Identity Char) , example "Identity String" "\"foo\"" (pure "foo" :: Identity String) , example "[Identity Char]" "\"xy\"" ([pure 'x', pure 'y'] :: [Identity Char]) , example "Maybe Char" "\"x\"" (pure 'x' :: Maybe Char) , example "Maybe String" "\"foo\"" (pure "foo" :: Maybe String) , example "Maybe [Identity Char]" "\"xy\"" (pure [pure 'x', pure 'y'] :: Maybe [Identity Char]) , example "Day; year >= 1000" "\"1999-10-12\"" (fromGregorian 1999 10 12) , example "Day; year > 0 && < 1000" "\"0500-03-04\"" (fromGregorian 500 3 4) , example "Day; year == 0" "\"0000-02-20\"" (fromGregorian 0 2 20) , example "Day; year < 0" "\"-0234-01-01\"" (fromGregorian (-234) 1 1) , example "Day; year < -1000" "\"-1234-01-01\"" (fromGregorian (-1234) 1 1) , example "Product I Maybe Int" "[1,2]" (Pair (pure 1) (pure 2) :: Product I Maybe Int) , example "Product I Maybe Int" "[1,null]" (Pair (pure 1) Nothing :: Product I Maybe Int) , example "Product I [] Char" "[\"a\",\"foo\"]" (Pair (pure 'a') "foo" :: Product I [] Char) , example "Sum I [] Int: InL" "{\"InL\":1}" (InL (pure 1) :: Sum I [] Int) , example "Sum I [] Int: InR" "{\"InR\":[1,2]}" (InR [1, 2] :: Sum I [] Int) , example "Sum I [] Char: InR" "{\"InR\":\"foo\"}" (InR "foo" :: Sum I [] Char) , example "Compose I I Int" "1" (pure 1 :: Compose I I Int) , example "Compose I [] Int" "[1]" (pure 1 :: Compose I [] Int) , example "Compose [] I Int" "[1]" (pure 1 :: Compose [] I Int) , example "Compose [] [] Int" "[[1]]" (pure 1 :: Compose [] [] Int) , example "Compose I I Char" "\"x\"" (pure 'x' :: Compose I I Char) , example "Compose I [] Char" "\"x\"" (pure 'x' :: Compose I [] Char) , example "Compose [] I Char" "\"x\"" (pure 'x' :: Compose [] I Char) , example "Compose [] [] Char" "[\"x\"]" (pure 'x' :: Compose [] [] Char) , example "Compose3 I I I Char" "\"x\"" (pure 'x' :: Compose3 I I I Char) , example "Compose3 I I [] Char" "\"x\"" (pure 'x' :: Compose3 I I [] Char) , example "Compose3 I [] I Char" "\"x\"" (pure 'x' :: Compose3 I [] I Char) , example "Compose3 I [] [] Char" "[\"x\"]" (pure 'x' :: Compose3 I [] [] Char) , example "Compose3 [] I I Char" "\"x\"" (pure 'x' :: Compose3 [] I I Char) , example "Compose3 [] I [] Char" "[\"x\"]" (pure 'x' :: Compose3 [] I [] Char) , example "Compose3 [] [] I Char" "[\"x\"]" (pure 'x' :: Compose3 [] [] I Char) , example "Compose3 [] [] [] Char" "[[\"x\"]]" (pure 'x' :: Compose3 [] [] [] Char) , example "Compose3' I I I Char" "\"x\"" (pure 'x' :: Compose3' I I I Char) , example "Compose3' I I [] Char" "\"x\"" (pure 'x' :: Compose3' I I [] Char) , example "Compose3' I [] I Char" "\"x\"" (pure 'x' :: Compose3' I [] I Char) , example "Compose3' I [] [] Char" "[\"x\"]" (pure 'x' :: Compose3' I [] [] Char) , example "Compose3' [] I I Char" "\"x\"" (pure 'x' :: Compose3' [] I I Char) , example "Compose3' [] I [] Char" "[\"x\"]" (pure 'x' :: Compose3' [] I [] Char) , example "Compose3' [] [] I Char" "[\"x\"]" (pure 'x' :: Compose3' [] [] I Char) , example "Compose3' [] [] [] Char" "[[\"x\"]]" (pure 'x' :: Compose3' [] [] [] Char) , example "MyEither Int String: Left" "42" (MyLeft 42 :: MyEither Int String) , example "MyEither Int String: Right" "\"foo\"" (MyRight "foo" :: MyEither Int String) -- newtypes from Monoid/Semigroup , example "Monoid.Dual Int" "2" (pure 2 :: Monoid.Dual Int) , example "Monoid.First Int" "2" (pure 2 :: Monoid.First Int) , example "Monoid.Last Int" "2" (pure 2 :: Monoid.Last Int) , example "Semigroup.Min Int" "2" (pure 2 :: Semigroup.Min Int) , example "Semigroup.Max Int" "2" (pure 2 :: Semigroup.Max Int) , example "Semigroup.First Int" "2" (pure 2 :: Semigroup.First Int) , example "Semigroup.Last Int" "2" (pure 2 :: Semigroup.Last Int) , example "Semigroup.WrappedMonoid Int" "2" (Semigroup.WrapMonoid 2 :: Semigroup.WrappedMonoid Int) , example "Semigroup.Option Just" "2" (pure 2 :: Semigroup.Option Int) , example "Semigroup.Option Nothing" "null" (Semigroup.Option (Nothing :: Maybe Bool)) ] jsonEncodingExamples :: [Example] jsonEncodingExamples = [ -- Maybe serialising is lossy -- https://github.com/bos/aeson/issues/376 example "Just Nothing" "null" (Just Nothing :: Maybe (Maybe Int)) -- infinities cannot be recovered, null is decoded as NaN , example "inf :: Double" "null" (Approx $ 1/0 :: Approx Double) ] jsonDecodingExamples :: [Example] jsonDecodingExamples = [ -- Maybe serialising is lossy -- https://github.com/bos/aeson/issues/376 MaybeExample "Nothing" "null" (Just Nothing :: Maybe (Maybe Int)) , MaybeExample "Just" "1" (Just $ Just 1 :: Maybe (Maybe Int)) , MaybeExample "Just Nothing" "null" (Just Nothing :: Maybe (Maybe (Maybe Int))) -- Integral values are truncated, and overflowed -- https://github.com/bos/aeson/issues/317 , MaybeExample "Word8 3" "3" (Just 3 :: Maybe Word8) , MaybeExample "Word8 3.00" "3.00" (Just 3 :: Maybe Word8) , MaybeExample "Word8 3.14" "3.14" (Nothing :: Maybe Word8) , MaybeExample "Word8 -1" "-1" (Nothing :: Maybe Word8) , MaybeExample "Word8 300" "300" (Nothing :: Maybe Word8) -- Negative zero year, encoding never produces such: , MaybeExample "Day -0000-02-03" "\"-0000-02-03\"" (Just (fromGregorian 0 2 3)) ] data Example where Example :: (Eq a, Show a, ToJSON a, FromJSON a) => String -> [L.ByteString] -> a -> Example -- empty bytestring will fail, any p [] == False MaybeExample :: (Eq a, Show a, FromJSON a) => String -> L.ByteString -> Maybe a -> Example example :: (Eq a, Show a, ToJSON a, FromJSON a) => String -> L.ByteString -> a -> Example example n bs x = Example n [bs] x data MyEither a b = MyLeft a | MyRight b deriving (Generic, Show, Eq) instance (ToJSON a, ToJSON b) => ToJSON (MyEither a b) where toJSON = genericToJSON defaultOptions { sumEncoding = UntaggedValue } toEncoding = genericToEncoding defaultOptions { sumEncoding = UntaggedValue } instance (FromJSON a, FromJSON b) => FromJSON (MyEither a b) where parseJSON = genericParseJSON defaultOptions { sumEncoding = UntaggedValue } assertJsonExample :: Example -> TestTree assertJsonExample (Example name bss val) = testCase name $ do assertSomeEqual "encode" bss (encode val) assertSomeEqual "encode/via value" bss (encode $ toJSON val) for_ bss $ \bs -> assertEqual "decode" (Just val) (decode bs) assertJsonExample (MaybeExample name bs mval) = testCase name $ assertEqual "decode" mval (decode bs) assertJsonEncodingExample :: Example -> TestTree assertJsonEncodingExample (Example name bss val) = testCase name $ do assertSomeEqual "encode" bss (encode val) assertSomeEqual "encode/via value" bss (encode $ toJSON val) assertJsonEncodingExample (MaybeExample name _ _) = testCase name $ assertFailure "cannot encode MaybeExample" assertSomeEqual :: (Eq a, Show a, Foldable f) => String -> f a -> a -> IO () assertSomeEqual preface expected actual | actual `elem` expected = return () | otherwise = assertFailure $ preface ++ ": expecting one of " ++ show (toList expected) ++ ", got " ++ show actual aeson-1.4.2.0/tests/Tests.hs0000644000000000000000000000063000000000000013707 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} module Main (main) where import Prelude.Compat import Test.Tasty (defaultMain, testGroup) import qualified DataFamilies.Properties as DF import qualified Properties import qualified UnitTests main :: IO () main = do ioTests <- UnitTests.ioTests let allTests = DF.tests : Properties.tests : UnitTests.tests : ioTests defaultMain (testGroup "tests" allTests) aeson-1.4.2.0/tests/Types.hs0000644000000000000000000001263500000000000013721 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} module Types (module Types) where import Prelude.Compat import Math.NumberTheory.Logarithms (intLog2) import Control.Applicative ((<$>)) import Data.Data import Data.Functor.Compose (Compose (..)) import Data.Functor.Identity (Identity (..)) import Data.Hashable (Hashable (..)) import Data.Semigroup (Option) import Data.Text import Data.Time (Day (..), fromGregorian) import GHC.Generics import Test.QuickCheck (Arbitrary (..), Property, counterexample, scale) import qualified Data.Map as Map import Data.Aeson import Data.Aeson.Types type I = Identity type Compose3 f g h = Compose (Compose f g) h type Compose3' f g h = Compose f (Compose g h) data Foo = Foo { fooInt :: Int , fooDouble :: Double , fooTuple :: (String, Text, Int) -- This definition causes an infinite loop in genericTo and genericFrom! -- , fooMap :: Map.Map String Foo , fooMap :: Map.Map String (Text,Int) } deriving (Show, Typeable, Data) data UFoo = UFoo { _UFooInt :: Int , uFooInt :: Int } deriving (Show, Eq, Data, Typeable) data OneConstructor = OneConstructor deriving (Show, Eq, Typeable, Data) data Product2 a b = Product2 a b deriving (Show, Eq, Typeable, Data) data Product6 a b c d e f = Product6 a b c d e f deriving (Show, Eq, Typeable, Data) data Sum4 a b c d = Alt1 a | Alt2 b | Alt3 c | Alt4 d deriving (Show, Eq, Typeable, Data) class ApproxEq a where (=~) :: a -> a -> Bool newtype Approx a = Approx { fromApprox :: a } deriving (Show, Data, Typeable, ApproxEq, Num) instance (ApproxEq a) => Eq (Approx a) where Approx a == Approx b = a =~ b data Nullary = C1 | C2 | C3 deriving (Eq, Show) data SomeType a = Nullary | Unary Int | Product String (Maybe Char) a | Record { testOne :: Double , testTwo :: Maybe Bool , testThree :: Maybe a } | List [a] deriving (Eq, Show) -- | This type requires IncoherentInstances for the instances of the type -- classes Data.Aeson.TH.LookupField and Data.Aeson.Types.FromJSON.FromRecord. -- -- The minimum known requirements for this type are: -- * Record type with at least two fields -- * One field type is either a type parameter or a type/data family -- * Another field type is a @Maybe@ of the above field type data IncoherentInstancesNeeded a = IncoherentInstancesNeeded { incoherentInstancesNeededMaybeNot :: a , incoherentInstancesNeededMaybeYes :: Maybe a } deriving Generic -- Used for testing UntaggedValue SumEncoding data EitherTextInt = LeftBool Bool | RightInt Int | BothTextInt Text Int | NoneNullary deriving (Eq, Show) data GADT a where GADT :: { gadt :: String } -> GADT String deriving Typeable deriving instance Data (GADT String) deriving instance Eq (GADT a) deriving instance Show (GADT a) newtype MaybeField = MaybeField { maybeField :: Maybe Int } newtype OptionField = OptionField { optionField :: Option Int } deriving (Eq, Show) deriving instance Generic Foo deriving instance Generic UFoo deriving instance Generic OneConstructor deriving instance Generic (Product2 a b) deriving instance Generic (Product6 a b c d e f) deriving instance Generic (Sum4 a b c d) deriving instance Generic (Approx a) deriving instance Generic Nullary deriving instance Generic (SomeType a) #if __GLASGOW_HASKELL__ >= 706 deriving instance Generic1 SomeType #endif deriving instance Generic OptionField deriving instance Generic EitherTextInt failure :: Show a => String -> String -> a -> Property failure func msg v = counterexample (func ++ " failed: " ++ msg ++ ", " ++ show v) False newtype BCEDay = BCEDay Day deriving (Eq, Show) zeroDay :: Day zeroDay = fromGregorian 0 0 0 instance Arbitrary BCEDay where arbitrary = fmap (BCEDay . ModifiedJulianDay . (+ toModifiedJulianDay zeroDay)) arbitrary instance ToJSON BCEDay where toJSON (BCEDay d) = toJSON d toEncoding (BCEDay d) = toEncoding d instance FromJSON BCEDay where parseJSON = fmap BCEDay . parseJSON -- | Scale the size of Arbitrary with '' newtype LogScaled a = LogScaled { getLogScaled :: a } deriving (Eq, Ord, Show) instance Hashable a => Hashable (LogScaled a) where hashWithSalt salt (LogScaled a) = hashWithSalt salt a instance Arbitrary a => Arbitrary (LogScaled a) where arbitrary = LogScaled <$> scale (\x -> intLog2 $ x + 1) arbitrary shrink = fmap LogScaled . shrink . getLogScaled instance ToJSON a => ToJSON (LogScaled a) where toJSON (LogScaled d) = toJSON d toEncoding (LogScaled d) = toEncoding d instance FromJSON a => FromJSON (LogScaled a) where parseJSON = fmap LogScaled . parseJSON instance (ToJSONKey a) => ToJSONKey (LogScaled a) where toJSONKey = contramapToJSONKeyFunction getLogScaled toJSONKey toJSONKeyList = contramapToJSONKeyFunction (fmap getLogScaled) toJSONKeyList instance (FromJSONKey a) => FromJSONKey (LogScaled a) where fromJSONKey = fmap LogScaled fromJSONKey fromJSONKeyList = coerceFromJSONKeyFunction (fromJSONKeyList :: FromJSONKeyFunction [a]) aeson-1.4.2.0/tests/UnitTests.hs0000644000000000000000000006061300000000000014556 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} -- For Data.Aeson.Types.camelTo {-# OPTIONS_GHC -fno-warn-deprecations #-} #if MIN_VERSION_base(4,9,0) {-# OPTIONS_GHC -fno-warn-unused-top-binds #-} #endif module UnitTests ( ioTests , tests , withEmbeddedJSONTest ) where import Prelude.Compat import Control.Monad (forM, forM_) import Data.Aeson ((.=), (.:), (.:?), (.:!), FromJSON(..), FromJSONKeyFunction(..), FromJSONKey(..), ToJSON1(..), decode, eitherDecode, encode, fromJSON, genericParseJSON, genericToEncoding, genericToJSON, object, withObject, withEmbeddedJSON) import Data.Aeson.Internal (JSONPathElement(..), formatError) import Data.Aeson.QQ.Simple (aesonQQ) import Data.Aeson.TH (deriveJSON, deriveToJSON, deriveToJSON1) import Data.Aeson.Text (encodeToTextBuilder) import Data.Aeson.Types (Options(..), Result(Success), ToJSON(..), Value(Null, Object), camelTo, camelTo2, defaultOptions, omitNothingFields, parse) import Data.Char (toUpper) import Data.Either.Compat (isLeft, isRight) import Data.Hashable (hash) import Data.HashMap.Strict (HashMap) import Data.List (sort) import Data.Maybe (fromMaybe) import Data.Sequence (Seq) import Data.Scientific (Scientific, scientific) import Data.Tagged (Tagged(..)) import Data.Text (Text) import Data.Time (UTCTime) import Data.Time.Format (parseTime) import Data.Time.Locale.Compat (defaultTimeLocale) import GHC.Generics (Generic) import Instances () import Numeric.Natural (Natural) import System.Directory (getDirectoryContents) import System.FilePath ((), takeExtension, takeFileName) import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (Assertion, assertBool, assertFailure, assertEqual, testCase) import Text.Printf (printf) import UnitTests.NullaryConstructors (nullaryConstructors) import qualified Data.ByteString.Base16.Lazy as LBase16 import qualified Data.ByteString.Lazy.Char8 as L import qualified Data.HashSet as HashSet import qualified Data.Text.Lazy as LT import qualified Data.Text.Lazy.Builder as TLB import qualified Data.Text.Lazy.Encoding as LT import qualified Data.Text.Lazy.Encoding as TLE import qualified ErrorMessages import qualified SerializationFormatSpec -- Asserts that we can use both modules at once in the test suite. import Data.Aeson.Parser.UnescapeFFI () import Data.Aeson.Parser.UnescapePure () tests :: TestTree tests = testGroup "unit" [ testGroup "SerializationFormatSpec" SerializationFormatSpec.tests , testGroup "ErrorMessages" ErrorMessages.tests , testGroup "camelCase" [ testCase "camelTo" $ roundTripCamel "aName" , testCase "camelTo" $ roundTripCamel "another" , testCase "camelTo" $ roundTripCamel "someOtherName" , testCase "camelTo" $ assertEqual "" "camel_apicase" (camelTo '_' "CamelAPICase") , testCase "camelTo2" $ roundTripCamel2 "aName" , testCase "camelTo2" $ roundTripCamel2 "another" , testCase "camelTo2" $ roundTripCamel2 "someOtherName" , testCase "camelTo2" $ assertEqual "" "camel_api_case" (camelTo2 '_' "CamelAPICase") ] , testGroup "encoding" [ testCase "goodProducer" goodProducer ] , testGroup "utctime" [ testCase "good" utcTimeGood , testCase "bad" utcTimeBad ] , testGroup "formatError" [ testCase "example 1" formatErrorExample ] , testGroup ".:, .:?, .:!" $ fmap (testCase "-") dotColonMark , testGroup "JSONPath" $ fmap (testCase "-") jsonPath , testGroup "Hashable laws" $ fmap (testCase "-") hashableLaws , testGroup "Object construction" $ fmap (testCase "-") objectConstruction , testGroup "Issue #351" $ fmap (testCase "-") issue351 , testGroup "Nullary constructors" $ fmap (testCase "-") nullaryConstructors , testGroup "FromJSONKey" $ fmap (testCase "-") fromJSONKeyAssertions , testCase "PR #455" pr455 , testCase "Unescape string (PR #477)" unescapeString , testCase "Show Options" showOptions , testGroup "SingleMaybeField" singleMaybeField , testCase "withEmbeddedJSON" withEmbeddedJSONTest , testCase "SingleFieldCon" singleFieldCon , testCase "Ratio with denominator 0" ratioDenominator0 , testCase "Big scientific exponent" bigScientificExponent , testCase "Big integer decoding" bigIntegerDecoding , testCase "Big natural decading" bigNaturalDecoding , testCase "Big integer key decoding" bigIntegerKeyDecoding , testGroup "QQ.Simple" [ testCase "example" $ assertEqual "" (object ["foo" .= True]) [aesonQQ| {"foo": true } |] ] ] roundTripCamel :: String -> Assertion roundTripCamel name = assertEqual "" name (camelFrom '_' $ camelTo '_' name) roundTripCamel2 :: String -> Assertion roundTripCamel2 name = assertEqual "" name (camelFrom '_' $ camelTo2 '_' name) camelFrom :: Char -> String -> String camelFrom c s = let (p:ps) = split c s in concat $ p : map capitalize ps where split c' s' = map L.unpack $ L.split c' $ L.pack s' capitalize t = toUpper (head t) : tail t data Wibble = Wibble { wibbleString :: String , wibbleInt :: Int } deriving (Generic, Show, Eq) instance FromJSON Wibble instance ToJSON Wibble where toJSON = genericToJSON defaultOptions toEncoding = genericToEncoding defaultOptions -- Test that if we put a bomb in a data structure, but only demand -- part of it via lazy encoding, we do not unexpectedly fail. goodProducer :: Assertion goodProducer = assertEqual "partial encoding should not explode on undefined" '{' (L.head (encode wibble)) where wibble = Wibble { wibbleString = replicate k 'a' , wibbleInt = 1 } k | arch32bit = 4047 | otherwise = 4030 arch32bit = (maxBound :: Int) == 2147483647 -- Test decoding various UTC time formats -- -- Note: the incomplete pattern matches for UTCTimes are completely -- intentional. The test expects these parses to succeed. If the -- pattern matches fails, there's a bug in either the test or in aeson -- and needs to be investigated. utcTimeGood :: Assertion utcTimeGood = do let ts1 = "2015-01-01T12:13:00.00Z" :: LT.Text let ts2 = "2015-01-01T12:13:00Z" :: LT.Text -- 'T' between date and time is not required, can be space let ts3 = "2015-01-03 12:13:00.00Z" :: LT.Text let ts4 = "2015-01-03 12:13:00.125Z" :: LT.Text let (Just (t1 :: UTCTime)) = parseWithAeson ts1 let (Just (t2 :: UTCTime)) = parseWithAeson ts2 let (Just (t3 :: UTCTime)) = parseWithAeson ts3 let (Just (t4 :: UTCTime)) = parseWithAeson ts4 assertEqual "utctime" (parseWithRead "%FT%T%QZ" ts1) t1 assertEqual "utctime" (parseWithRead "%FT%T%QZ" ts2) t2 assertEqual "utctime" (parseWithRead "%F %T%QZ" ts3) t3 assertEqual "utctime" (parseWithRead "%F %T%QZ" ts4) t4 -- Time zones. Both +HHMM and +HH:MM are allowed for timezone -- offset, and MM may be omitted. let ts5 = "2015-01-01T12:30:00.00+00" :: LT.Text let ts6 = "2015-01-01T12:30:00.00+01:15" :: LT.Text let ts7 = "2015-01-01T12:30:00.00-02" :: LT.Text let ts8 = "2015-01-01T22:00:00.00-03" :: LT.Text let ts9 = "2015-01-01T22:00:00.00-04:30" :: LT.Text let (Just (t5 :: UTCTime)) = parseWithAeson ts5 let (Just (t6 :: UTCTime)) = parseWithAeson ts6 let (Just (t7 :: UTCTime)) = parseWithAeson ts7 let (Just (t8 :: UTCTime)) = parseWithAeson ts8 let (Just (t9 :: UTCTime)) = parseWithAeson ts9 assertEqual "utctime" (parseWithRead "%FT%T%QZ" "2015-01-01T12:30:00.00Z") t5 assertEqual "utctime" (parseWithRead "%FT%T%QZ" "2015-01-01T11:15:00.00Z") t6 assertEqual "utctime" (parseWithRead "%FT%T%QZ" "2015-01-01T14:30:00Z") t7 -- ts8 wraps around to the next day in UTC assertEqual "utctime" (parseWithRead "%FT%T%QZ" "2015-01-02T01:00:00Z") t8 assertEqual "utctime" (parseWithRead "%FT%T%QZ" "2015-01-02T02:30:00Z") t9 -- Seconds in Time can be omitted let ts10 = "2015-01-03T12:13Z" :: LT.Text let ts11 = "2015-01-03 12:13Z" :: LT.Text let ts12 = "2015-01-01T12:30-02" :: LT.Text let (Just (t10 :: UTCTime)) = parseWithAeson ts10 let (Just (t11 :: UTCTime)) = parseWithAeson ts11 let (Just (t12 :: UTCTime)) = parseWithAeson ts12 assertEqual "utctime" (parseWithRead "%FT%H:%MZ" ts10) t10 assertEqual "utctime" (parseWithRead "%F %H:%MZ" ts11) t11 assertEqual "utctime" (parseWithRead "%FT%T%QZ" "2015-01-01T14:30:00Z") t12 -- leap seconds are included correctly let ts13 = "2015-08-23T23:59:60.128+00" :: LT.Text let (Just (t13 :: UTCTime)) = parseWithAeson ts13 assertEqual "utctime" (parseWithRead "%FT%T%QZ" "2015-08-23T23:59:60.128Z") t13 let ts14 = "2015-08-23T23:59:60.999999999999+00" :: LT.Text let (Just (t14 :: UTCTime)) = parseWithAeson ts14 assertEqual "utctime" (parseWithRead "%FT%T%QZ" "2015-08-23T23:59:60.999999999999Z") t14 where parseWithRead :: String -> LT.Text -> UTCTime parseWithRead f s = fromMaybe (error "parseTime input malformed") . parseTime defaultTimeLocale f . LT.unpack $ s parseWithAeson :: LT.Text -> Maybe UTCTime parseWithAeson s = decode . LT.encodeUtf8 $ LT.concat ["\"", s, "\""] -- Test that a few non-timezone qualified timestamp formats get -- rejected if decoding to UTCTime. utcTimeBad :: Assertion utcTimeBad = do verifyFailParse "2000-01-01T12:13:00" -- missing Zulu time not allowed (some TZ required) verifyFailParse "2000-01-01 12:13:00" -- missing Zulu time not allowed (some TZ required) verifyFailParse "2000-01-01" -- date only not OK verifyFailParse "2000-01-01Z" -- date only not OK verifyFailParse "2015-01-01T12:30:00.00+00Z" -- no Zulu if offset given verifyFailParse "2015-01-01T12:30:00.00+00:00Z" -- no Zulu if offset given verifyFailParse "2015-01-03 12:13:00.Z" -- decimal at the end but no digits verifyFailParse "2015-01-03 12:13.000Z" -- decimal at the end, but no seconds verifyFailParse "2015-01-03 23:59:61Z" -- exceeds allowed seconds per day where verifyFailParse (s :: LT.Text) = let (dec :: Maybe UTCTime) = decode . LT.encodeUtf8 $ LT.concat ["\"", s, "\""] in assertEqual "verify failure" Nothing dec -- Non identifier keys should be escaped & enclosed in brackets formatErrorExample :: Assertion formatErrorExample = let rhs = formatError [Index 0, Key "foo", Key "bar", Key "a.b.c", Key "", Key "'\\", Key "end"] "error msg" lhs = "Error in $[0].foo.bar['a.b.c']['']['\\'\\\\'].end: error msg" in assertEqual "formatError example" lhs rhs ------------------------------------------------------------------------------ -- Comparison (.:?) and (.:!) ------------------------------------------------------------------------------ newtype T1 = T1 (Maybe Int) deriving (Eq, Show) newtype T2 = T2 (Maybe Int) deriving (Eq, Show) newtype T3 = T3 (Maybe Int) deriving (Eq, Show) instance FromJSON T1 where parseJSON = fmap T1 . withObject "T1" (.: "value") instance FromJSON T2 where parseJSON = fmap T2 . withObject "T2" (.:? "value") instance FromJSON T3 where parseJSON = fmap T3 . withObject "T3" (.:! "value") dotColonMark :: [Assertion] dotColonMark = [ assertEqual ".: not-present" Nothing (decode ex1 :: Maybe T1) , assertEqual ".: 42" (Just (T1 (Just 42))) (decode ex2 :: Maybe T1) , assertEqual ".: null" (Just (T1 Nothing)) (decode ex3 :: Maybe T1) , assertEqual ".:? not-present" (Just (T2 Nothing)) (decode ex1 :: Maybe T2) , assertEqual ".:? 42" (Just (T2 (Just 42))) (decode ex2 :: Maybe T2) , assertEqual ".:? null" (Just (T2 Nothing)) (decode ex3 :: Maybe T2) , assertEqual ".:! not-present" (Just (T3 Nothing)) (decode ex1 :: Maybe T3) , assertEqual ".:! 42" (Just (T3 (Just 42))) (decode ex2 :: Maybe T3) , assertEqual ".:! null" Nothing (decode ex3 :: Maybe T3) ] where ex1 = "{}" ex2 = "{\"value\": 42 }" ex3 = "{\"value\": null }" ------------------------------------------------------------------------------ -- These tests check that JSONPath is tracked correctly ----------------------------------------------------------------------------- jsonPath :: [Assertion] jsonPath = [ -- issue #356 assertEqual "Either" (Left "Error in $[1].Left[1]: expected Bool, encountered Number") (eitherDecode "[1,{\"Left\":[2,3]}]" :: Either String (Int, Either (Int, Bool) ())) -- issue #358 , assertEqual "Seq a" (Left "Error in $[2]: expected Int, encountered Boolean") (eitherDecode "[0,1,true]" :: Either String (Seq Int)) , assertEqual "Wibble" (Left "Error in $.wibbleInt: expected Int, encountered Boolean") (eitherDecode "{\"wibbleString\":\"\",\"wibbleInt\":true}" :: Either String Wibble) ] ------------------------------------------------------------------------------ -- Check that the hashes of two equal Value are the same ------------------------------------------------------------------------------ hashableLaws :: [Assertion] hashableLaws = [ assertEqual "Hashable Object" (hash a) (hash b) ] where a = object ["223" .= False, "807882556" .= True] b = object ["807882556" .= True, "223" .= False] ------------------------------------------------------------------------------ -- Check that an alternative way to construct objects works ------------------------------------------------------------------------------ objectConstruction :: [Assertion] objectConstruction = [ assertEqual "Equal objects constructed differently" recommended notRecommended ] where recommended = object ["foo" .= True, "bar" .= (-1 :: Int)] notRecommended = Object (mconcat ["foo" .= True, "bar" .= (-1 :: Int)]) ------------------------------------------------------------------------------- -- ToJSONKey ------------------------------------------------------------------------------- newtype MyText = MyText Text deriving (FromJSONKey) newtype MyText' = MyText' Text instance FromJSONKey MyText' where fromJSONKey = fmap MyText' fromJSONKey fromJSONKeyList = error "not used" fromJSONKeyAssertions :: [Assertion] fromJSONKeyAssertions = [ assertIsCoerce "Text" (fromJSONKey :: FromJSONKeyFunction Text) , assertIsCoerce "Tagged Int Text" (fromJSONKey :: FromJSONKeyFunction (Tagged Int Text)) , assertIsCoerce "MyText" (fromJSONKey :: FromJSONKeyFunction MyText) #if __GLASGOW_HASKELL__ >= 710 , assertIsCoerce' "MyText'" (fromJSONKey :: FromJSONKeyFunction MyText') #endif ] where assertIsCoerce _ (FromJSONKeyCoerce _) = pure () assertIsCoerce n _ = assertFailure n #if __GLASGOW_HASKELL__ >= 710 assertIsCoerce' _ (FromJSONKeyCoerce _) = pure () assertIsCoerce' n _ = pickWithRules (assertFailure n) (pure ()) -- | Pick the first when RULES are enabled, e.g. optimisations are on pickWithRules :: a -- ^ Pick this when RULES are on -> a -- ^ use this otherwise -> a pickWithRules _ = id {-# NOINLINE pickWithRules #-} {-# RULES "pickWithRules/rule" [0] forall x. pickWithRules x = const x #-} #endif ------------------------------------------------------------------------------ -- Regressions ------------------------------------------------------------------------------ -- A regression test for: https://github.com/bos/aeson/issues/351 overlappingRegression :: FromJSON a => L.ByteString -> [a] overlappingRegression bs = fromMaybe [] $ decode bs issue351 :: [Assertion] issue351 = [ assertEqual "Int" ([1, 2, 3] :: [Int]) $ overlappingRegression "[1, 2, 3]" , assertEqual "Char" ("abc" :: String) $ overlappingRegression "\"abc\"" , assertEqual "Char" ("" :: String) $ overlappingRegression "[\"a\", \"b\", \"c\"]" ] ------------------------------------------------------------------------------ -- Comparison between bytestring and text encoders ------------------------------------------------------------------------------ ioTests :: IO [TestTree] ioTests = do enc <- encoderComparisonTests js <- jsonTestSuite return [enc, js] encoderComparisonTests :: IO TestTree encoderComparisonTests = do encoderTests <- forM testFiles $ \file0 -> do let file = "benchmarks/json-data/" ++ file0 return $ testCase file $ do inp <- L.readFile file case eitherDecode inp of Left err -> assertFailure $ "Decoding failure: " ++ err Right val -> assertEqual "" (encode val) (encodeViaText val) return $ testGroup "encoders" encoderTests where encodeViaText :: Value -> L.ByteString encodeViaText = TLE.encodeUtf8 . TLB.toLazyText . encodeToTextBuilder . toJSON testFiles = [ "example.json" , "integers.json" , "jp100.json" , "numbers.json" , "twitter10.json" , "twitter20.json" , "geometry.json" , "jp10.json" , "jp50.json" , "twitter1.json" , "twitter100.json" , "twitter50.json" ] -- A regression test for: https://github.com/bos/aeson/issues/293 data MyRecord = MyRecord {_field1 :: Maybe Int, _field2 :: Maybe Bool} data MyRecord2 = MyRecord2 {_field3 :: Maybe Int, _field4 :: Maybe Bool} deriving Generic instance ToJSON MyRecord2 instance FromJSON MyRecord2 -- A regression test for: https://github.com/bos/aeson/pull/477 unescapeString :: Assertion unescapeString = do assertEqual "Basic escaping" (Right ("\" / \\ \b \f \n \r \t" :: String)) (eitherDecode "\"\\\" \\/ \\\\ \\b \\f \\n \\r \\t\"") forM_ [minBound .. maxBound :: Char] $ \ c -> let s = LT.pack [c] in assertEqual (printf "UTF-16 encoded '\\x%X'" c) (Right s) (eitherDecode $ utf16Char s) where utf16Char = formatString . LBase16.encode . LT.encodeUtf16BE formatString s | L.length s == 4 = L.concat ["\"\\u", s, "\""] | L.length s == 8 = L.concat ["\"\\u", L.take 4 s, "\\u", L.drop 4 s, "\""] | otherwise = error "unescapeString: can't happen" -- JSONTestSuite jsonTestSuiteTest :: FilePath -> TestTree jsonTestSuiteTest path = testCase fileName $ do payload <- L.readFile path let result = eitherDecode payload :: Either String Value assertBool fileName $ case take 2 fileName of "i_" -> isRight result "n_" -> isLeft result "y_" -> isRight result _ -> isRight result -- test_transform tests have inconsistent names where fileName = takeFileName path -- Build a collection of tests based on the current contents of the -- JSONTestSuite test directories. jsonTestSuite :: IO TestTree jsonTestSuite = do let suitePath = "tests/JSONTestSuite" let suites = ["test_parsing", "test_transform"] testPaths <- fmap (sort . concat) . forM suites $ \suite -> do let dir = suitePath suite entries <- getDirectoryContents dir let ok name = takeExtension name == ".json" && not (name `HashSet.member` blacklist) return . map (dir ) . filter ok $ entries return $ testGroup "JSONTestSuite" $ map jsonTestSuiteTest testPaths -- The set expected-to-be-failing JSONTestSuite tests. -- Not all of these failures are genuine bugs. -- Of those that are bugs, not all are worth fixing. blacklist :: HashSet.HashSet String -- blacklist = HashSet.empty blacklist = _blacklist _blacklist :: HashSet.HashSet String _blacklist = HashSet.fromList [ "i_object_key_lone_2nd_surrogate.json" , "i_string_1st_surrogate_but_2nd_missing.json" , "i_string_1st_valid_surrogate_2nd_invalid.json" , "i_string_UTF-16LE_with_BOM.json" , "i_string_UTF-16_invalid_lonely_surrogate.json" , "i_string_UTF-16_invalid_surrogate.json" , "i_string_UTF-8_invalid_sequence.json" , "i_string_incomplete_surrogate_and_escape_valid.json" , "i_string_incomplete_surrogate_pair.json" , "i_string_incomplete_surrogates_escape_valid.json" , "i_string_invalid_lonely_surrogate.json" , "i_string_invalid_surrogate.json" , "i_string_inverted_surrogates_U+1D11E.json" , "i_string_lone_second_surrogate.json" , "i_string_not_in_unicode_range.json" , "i_string_truncated-utf-8.json" , "i_structure_UTF-8_BOM_empty_object.json" , "n_string_unescaped_crtl_char.json" , "n_string_unescaped_newline.json" , "n_string_unescaped_tab.json" , "string_1_escaped_invalid_codepoint.json" , "string_1_invalid_codepoint.json" , "string_1_invalid_codepoints.json" , "string_2_escaped_invalid_codepoints.json" , "string_2_invalid_codepoints.json" , "string_3_escaped_invalid_codepoints.json" , "string_3_invalid_codepoints.json" , "y_string_utf16BE_no_BOM.json" , "y_string_utf16LE_no_BOM.json" ] -- A regression test for: https://github.com/bos/aeson/pull/455 data Foo a = FooNil | FooCons (Foo Int) pr455 :: Assertion pr455 = assertEqual "FooCons FooNil" (toJSON foo) (liftToJSON undefined undefined foo) where foo :: Foo Int foo = FooCons FooNil showOptions :: Assertion showOptions = assertEqual "Show Options" ( "Options {" ++ "fieldLabelModifier =~ \"exampleField\"" ++ ", constructorTagModifier =~ \"ExampleConstructor\"" ++ ", allNullaryToStringTag = True" ++ ", omitNothingFields = False" ++ ", sumEncoding = TaggedObject {tagFieldName = \"tag\", contentsFieldName = \"contents\"}" ++ ", unwrapUnaryRecords = False" ++ ", tagSingleConstructors = False" ++ "}") (show defaultOptions) newtype SingleMaybeField = SingleMaybeField { smf :: Maybe Int } deriving (Eq, Show, Generic) singleMaybeField :: [TestTree] singleMaybeField = do (gName, gToJSON, gToEncoding, gFromJSON) <- [ ("generic", genericToJSON opts, genericToEncoding opts, parse (genericParseJSON opts)) , ("th", toJSON, toEncoding, fromJSON) ] return $ testCase gName $ do assertEqual "toJSON" Null (gToJSON v) assertEqual "toEncoding" (toEncoding (gToJSON v)) (gToEncoding v) assertEqual "fromJSON" (Success v) (gFromJSON Null) where v = SingleMaybeField Nothing opts = defaultOptions{omitNothingFields=True,unwrapUnaryRecords=True} newtype EmbeddedJSONTest = EmbeddedJSONTest Int deriving (Eq, Show) instance FromJSON EmbeddedJSONTest where parseJSON = withObject "Object" $ \o -> EmbeddedJSONTest <$> (o .: "prop" >>= withEmbeddedJSON "Quoted Int" parseJSON) withEmbeddedJSONTest :: Assertion withEmbeddedJSONTest = assertEqual "Unquote embedded JSON" (Right $ EmbeddedJSONTest 1) (eitherDecode "{\"prop\":\"1\"}") -- Regression test for https://github.com/bos/aeson/issues/627 newtype SingleFieldCon = SingleFieldCon Int deriving (Eq, Show, Generic) instance FromJSON SingleFieldCon where parseJSON = genericParseJSON defaultOptions{unwrapUnaryRecords=True} -- This option should have no effect on this type singleFieldCon :: Assertion singleFieldCon = assertEqual "fromJSON" (Right (SingleFieldCon 0)) (eitherDecode "0") ratioDenominator0 :: Assertion ratioDenominator0 = assertEqual "Ratio with denominator 0" (Left "Error in $: Ratio denominator was 0") (eitherDecode "{ \"numerator\": 1, \"denominator\": 0 }" :: Either String Rational) bigScientificExponent :: Assertion bigScientificExponent = assertEqual "Encoding an integral scientific with a large exponent should normalize it" "1.0e2000" (encode (scientific 1 2000 :: Scientific)) bigIntegerDecoding :: Assertion bigIntegerDecoding = assertEqual "Decoding an Integer with a large exponent should fail" (Left "Error in $: expected a number with exponent <= 1024, encountered Number") ((eitherDecode :: L.ByteString -> Either String Integer) "1e2000") bigNaturalDecoding :: Assertion bigNaturalDecoding = assertEqual "Decoding a Natural with a large exponent should fail" (Left "Error in $: expected a number with exponent <= 1024, encountered Number") ((eitherDecode :: L.ByteString -> Either String Integer) "1e2000") bigIntegerKeyDecoding :: Assertion bigIntegerKeyDecoding = assertEqual "Decoding an Integer key with a large exponent should fail" (Left "Error in $['1e2000']: expected a number with exponent <= 1024, encountered Number") ((eitherDecode :: L.ByteString -> Either String (HashMap Integer Value)) "{ \"1e2000\": null }") bigNaturalKeyDecoding :: Assertion bigNaturalKeyDecoding = assertEqual "Decoding an Integer key with a large exponent should fail" (Left "Error in $['1e2000']: expected a number with exponent <= 1024, encountered Number") ((eitherDecode :: L.ByteString -> Either String (HashMap Natural Value)) "{ \"1e2000\": null }") deriveJSON defaultOptions{omitNothingFields=True} ''MyRecord deriveToJSON defaultOptions ''Foo deriveToJSON1 defaultOptions ''Foo deriveJSON defaultOptions{omitNothingFields=True,unwrapUnaryRecords=True} ''SingleMaybeField aeson-1.4.2.0/tests/UnitTests/0000755000000000000000000000000000000000000014214 5ustar0000000000000000aeson-1.4.2.0/tests/UnitTests/NullaryConstructors.hs0000644000000000000000000000562500000000000020637 0ustar0000000000000000{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-deprecations #-} module UnitTests.NullaryConstructors ( nullaryConstructors ) where import Prelude.Compat import Data.Aeson (decode, eitherDecode, fromEncoding, Value) import Data.Aeson.Internal (IResult (..), iparse) import Data.Aeson.Types (Parser) import Data.ByteString.Builder (toLazyByteString) import Data.Maybe (fromJust) import Encoders import Test.Tasty.HUnit ((@=?), Assertion) import Types import qualified Data.ByteString.Lazy.Char8 as L nullaryConstructors :: [Assertion] nullaryConstructors = [ dec "\"C1\"" @=? thNullaryToJSONString C1 , dec "\"C1\"" @=? gNullaryToJSONString C1 , dec "{\"c1\":[]}" @=? thNullaryToJSONObjectWithSingleField C1 , dec "{\"c1\":[]}" @=? gNullaryToJSONObjectWithSingleField C1 , dec "[\"c1\",[]]" @=? gNullaryToJSON2ElemArray C1 , dec "[\"c1\",[]]" @=? thNullaryToJSON2ElemArray C1 , dec "{\"tag\":\"c1\"}" @=? thNullaryToJSONTaggedObject C1 , dec "{\"tag\":\"c1\"}" @=? gNullaryToJSONTaggedObject C1 , decE "\"C1\"" @=? enc (gNullaryToEncodingString C1) , decE "\"C1\"" @=? enc (thNullaryToEncodingString C1) , decE "[\"c1\",[]]" @=? enc (gNullaryToEncoding2ElemArray C1) , decE "[\"c1\",[]]" @=? enc (thNullaryToEncoding2ElemArray C1) , decE "{\"c1\":[]}" @=? enc (thNullaryToEncodingObjectWithSingleField C1) , decE "{\"c1\":[]}" @=? enc (gNullaryToEncodingObjectWithSingleField C1) , decE "{\"tag\":\"c1\"}" @=? enc (thNullaryToEncodingTaggedObject C1) , decE "{\"tag\":\"c1\"}" @=? enc (gNullaryToEncodingTaggedObject C1) , ISuccess C1 @=? parse thNullaryParseJSONTaggedObject (dec "{\"tag\":\"c1\"}") , ISuccess C1 @=? parse gNullaryParseJSONTaggedObject (dec "{\"tag\":\"c1\"}") , ISuccess C1 @=? parse thNullaryParseJSONString (dec "\"C1\"") , ISuccess C1 @=? parse gNullaryParseJSONString (dec "\"C1\"") , ISuccess C1 @=? parse thNullaryParseJSON2ElemArray (dec "[\"c1\",[]]") , ISuccess C1 @=? parse gNullaryParseJSON2ElemArray (dec "[\"c1\",[]]") , ISuccess C1 @=? parse thNullaryParseJSONObjectWithSingleField (dec "{\"c1\":[]}") , ISuccess C1 @=? parse gNullaryParseJSONObjectWithSingleField (dec "{\"c1\":[]}") -- Make sure that the old `"contents" : []' is still allowed , ISuccess C1 @=? parse thNullaryParseJSONTaggedObject (dec "{\"tag\":\"c1\",\"contents\":[]}") , ISuccess C1 @=? parse gNullaryParseJSONTaggedObject (dec "{\"tag\":\"c1\",\"contents\":[]}") ] where enc = eitherDecode . toLazyByteString . fromEncoding dec :: L.ByteString -> Value dec = fromJust . decode decE :: L.ByteString -> Either String Value decE = eitherDecode parse :: (a -> Parser b) -> a -> IResult b parse parsejson v = iparse parsejson v