SlideShare una empresa de Scribd logo
1 de 34
Descargar para leer sin conexión
Simple JSON Parser
Haskell School, 20th September 2016 
LEE Dongjun, redongjun@gmail.com
meetup.json
{   "rsvp_limit": 15, 
    "status": "upcoming", 
    "visibility": "public", 
    "venue": { 
        "name": "Hyperconnect, Inc", 
        "address": "14F, 5 Seocho‐daero 78‐gil, Seoc..", 
        "city": "Seoul", 
        "country": "kr", 
        "lat": 37.49721, 
        "lon": 127.027374}, 
    "id": "140930019688259", 
    "time": 1474326000, 
    "event_url": "https://www.facebook.com/events/14..", 
    "name": "Simple JSON Parser", 
    "group": { 
        "id": 1065398240148353, 
        "name": "Haskell School", 
        "join_mode": "open", 
        "group_url": "https://www.facebook.com/group.."} 
} 
Parsing Boolean
true or false
1. import the parsec library 
‐‐ Returns the parsed string 
2. string :: String ‐> Parser String 
3. parse :: Parser a ‐> name ‐> s ‐> Either ParseError a 
import Text.ParserCombinators.Parsec 
matchTrue :: Parser String 
matchTrue = string "true" 
parse matchTrue "a json parser" "true" 
Right "true" 
Parsing Boolean (cont'd)
parse matchTrue "a json parser" "false" 
                                 ^ 
Left "a json parser" (line 1, column 1): 
unexpected "f" 
expecting "true" 
parsing "false"
matchFalse :: Parser String 
matchFalse = string "false" 
parse matchFalse "a json parser" "false" 
Right "false" 
Parsec library
A monadic parser combinator library, written by Daan Leijen.
Combinator parsers are written and used within the same
programming language as the rest of the program. There is no
gap between the grammar formalism (Yacc) and the actual
programming language used (C).
Parsers are first­class values within the language.
1. Parsec module
‐‐ backwards‐compatible layer for Parsec v2 
import Text.ParserCombinators.Parsec 
‐‐ Parsec v3 
import Text.Parsec 
import Text.Parsec.String 
Parsec library (cont'd)
2. Parser type constructor
Parser a = ParsecT String () Identity a 
type Parser = Parsec String () 
type Parsec s u = ParsecT s u Identity 
data ParsecT s u m a 
ParserT monad transformer and Parser type
ParsecT s u m a is a parser with stream type s, user state type u,
underlying monad m and return type a.
fmap  :: Functor f => (a ‐> b) ‐> f a ‐> f b 
(<*>) :: Applicative f => f (a ‐> b) ‐> f a ‐> f b 
(>>=) :: Monad m => m a ‐> (a ‐> m b) ‐> m b 
Parsec library (cont'd)
3. helper functions (parse, parseTest, ...)
parse :: Stream s Identity t =>  
(Parsec s () a) ‐> SourceName ‐> s ‐> Either ParseError a 
parse p filePath input runs a parser p over Identity without user
state. The filePath is only used in error messages and may be the
empty string. Returns either a ParseError (Left) or a value of type a
(Right).
‐‐ The expression parseTest p input applies a parser p  
‐‐ against input input and prints the result to stdout.  
‐‐ Used for testing parsers 
parseTest :: (Stream s Identity t, Show a) =>  
(Parsec s () a) ‐> s ‐> IO ()
Real Boolean?
parse matchTrue "a json parser" "true" 
Right "true" ‐‐ string 
realTrue :: Parser Bool 
realTrue = True ‐‐ ? 
Dealing with a value with a context 1
import Control.Applicative (pure) 
pure :: a ‐> f a ‐‐ Bool ‐> Parser Bool 
import Control.Monad (return)
return :: a ‐> m a ‐‐ Bool ‐> Parser Bool 
realTrue :: Parser Bool 
realTrue = pure True ‐‐ or return True 
parse realTrue "a json parser" "true" 
Right True ‐‐ boolean 
Combining parsers
 >>  (bind) operator
‐‐ Sequentially compose two actions, discarding any  
‐‐ value produced by the first, 
(>>)  :: m a ‐> (_ ‐> m b) ‐> m b 
(>>=) :: m a ‐> (a ‐> m b) ‐> m b  
boolTrue :: Parser Bool 
boolTrue = matchTrue >> pure True 
do­notation style
boolTrue :: Parser Bool 
boolTrue = do 
             matchTrue 
             return True 
Combining parsers (cont'd)
Applicative style
‐‐ Sequence actions,  
‐‐ discarding the value of the first argument. 
(*>) :: Parser a ‐> Parser b ‐> Parser b 
‐‐ discarding the value of the second argument. 
(<*) :: Parser a ‐> Parser b ‐> Parser a 
boolTrue  = matchTrue *> realTrue 
boolFalse = realFalse <* matchFalse 
Real Boolean? (cont'd)
parse boolTrue "a json parser" "true" 
Right True ‐‐ real boolean 
parse boolTrue "a json parser" "false" 
Left "a json parser" (line 1, column 1): 
unexpected "f" 
expecting "true" 
parse boolFalse "a json parser" "false" 
Right False ‐‐ real boolean 
parse boolFalse "a json parser" "true" 
Left "a json parser" (line 1, column 1): 
unexpected "t" 
expecting "false" 
Matching one of multiple parsers
bool = boolTrue || boolFalse ‐‐ ? 
‐‐ the choice combinator 
(<|>) :: Parser a ‐> Parser a ‐> Parser a 
This combinator implements choice. The parser p <|> q first
applies p. If it succeeds, the value of p is returned. If p fails without
consuming any input, parser q is tried.
bool :: Parser Bool 
bool = boolTrue <|> boolFalse 
parse bool "a json parser" "true" 
Right True ‐‐ boolean 
parse bool "a json parser" "false" 
Right False ‐‐ boolean 
Parsing String Literals
"rsvp_limit"
char :: Parser Char 
noneOf :: [Char] ‐> Parser Char 
many :: Parser p ‐> Parser [p] 
stringLiteral :: Parser String 
stringLiteral =  
              char '"' *> many (noneOf """) <* char '"' 
parse stringLiteral "a json parser" ""rsvp_limit"" 
Right "rsvp_limit" 
parse stringLiteral "a json parser" "rsvp_limit" 
Left "a json parser" (line 1, column 1): 
unexpected "r" 
expecting """ 
Return Values
value = bool <|> stringLiteral :: Parser ? 
Couldn't match type ‘[Char]’ with ‘Bool’ 
Expected type: ParsecT String () Data.Functor.Id.. Bool 
Actual type: Parser String 
In the second argument of ‘(<|>)’, namely ‘stringLi..’ 
In the expression: bool <|> stringLiteral 
data JSONVal = Bool Bool 
             | String String 
‐‐           | constructor type 
‐‐           | JString String 
‐‐ JString "string" :: JSONVal 
parseJson :: Parser JSONVal 
Return Values (cont'd)
parseJson :: Parser JSONVal 
parseJson = bool <|> stringLiteral 
Couldn't match type ‘Bool’ with ‘JSONVal’ 
Expected type: Text.Parsec.Prim.ParsecT 
String () Data.Functor.Identity.Identity JSONVal 
Actual type: Parser Bool 
In the first argument of ‘(<|>)’, namely ‘bool’ 
In the expression: bool <|> stringLiteral 
Couldn't match type ‘[Char]’ with ‘JSONVal’ 
Expected type: Text.Parsec.Prim.ParsecT 
String () Data.Functor.Identity.Identity JSONVal 
Actual type: Parser String 
In the second argument of ‘(<|>)’, namely ‘stringLite..’ 
In the expression: bool <|> stringLiteral 
Failed, modules loaded: none. 
Parsing Boolean
data JSONVal = Bool Bool | ... 
parseBool :: Parser JSONVal 
parseBool =  Bool bool ‐‐ Bool (Parser Bool)? 
Dealing with a value with a context 2
The Functor class is used for types that can be mapped over.
fmap :: (a ‐> b) ‐> f a ‐> f b 
(<$>) :: (a ‐> b) ‐> Parser a ‐> Parser b 
parseBool =  Bool <$> bool ‐‐ fmap Bool bool 
parse parseBool "a json parser" "true" 
Right (Bool True) 
parse parseBool "a json parser" "false" 
Right (Bool False) 
Parsing String
data JSONVal = ... | String String 
parseString :: Parser JSONVal
parseString = String <$> stringLiteral 
parseJson :: Parser JSONVal 
parseJson = ... <|> parseString 
parse parseJson "a json parser" ""rsvp_limit"" 
Right (String "rsvp_limit") 
parse parseJson "a json parser" "true" 
Right (Bool True) 
Improving error messages
parse parseJson "a json parser" "apple" 
Left "a json parser" (line 1, column 1): 
unexpected "a" 
expecting "true", "false" or """ ‐‐ ? 
<?> :: Parser p ‐> String ‐> Parser p 
The parser p <?> msg behaves as parser p, but whenever the
parser p fails without consuming any input, it replaces expect error
messages with the expect error message msg.
parseJson = (parseBool <?> "boolean") 
        <|> (parseString <?> "string literal") 
parse parseJson "a json parser" "apple" 
Left "a json parser" (line 1, column 1): 
unexpected "a" 
expecting boolean or string literal ‐‐ replaced err msgs 
Parsing Number
15
many1 :: Parser p ‐> Parser [p] 
digit :: Parser Char 
read :: String ‐> a 
ghci> parse (many letter) "many vs many1" "20th" 
Right "" 
ghci> parse (many1 letter) "many vs many1" "20th" 
Left ... 
data JSONVal = ... | Number Integer 
parseNumber :: Parser JSONVal
parseNumber = do  
          n <‐ many1 digit ‐‐ bind(<‐) operator 
          return (Number (read n)) 
parse parseNumber "a json parser" "15" 
Right (Number 15) 
Parsing Number (cont'd)
Dealing with a value with a context 3
‐‐ Monad : Promote a function to a monad. 
liftM :: Monad m => (a1 ‐> r) ‐> m a1 ‐> m r 
liftA :: Applicative f => (a ‐> b) ‐> f a ‐> f b 
fmap :: (a ‐> b) ‐> f a ‐> f b 
inport Control.Monad (liftM) 
parseNumber :: Parser JSONVal
parseNumber = liftM (Number . read) ‐‐ String ‐> JSONVal 
                    (many1 digit) ‐‐ Parser String 
‐‐ Function composition. 
‐‐ (.) :: (b ‐> c) ‐> (a ‐> b) ‐> a ‐> c 
parse parseNumber "a json parser" "15" 
Right (Number 15) 
Parsing Float
37.4972
parse parseNumber "a json parser" "37.4972" 
Right (Number 37) ‐‐ 37.4972 ? 
data JSONVal = ... | Float Double 
parseFloat :: Parser JsonVal 
parseFloat = do 
       whole <‐ many1 digit 
       char '.' 
       decimal <‐ many1 digit 
       return $ (Float . read) (whole++"."++decimal) 
‐‐ Application operator; f $ g $ h x  =  f (g (h x)) 
‐‐ ($) :: (a ‐> b) ‐> a ‐> b 
parse parseFloat "a json parser" "37.4972" 
Right (Float 37.4972) 
Parsing Number and Float
parseJson :: Parser JSONVal 
parseJson = ... <|> parseNumber <|> parseFloat 
parse parseJson "a json parser" "15" 
Right (Number 15) 
parse parseJson "a json parser" "37.4972" 
Right (Number 37) 
parseJson :: Parser JSONVal 
parseJson = ... <|> parseFloat <|> parseNumber 
parse parseJson "a json parser" "37.4972" 
Right (Float 37.4972) 
parse parseJson "a json parser" "15" 
Left "a json parser" (line 1, column 3): 
unexpected end of input 
expecting digit or "." 
Predictive parsers
(<|>) :: Parser a ‐> Parser a ‐> Parser a 
p <|> q, The parser is called predictive since q is only tried when
parser p didn't consume any input (i.e.. the look ahead is 1). This
non­backtracking behaviour allows for both an efficient
implementation of the parser combinators and the generation of
good error messages.
testOr = string "(a)" 
     <|> string "(b)" 
ghci> run testOr "(b)" 
parse error at (line 1, column 2): 
unexpected ’b’ 
expecting ’a’ 
try combinator
try :: Parser a ‐> Parser a 
The parser try p behaves like parser p, except that it pretends that
it hasn't consumed any input when an error occurs.
parseJson :: Parser JSONVal 
parseJson = ...  
        <|> try (parseFloat) 
        <|> parseNumber 
parse parseJson "a json parser" "37.4972" 
Right (Float 37.4972) 
parse parseJson "a json parser" "15" 
Right (Number 15) 
Parsing Array
["Hello","Goodbye",true,false,true]
sepBy :: Parser a ‐> Parser sep ‐> Parser [a] 
data JSONVal = ... | Array [JSONVal] 
array :: Parser [JSONVal] 
array =  
    char '[' *> sepBy parseJson (char ',') <* char ']' 
parseArray :: Parser JSONVal 
parseArray = Array <$> array 
parseJson = ... <|> parseArray 
parse parseJson "a json parser" "[true,true,true]" 
Right (Array [Bool True,Bool True,Bool True]) 
Parsing Object
{"name":"Jun","male":true}
objectEntry :: Parser (String, JSONVal) 
objectEntry = do 
      key <‐ stringLiteral 
      char ':' 
      value <‐ parseJson 
      return (key, value) 
parse objectEntry "a json parser" ""male":true" 
Right ("male",Bool True) 
Parsing Object (cont'd)
data JSONVal = ... | Object [(String, JSONVal)] | ... 
parseObject :: Parser JSONVal
parseObject = do 
   char '{' 
   obj <‐ sepBy objectEntry (char ',')
   char '}' 
   return $ Object obj 
parseJson = ... <|> parseObject 
parse parseJson "a json parser" "{"male":true}" 
Right (Object [("male",Bool True)]) 
Whitespace
parse parseJson "a json parser" "[true, true, true]" 
                                       ^ 
Left (line 1, column 7): 
unexpected " " 
expecting boolean, string literal, digit, "[" or "{" 
oneOf :: [Char] ‐> Parser Char 
oneOf cs succeeds if the current character is in the supplied list of
characters cs. Returns the parsed character.
ws :: Parser String 
ws = many (oneOf " tn") 
lexeme p = p <* ws 
Whitespace (cont'd)
parseBool = lexeme (Bool <$> bool) 
parseString = lexeme (String <$> stringLiteral) 
... 
parseArray = Array <$> array 
array = (lexeme $ char '[') *> 
        (sepBy parseJson (lexeme $ char ',')) 
        <* (lexeme $ char ']') 
parse parseJson "a json parser" "[true, true, true]" 
Right (Array [Bool True,Bool True,Bool True]) 
simple json parser
parseFromFile :: Parser a ‐> String ‐> IO (...) 
parseFromFile p filePath runs a lazy bytestring parser p on the
input read from filePath using readFile...
ghci> parseFromFile parseJson "meetup.json" 
Right (Object [ 
   ("rsvp_limit",Number 15), 
   ("status",String "upcoming"), 
   ("visibility",String "public"), 
   ("venue",Object [ 
       ("name",String "Hyperconnect, Inc"), ... 
ghci> Right (Object x) <‐ parseFromFile parseJson "m..." 
ghci> lookup "rsvp_limit" x 
Just (Number 15) 
ghci> lookup "status" x 
Just (String "upcoming") 
Handling state
runParser :: Parsec s u a ‐> u ‐> SourceName ‐> s ‐> Ei. 
runParser p state filePath input runs parser p on the input list of
tokens input, obtained from source filePath with the initial user
state st (u).
getState :: Monad m => ParsecT s u m u 
putState :: Monad m => u ‐> ParsecT s u m () 
parseObject :: Parsec String Int JSONVal 
parseObject = do ...  
              c <‐ getState 
              putState (c+1) ... ‐‐ modifyState (+1) 
liftM (runParser (parseJson >> getState) 0 "")  
      (readFile "meetup.json") 
Right 3 
One more thing...
aeson and megaparsec, ...
Switch from Parsec to Megaparsec
Haskellschool project : scheme interpreter
Summary
parsers: string, char, noneOf, oneOf, ...
type constructor: parser, parsec, parsecT
helper functions: parse, parseTest, parseFromFile, runParser
dealing with a value with a context: pure, return, liftM, fmap
combining parsers:  >>  op, do­notation,  <* ,  *>  applicative
matching one of multiple parsers:  <|> 
data, type
improving error messages:  <?> 
predictive parser: try
handling state: getState, putState, modifyState
References
Parsec, a fast combinator parser by DAAN LEIJEN
An introduction to parsing text in Haskell with Parsec on
Wilson's blog.
Real World Haskell by Bryan O'Sullivan, Don Stewart, and
John Goerzen : Chapter 16. Using Parsec
Write Yourself a Scheme in 48 Hours/Parsing
Parsing Stuff in Haskell by Ben Clifford
Simple JSON Parser file

Más contenido relacionado

La actualidad más candente

Telerik Test studio
Telerik Test studio Telerik Test studio
Telerik Test studio Ahamad Sk
 
API Testing following the Test Pyramid
API Testing following the Test PyramidAPI Testing following the Test Pyramid
API Testing following the Test PyramidElias Nogueira
 
Moq & Fakes Framework を使った実践的ユニットテスト - BuildInsider
Moq & Fakes Framework を使った実践的ユニットテスト - BuildInsiderMoq & Fakes Framework を使った実践的ユニットテスト - BuildInsider
Moq & Fakes Framework を使った実践的ユニットテスト - BuildInsider貴志 上坂
 
Testing in-python-and-pytest-framework
Testing in-python-and-pytest-frameworkTesting in-python-and-pytest-framework
Testing in-python-and-pytest-frameworkArulalan T
 
Create an architecture for web test automation
Create an architecture for web test automationCreate an architecture for web test automation
Create an architecture for web test automationElias Nogueira
 
Introduction to testing with MSTest, Visual Studio, and Team Foundation Serve...
Introduction to testing with MSTest, Visual Studio, and Team Foundation Serve...Introduction to testing with MSTest, Visual Studio, and Team Foundation Serve...
Introduction to testing with MSTest, Visual Studio, and Team Foundation Serve...Thomas Weller
 
Windows で拡張モジュールをビルドしてみた
Windows で拡張モジュールをビルドしてみたWindows で拡張モジュールをビルドしてみた
Windows で拡張モジュールをビルドしてみたy-uti
 
これでできる! Microsoft Teams アプリ開発のポイント徹底解説
これでできる! Microsoft Teams アプリ開発のポイント徹底解説これでできる! Microsoft Teams アプリ開発のポイント徹底解説
これでできる! Microsoft Teams アプリ開発のポイント徹底解説Osamu Monoe
 
Automation Testing with Test Complete
Automation Testing with Test CompleteAutomation Testing with Test Complete
Automation Testing with Test CompleteVartika Saxena
 
Introduction à React JS
Introduction à React JSIntroduction à React JS
Introduction à React JSAbdoulaye Dieng
 
Workshop Spring - Session 1 - L'offre Spring et les bases
Workshop Spring  - Session 1 - L'offre Spring et les basesWorkshop Spring  - Session 1 - L'offre Spring et les bases
Workshop Spring - Session 1 - L'offre Spring et les basesAntoine Rey
 

La actualidad más candente (19)

Node.js
Node.jsNode.js
Node.js
 
Unit Testing (C#)
Unit Testing (C#)Unit Testing (C#)
Unit Testing (C#)
 
Telerik Test studio
Telerik Test studio Telerik Test studio
Telerik Test studio
 
API Testing following the Test Pyramid
API Testing following the Test PyramidAPI Testing following the Test Pyramid
API Testing following the Test Pyramid
 
Angular Unit Testing
Angular Unit TestingAngular Unit Testing
Angular Unit Testing
 
Moq & Fakes Framework を使った実践的ユニットテスト - BuildInsider
Moq & Fakes Framework を使った実践的ユニットテスト - BuildInsiderMoq & Fakes Framework を使った実践的ユニットテスト - BuildInsider
Moq & Fakes Framework を使った実践的ユニットテスト - BuildInsider
 
Testing in-python-and-pytest-framework
Testing in-python-and-pytest-frameworkTesting in-python-and-pytest-framework
Testing in-python-and-pytest-framework
 
Fuzzing
FuzzingFuzzing
Fuzzing
 
Angular Observables & RxJS Introduction
Angular Observables & RxJS IntroductionAngular Observables & RxJS Introduction
Angular Observables & RxJS Introduction
 
Create an architecture for web test automation
Create an architecture for web test automationCreate an architecture for web test automation
Create an architecture for web test automation
 
Transactional Memory
Transactional MemoryTransactional Memory
Transactional Memory
 
Introduction to testing with MSTest, Visual Studio, and Team Foundation Serve...
Introduction to testing with MSTest, Visual Studio, and Team Foundation Serve...Introduction to testing with MSTest, Visual Studio, and Team Foundation Serve...
Introduction to testing with MSTest, Visual Studio, and Team Foundation Serve...
 
Windows で拡張モジュールをビルドしてみた
Windows で拡張モジュールをビルドしてみたWindows で拡張モジュールをビルドしてみた
Windows で拡張モジュールをビルドしてみた
 
PHPUnit - Unit testing
PHPUnit - Unit testingPHPUnit - Unit testing
PHPUnit - Unit testing
 
これでできる! Microsoft Teams アプリ開発のポイント徹底解説
これでできる! Microsoft Teams アプリ開発のポイント徹底解説これでできる! Microsoft Teams アプリ開発のポイント徹底解説
これでできる! Microsoft Teams アプリ開発のポイント徹底解説
 
Automation Testing with Test Complete
Automation Testing with Test CompleteAutomation Testing with Test Complete
Automation Testing with Test Complete
 
Introduction à React JS
Introduction à React JSIntroduction à React JS
Introduction à React JS
 
Workshop Spring - Session 1 - L'offre Spring et les bases
Workshop Spring  - Session 1 - L'offre Spring et les basesWorkshop Spring  - Session 1 - L'offre Spring et les bases
Workshop Spring - Session 1 - L'offre Spring et les bases
 
Nunit
NunitNunit
Nunit
 

Destacado

메일플러그 기업보안메일 〈메일 아카이빙〉
메일플러그 기업보안메일 〈메일 아카이빙〉메일플러그 기업보안메일 〈메일 아카이빙〉
메일플러그 기업보안메일 〈메일 아카이빙〉MAILPLUG
 
Parse Apps with Ember.js
Parse Apps with Ember.jsParse Apps with Ember.js
Parse Apps with Ember.jsMatthew Beale
 
How to Write the Fastest JSON Parser/Writer in the World
How to Write the Fastest JSON Parser/Writer in the WorldHow to Write the Fastest JSON Parser/Writer in the World
How to Write the Fastest JSON Parser/Writer in the WorldMilo Yip
 
Security threats in Android OS + App Permissions
Security threats in Android OS + App PermissionsSecurity threats in Android OS + App Permissions
Security threats in Android OS + App PermissionsHariharan Ganesan
 
Android training day 4
Android training day 4Android training day 4
Android training day 4Vivek Bhusal
 
Tips dan Third Party Library untuk Android - Part 1
Tips dan Third Party Library untuk Android - Part 1Tips dan Third Party Library untuk Android - Part 1
Tips dan Third Party Library untuk Android - Part 1Ibnu Sina Wardy
 
Android permission system
Android permission systemAndroid permission system
Android permission systemShivang Goel
 
Anatomizing online payment systems: hack to shop
Anatomizing online payment systems: hack to shopAnatomizing online payment systems: hack to shop
Anatomizing online payment systems: hack to shopAbhinav Mishra
 
Sandbox Introduction
Sandbox IntroductionSandbox Introduction
Sandbox Introductionmsimkin
 
Web Services and Android - OSSPAC 2009
Web Services and Android - OSSPAC 2009Web Services and Android - OSSPAC 2009
Web Services and Android - OSSPAC 2009sullis
 
Android permission system
Android permission systemAndroid permission system
Android permission systemShivang Goel
 
Android secuirty permission - upload
Android secuirty   permission - uploadAndroid secuirty   permission - upload
Android secuirty permission - uploadBin Yang
 
Android AsyncTask Tutorial
Android AsyncTask TutorialAndroid AsyncTask Tutorial
Android AsyncTask TutorialPerfect APK
 
Android 6.0 permission change
Android 6.0 permission changeAndroid 6.0 permission change
Android 6.0 permission change彥彬 洪
 

Destacado (20)

메일플러그 기업보안메일 〈메일 아카이빙〉
메일플러그 기업보안메일 〈메일 아카이빙〉메일플러그 기업보안메일 〈메일 아카이빙〉
메일플러그 기업보안메일 〈메일 아카이빙〉
 
Mule parsing with json part2
Mule parsing with json part2Mule parsing with json part2
Mule parsing with json part2
 
Parse Apps with Ember.js
Parse Apps with Ember.jsParse Apps with Ember.js
Parse Apps with Ember.js
 
How to Write the Fastest JSON Parser/Writer in the World
How to Write the Fastest JSON Parser/Writer in the WorldHow to Write the Fastest JSON Parser/Writer in the World
How to Write the Fastest JSON Parser/Writer in the World
 
Security threats in Android OS + App Permissions
Security threats in Android OS + App PermissionsSecurity threats in Android OS + App Permissions
Security threats in Android OS + App Permissions
 
Android training day 4
Android training day 4Android training day 4
Android training day 4
 
Tips dan Third Party Library untuk Android - Part 1
Tips dan Third Party Library untuk Android - Part 1Tips dan Third Party Library untuk Android - Part 1
Tips dan Third Party Library untuk Android - Part 1
 
Android permission system
Android permission systemAndroid permission system
Android permission system
 
Anatomizing online payment systems: hack to shop
Anatomizing online payment systems: hack to shopAnatomizing online payment systems: hack to shop
Anatomizing online payment systems: hack to shop
 
Sandbox Introduction
Sandbox IntroductionSandbox Introduction
Sandbox Introduction
 
Web Services and Android - OSSPAC 2009
Web Services and Android - OSSPAC 2009Web Services and Android - OSSPAC 2009
Web Services and Android - OSSPAC 2009
 
Android(1)
Android(1)Android(1)
Android(1)
 
Android permission system
Android permission systemAndroid permission system
Android permission system
 
Android secuirty permission - upload
Android secuirty   permission - uploadAndroid secuirty   permission - upload
Android secuirty permission - upload
 
Android AsyncTask Tutorial
Android AsyncTask TutorialAndroid AsyncTask Tutorial
Android AsyncTask Tutorial
 
Android 6.0 permission change
Android 6.0 permission changeAndroid 6.0 permission change
Android 6.0 permission change
 
Json Tutorial
Json TutorialJson Tutorial
Json Tutorial
 
Android new permission model
Android new permission modelAndroid new permission model
Android new permission model
 
Basic Android Push Notification
Basic Android Push NotificationBasic Android Push Notification
Basic Android Push Notification
 
JSON overview and demo
JSON overview and demoJSON overview and demo
JSON overview and demo
 

Último

Boost PC performance: How more available memory can improve productivity
Boost PC performance: How more available memory can improve productivityBoost PC performance: How more available memory can improve productivity
Boost PC performance: How more available memory can improve productivityPrincipled Technologies
 
Automating Google Workspace (GWS) & more with Apps Script
Automating Google Workspace (GWS) & more with Apps ScriptAutomating Google Workspace (GWS) & more with Apps Script
Automating Google Workspace (GWS) & more with Apps Scriptwesley chun
 
Presentation on how to chat with PDF using ChatGPT code interpreter
Presentation on how to chat with PDF using ChatGPT code interpreterPresentation on how to chat with PDF using ChatGPT code interpreter
Presentation on how to chat with PDF using ChatGPT code interpreternaman860154
 
Slack Application Development 101 Slides
Slack Application Development 101 SlidesSlack Application Development 101 Slides
Slack Application Development 101 Slidespraypatel2
 
IAC 2024 - IA Fast Track to Search Focused AI Solutions
IAC 2024 - IA Fast Track to Search Focused AI SolutionsIAC 2024 - IA Fast Track to Search Focused AI Solutions
IAC 2024 - IA Fast Track to Search Focused AI SolutionsEnterprise Knowledge
 
Breaking the Kubernetes Kill Chain: Host Path Mount
Breaking the Kubernetes Kill Chain: Host Path MountBreaking the Kubernetes Kill Chain: Host Path Mount
Breaking the Kubernetes Kill Chain: Host Path MountPuma Security, LLC
 
A Year of the Servo Reboot: Where Are We Now?
A Year of the Servo Reboot: Where Are We Now?A Year of the Servo Reboot: Where Are We Now?
A Year of the Servo Reboot: Where Are We Now?Igalia
 
What Are The Drone Anti-jamming Systems Technology?
What Are The Drone Anti-jamming Systems Technology?What Are The Drone Anti-jamming Systems Technology?
What Are The Drone Anti-jamming Systems Technology?Antenna Manufacturer Coco
 
The Role of Taxonomy and Ontology in Semantic Layers - Heather Hedden.pdf
The Role of Taxonomy and Ontology in Semantic Layers - Heather Hedden.pdfThe Role of Taxonomy and Ontology in Semantic Layers - Heather Hedden.pdf
The Role of Taxonomy and Ontology in Semantic Layers - Heather Hedden.pdfEnterprise Knowledge
 
Advantages of Hiring UIUX Design Service Providers for Your Business
Advantages of Hiring UIUX Design Service Providers for Your BusinessAdvantages of Hiring UIUX Design Service Providers for Your Business
Advantages of Hiring UIUX Design Service Providers for Your BusinessPixlogix Infotech
 
How to Troubleshoot Apps for the Modern Connected Worker
How to Troubleshoot Apps for the Modern Connected WorkerHow to Troubleshoot Apps for the Modern Connected Worker
How to Troubleshoot Apps for the Modern Connected WorkerThousandEyes
 
2024: Domino Containers - The Next Step. News from the Domino Container commu...
2024: Domino Containers - The Next Step. News from the Domino Container commu...2024: Domino Containers - The Next Step. News from the Domino Container commu...
2024: Domino Containers - The Next Step. News from the Domino Container commu...Martijn de Jong
 
Driving Behavioral Change for Information Management through Data-Driven Gree...
Driving Behavioral Change for Information Management through Data-Driven Gree...Driving Behavioral Change for Information Management through Data-Driven Gree...
Driving Behavioral Change for Information Management through Data-Driven Gree...Enterprise Knowledge
 
Finology Group – Insurtech Innovation Award 2024
Finology Group – Insurtech Innovation Award 2024Finology Group – Insurtech Innovation Award 2024
Finology Group – Insurtech Innovation Award 2024The Digital Insurer
 
Real Time Object Detection Using Open CV
Real Time Object Detection Using Open CVReal Time Object Detection Using Open CV
Real Time Object Detection Using Open CVKhem
 
GenCyber Cyber Security Day Presentation
GenCyber Cyber Security Day PresentationGenCyber Cyber Security Day Presentation
GenCyber Cyber Security Day PresentationMichael W. Hawkins
 
🐬 The future of MySQL is Postgres 🐘
🐬  The future of MySQL is Postgres   🐘🐬  The future of MySQL is Postgres   🐘
🐬 The future of MySQL is Postgres 🐘RTylerCroy
 
Workshop - Best of Both Worlds_ Combine KG and Vector search for enhanced R...
Workshop - Best of Both Worlds_ Combine  KG and Vector search for  enhanced R...Workshop - Best of Both Worlds_ Combine  KG and Vector search for  enhanced R...
Workshop - Best of Both Worlds_ Combine KG and Vector search for enhanced R...Neo4j
 
08448380779 Call Girls In Greater Kailash - I Women Seeking Men
08448380779 Call Girls In Greater Kailash - I Women Seeking Men08448380779 Call Girls In Greater Kailash - I Women Seeking Men
08448380779 Call Girls In Greater Kailash - I Women Seeking MenDelhi Call girls
 
[2024]Digital Global Overview Report 2024 Meltwater.pdf
[2024]Digital Global Overview Report 2024 Meltwater.pdf[2024]Digital Global Overview Report 2024 Meltwater.pdf
[2024]Digital Global Overview Report 2024 Meltwater.pdfhans926745
 

Último (20)

Boost PC performance: How more available memory can improve productivity
Boost PC performance: How more available memory can improve productivityBoost PC performance: How more available memory can improve productivity
Boost PC performance: How more available memory can improve productivity
 
Automating Google Workspace (GWS) & more with Apps Script
Automating Google Workspace (GWS) & more with Apps ScriptAutomating Google Workspace (GWS) & more with Apps Script
Automating Google Workspace (GWS) & more with Apps Script
 
Presentation on how to chat with PDF using ChatGPT code interpreter
Presentation on how to chat with PDF using ChatGPT code interpreterPresentation on how to chat with PDF using ChatGPT code interpreter
Presentation on how to chat with PDF using ChatGPT code interpreter
 
Slack Application Development 101 Slides
Slack Application Development 101 SlidesSlack Application Development 101 Slides
Slack Application Development 101 Slides
 
IAC 2024 - IA Fast Track to Search Focused AI Solutions
IAC 2024 - IA Fast Track to Search Focused AI SolutionsIAC 2024 - IA Fast Track to Search Focused AI Solutions
IAC 2024 - IA Fast Track to Search Focused AI Solutions
 
Breaking the Kubernetes Kill Chain: Host Path Mount
Breaking the Kubernetes Kill Chain: Host Path MountBreaking the Kubernetes Kill Chain: Host Path Mount
Breaking the Kubernetes Kill Chain: Host Path Mount
 
A Year of the Servo Reboot: Where Are We Now?
A Year of the Servo Reboot: Where Are We Now?A Year of the Servo Reboot: Where Are We Now?
A Year of the Servo Reboot: Where Are We Now?
 
What Are The Drone Anti-jamming Systems Technology?
What Are The Drone Anti-jamming Systems Technology?What Are The Drone Anti-jamming Systems Technology?
What Are The Drone Anti-jamming Systems Technology?
 
The Role of Taxonomy and Ontology in Semantic Layers - Heather Hedden.pdf
The Role of Taxonomy and Ontology in Semantic Layers - Heather Hedden.pdfThe Role of Taxonomy and Ontology in Semantic Layers - Heather Hedden.pdf
The Role of Taxonomy and Ontology in Semantic Layers - Heather Hedden.pdf
 
Advantages of Hiring UIUX Design Service Providers for Your Business
Advantages of Hiring UIUX Design Service Providers for Your BusinessAdvantages of Hiring UIUX Design Service Providers for Your Business
Advantages of Hiring UIUX Design Service Providers for Your Business
 
How to Troubleshoot Apps for the Modern Connected Worker
How to Troubleshoot Apps for the Modern Connected WorkerHow to Troubleshoot Apps for the Modern Connected Worker
How to Troubleshoot Apps for the Modern Connected Worker
 
2024: Domino Containers - The Next Step. News from the Domino Container commu...
2024: Domino Containers - The Next Step. News from the Domino Container commu...2024: Domino Containers - The Next Step. News from the Domino Container commu...
2024: Domino Containers - The Next Step. News from the Domino Container commu...
 
Driving Behavioral Change for Information Management through Data-Driven Gree...
Driving Behavioral Change for Information Management through Data-Driven Gree...Driving Behavioral Change for Information Management through Data-Driven Gree...
Driving Behavioral Change for Information Management through Data-Driven Gree...
 
Finology Group – Insurtech Innovation Award 2024
Finology Group – Insurtech Innovation Award 2024Finology Group – Insurtech Innovation Award 2024
Finology Group – Insurtech Innovation Award 2024
 
Real Time Object Detection Using Open CV
Real Time Object Detection Using Open CVReal Time Object Detection Using Open CV
Real Time Object Detection Using Open CV
 
GenCyber Cyber Security Day Presentation
GenCyber Cyber Security Day PresentationGenCyber Cyber Security Day Presentation
GenCyber Cyber Security Day Presentation
 
🐬 The future of MySQL is Postgres 🐘
🐬  The future of MySQL is Postgres   🐘🐬  The future of MySQL is Postgres   🐘
🐬 The future of MySQL is Postgres 🐘
 
Workshop - Best of Both Worlds_ Combine KG and Vector search for enhanced R...
Workshop - Best of Both Worlds_ Combine  KG and Vector search for  enhanced R...Workshop - Best of Both Worlds_ Combine  KG and Vector search for  enhanced R...
Workshop - Best of Both Worlds_ Combine KG and Vector search for enhanced R...
 
08448380779 Call Girls In Greater Kailash - I Women Seeking Men
08448380779 Call Girls In Greater Kailash - I Women Seeking Men08448380779 Call Girls In Greater Kailash - I Women Seeking Men
08448380779 Call Girls In Greater Kailash - I Women Seeking Men
 
[2024]Digital Global Overview Report 2024 Meltwater.pdf
[2024]Digital Global Overview Report 2024 Meltwater.pdf[2024]Digital Global Overview Report 2024 Meltwater.pdf
[2024]Digital Global Overview Report 2024 Meltwater.pdf
 

Simple JSON parser