Skip to content

Instantly share code, notes, and snippets.

@joneshf
Created September 5, 2017 05:10
Show Gist options
  • Save joneshf/79787bc20bd678db690cc22480fb86d9 to your computer and use it in GitHub Desktop.
Save joneshf/79787bc20bd678db690cc22480fb86d9 to your computer and use it in GitHub Desktop.
module Main where
import Prelude
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, logShow)
import Control.Monad.Except (runExcept)
import Data.Either (Either(..))
import Data.Foreign (ForeignError(..))
import Data.Foreign.Generic (defaultOptions, genericDecodeJSON)
import Data.Foreign.Generic.Types (Options)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.List.Types (List(..))
import Data.Newtype (unwrap)
import Data.NonEmpty (NonEmpty(..))
main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do
logShow $ handleResponse """{}"""
logShow $ handleResponse """{ "bar": 123, "baz": true }"""
handleResponse :: String -> String
handleResponse body = case runExcept (genericDecodeJSON options body) of
Left nel -> handleErrors $ unwrap nel
Right (Foo record) -> "We decoded properly: " <> show (Foo record)
where
options :: Options
options = defaultOptions { unwrapSingleConstructors = true }
handleErrors :: NonEmpty List ForeignError -> String
handleErrors = case _ of
NonEmpty error Nil -> handleError error
_ -> "Some other pretty printed error"
handleError :: ForeignError -> String
handleError = case _ of
ErrorAtIndex _ error -> handleError error
ErrorAtProperty _ error -> handleError error
TypeMismatch _ "Undefined" -> "Empty request body"
_ -> "Some other thing here as well"
newtype Foo
= Foo
{ bar :: Int
, baz :: Boolean
}
derive instance genericFoo :: Generic Foo _
instance showFoo :: Show Foo where
show = genericShow
➜ foreign-stuff git:(master) ✗ $(npm bin)/pulp run
* Building project in /home/joneshf/programming/kika/foreign-stuff
* Build successful.
"Empty request body"
"We decoded properly: (Foo { bar: 123, baz: true })"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment