Skip to content

Instantly share code, notes, and snippets.

@cryogenian
Created June 27, 2016 10:38
Show Gist options
  • Save cryogenian/1bdab2efecfd46011a4b05537c0f4113 to your computer and use it in GitHub Desktop.
Save cryogenian/1bdab2efecfd46011a4b05537c0f4113 to your computer and use it in GitHub Desktop.
Argonaut example
{
"foo": [
{"bar": 1, "baz": 12},
{"bar": 14, "baz": "quux"}
]
}
module Main where
import Prelude
import Control.Alt ((<|>))
import Control.Monad.Aff (launchAff)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Exception (EXCEPTION)
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Argonaut as A
import Data.Either (Either(..))
import Node.Encoding (Encoding(UTF8))
import Node.FS (FS)
import Node.FS.Aff (readTextFile)
import Debug.Trace as T
-- | We're going to decode something like
-- | ```
-- | {
-- | "foo": [
-- | {"bar": 1, "baz": 12},
-- | {"bar": 14, "baz": "quux"}
-- | ]
-- | }
-- | ```
-- | This is instance based approach. We define newtype wrappers to provide instances
-- | and use fancy combinators like `.?` (this thing tries to get object field and decode it)
newtype BarBaz =
BarBaz { bar Number
, baz Either Int String
}
instance decodeJsonBarBazDecodeJson BarBaz where
decodeJson json = do
-- decode json to JObject (StrMap Json)
obj ← decodeJson json
-- get `bar` field and decode it. Type for decoding is infered from last expression
-- it should be `Number`
bar ← obj .? "bar"
-- get baz field and wrap result with `Either`n
baz ←
-- try to decode it as `Int`
(obj .? "baz" >>= pure <<< Right)
<|>
-- if it fails try to decode it as `String`
(obj .? "baz" >>= pure <<< Left)
-- return value wrapped with `Right`
pure $ BarBaz { bar, baz }
-- Main example, note that using instances allows us automatically decode common things
-- Like arrays, lists, maybes (funny but we can't decode `Int|String` to `Either Int String`,
-- see https://github.com/purescript-contrib/purescript-argonaut-codecs/blob/master/src/Data/Argonaut/Decode/Class.purs#L82)
newtype Foo = Foo { foo Array BarBaz }
instance decodeJsonFooDecodeJson Foo where
decodeJson json = do
-- Again decode to JObject
obj ← decodeJson json
-- get field and decode
foo ← obj .? "foo"
-- return value wrapped with Right
pure $ Foo { foo }
-- Here 0.9.1 purescript is used in 0.8.5 `launchAff` has `Eff _ Unit` type and we can omit `void`
main e. Eff (fs FS, err EXCEPTION|e) Unit
main = void $ launchAff do
-- read file and get continuation (Aff) with its content
txt ← readTextFile UTF8 "./input.json"
let
-- We need type annotation here because `traceAnyA` defined `∀ a m. (Applicative m) ⇒ a → m Unit`
-- and purescript has no idea what's that `a` is.
fooOrError Either String Foo
fooOrError =
-- Parse String from that continuation and throw error if it's invalid json
A.jsonParser txt
-- Decode
>>= decodeJson
-- Just log decoded value
T.traceAnyA fooOrError
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment