Skip to content

Instantly share code, notes, and snippets.

Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save justinwoo/9d0bb67a84c227f327da7171bb7105c2 to your computer and use it in GitHub Desktop.
Save justinwoo/9d0bb67a84c227f327da7171bb7105c2 to your computer and use it in GitHub Desktop.
When you have json that you know could be rubbish and just need a concrete parser to change how specific fields are parsed.
module Main where
import Prelude
import Effect (Effect)
import Effect.Console (logShow)
import Data.Either (Either)
import Foreign (ForeignError)
import Data.List.NonEmpty (NonEmptyList)
import Data.Maybe (fromMaybe)
import Data.Nullable as Nullable
import Record (modify)
import Simple.JSON (readJSON)
import Type.Prelude (SProxy(..))
type MyThingy =
{ a :: String
, b :: Array String
}
myThingyJsonThing1 :: String
myThingyJsonThing1 =
"""
{ "a": "hello"
, "b": null
}
"""
myThingyJsonThing2 :: String
myThingyJsonThing2 =
"""
{ "a": "hello"
, "b": []
}
"""
-- by using modify here, the type that is being parsed here uses "b" :: Nullable (Array String) from simple-json!
-- you can look at the definition of modify in purescript-record to see how the types line up!
parseMyThingyJsonFromImperfectJsonButConvertTheDirtyProperty ::
String -> Either (NonEmptyList ForeignError) MyThingy
parseMyThingyJsonFromImperfectJsonButConvertTheDirtyProperty str =
modify (SProxy :: SProxy "b") (fromMaybe [] <<< Nullable.toMaybe) <$> readJSON str
main :: Effect Unit
main = do
logShow $ parseMyThingyJsonFromImperfectJsonButConvertTheDirtyProperty myThingyJsonThing1
-- (Right { a: "hello", b: [] })
logShow $ parseMyThingyJsonFromImperfectJsonButConvertTheDirtyProperty myThingyJsonThing2
-- (Right { a: "hello", b: [] })
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment