SlideShare a Scribd company logo
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

More Related Content

PDF
manual 7.pdf
PPTX
Pogradeci
PDF
메일플러그 기업보안메일 〈메일 아카이빙〉
PPTX
Mule parsing with json part2
PDF
Parse Apps with Ember.js
PPTX
How to Write the Fastest JSON Parser/Writer in the World
PPTX
Security threats in Android OS + App Permissions
ODP
Android training day 4
manual 7.pdf
Pogradeci
메일플러그 기업보안메일 〈메일 아카이빙〉
Mule parsing with json part2
Parse Apps with Ember.js
How to Write the Fastest JSON Parser/Writer in the World
Security threats in Android OS + App Permissions
Android training day 4

Viewers also liked (20)

PPTX
Tips dan Third Party Library untuk Android - Part 1
ODP
Android permission system
PDF
Anatomizing online payment systems: hack to shop
PPT
Sandbox Introduction
PDF
Web Services and Android - OSSPAC 2009
ODP
Android(1)
ODP
Android permission system
PPTX
Android secuirty permission - upload
PPTX
Android AsyncTask Tutorial
PDF
Android 6.0 permission change
ODP
Json Tutorial
PDF
Android new permission model
PDF
Basic Android Push Notification
PPTX
JSON overview and demo
PDF
App Permissions
PDF
Android webservices
ODP
Android porting for dummies @droidconin 2011
PPTX
Android json parser tutorial – example
PDF
Android security
PPTX
Android - Bluetooth
Tips dan Third Party Library untuk Android - Part 1
Android permission system
Anatomizing online payment systems: hack to shop
Sandbox Introduction
Web Services and Android - OSSPAC 2009
Android(1)
Android permission system
Android secuirty permission - upload
Android AsyncTask Tutorial
Android 6.0 permission change
Json Tutorial
Android new permission model
Basic Android Push Notification
JSON overview and demo
App Permissions
Android webservices
Android porting for dummies @droidconin 2011
Android json parser tutorial – example
Android security
Android - Bluetooth
Ad

Similar to Simple JSON parser (14)

PDF
Combinator parsing
ODP
Parsec
PDF
hySON
PDF
hySON - D2Fest
PPTX
Screaming fast json parsing on Android
PDF
How we use Instaparse
PDF
Parsing swiftly-Cocoaheads-2015-02-12
DOC
quick json parser
KEY
Invertible-syntax 入門
PDF
TI1220 Lecture 9: Parsing & interpretation
PDF
TMPA-2017: Functional Parser of Markdown Language Based on Monad Combining an...
PDF
The Art Of Parsing @ Devoxx France 2014
PDF
Transform your State \/ Err
PDF
Petitparser at the Deep into Smalltalk School 2011
Combinator parsing
Parsec
hySON
hySON - D2Fest
Screaming fast json parsing on Android
How we use Instaparse
Parsing swiftly-Cocoaheads-2015-02-12
quick json parser
Invertible-syntax 入門
TI1220 Lecture 9: Parsing & interpretation
TMPA-2017: Functional Parser of Markdown Language Based on Monad Combining an...
The Art Of Parsing @ Devoxx France 2014
Transform your State \/ Err
Petitparser at the Deep into Smalltalk School 2011
Ad

Recently uploaded (20)

PDF
NewMind AI Weekly Chronicles - August'25 Week I
PDF
KodekX | Application Modernization Development
PDF
Diabetes mellitus diagnosis method based random forest with bat algorithm
PPTX
Big Data Technologies - Introduction.pptx
PDF
Approach and Philosophy of On baking technology
PDF
Review of recent advances in non-invasive hemoglobin estimation
DOCX
The AUB Centre for AI in Media Proposal.docx
PDF
7 ChatGPT Prompts to Help You Define Your Ideal Customer Profile.pdf
PDF
The Rise and Fall of 3GPP – Time for a Sabbatical?
PDF
Electronic commerce courselecture one. Pdf
PDF
Chapter 3 Spatial Domain Image Processing.pdf
PPT
“AI and Expert System Decision Support & Business Intelligence Systems”
PDF
Profit Center Accounting in SAP S/4HANA, S4F28 Col11
PDF
Advanced methodologies resolving dimensionality complications for autism neur...
PDF
Reach Out and Touch Someone: Haptics and Empathic Computing
PDF
Empathic Computing: Creating Shared Understanding
PPTX
sap open course for s4hana steps from ECC to s4
PPTX
KOM of Painting work and Equipment Insulation REV00 update 25-dec.pptx
PDF
Unlocking AI with Model Context Protocol (MCP)
PPTX
Cloud computing and distributed systems.
NewMind AI Weekly Chronicles - August'25 Week I
KodekX | Application Modernization Development
Diabetes mellitus diagnosis method based random forest with bat algorithm
Big Data Technologies - Introduction.pptx
Approach and Philosophy of On baking technology
Review of recent advances in non-invasive hemoglobin estimation
The AUB Centre for AI in Media Proposal.docx
7 ChatGPT Prompts to Help You Define Your Ideal Customer Profile.pdf
The Rise and Fall of 3GPP – Time for a Sabbatical?
Electronic commerce courselecture one. Pdf
Chapter 3 Spatial Domain Image Processing.pdf
“AI and Expert System Decision Support & Business Intelligence Systems”
Profit Center Accounting in SAP S/4HANA, S4F28 Col11
Advanced methodologies resolving dimensionality complications for autism neur...
Reach Out and Touch Someone: Haptics and Empathic Computing
Empathic Computing: Creating Shared Understanding
sap open course for s4hana steps from ECC to s4
KOM of Painting work and Equipment Insulation REV00 update 25-dec.pptx
Unlocking AI with Model Context Protocol (MCP)
Cloud computing and distributed systems.

Simple JSON parser