Commit 849e94c9 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[graph] package upgrade + add date to screenshot

parent 7d4c8790
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
let mkPackage = let mkPackage =
https://raw.githubusercontent.com/purescript/package-sets/psc-0.13.8-20200724/src/mkPackage.dhall sha256:0b197efa1d397ace6eb46b243ff2d73a3da5638d8d0ac8473e8e4a8fc528cf57 https://raw.githubusercontent.com/purescript/package-sets/psc-0.13.8-20200822/src/mkPackage.dhall sha256:0b197efa1d397ace6eb46b243ff2d73a3da5638d8d0ac8473e8e4a8fc528cf57
--let upstream =
-- https://github.com/purescript/package-sets/releases/download/psc-0.13.8-20200822/packages.dhall sha256:2230fc547841b54bca815eb0058414aa03ed7b675042f8b3dda644e1952824e5
let upstream = let upstream =
https://github.com/purescript/package-sets/releases/download/psc-0.13.8-20200724/packages.dhall sha256:2230fc547841b54bca815eb0058414aa03ed7b675042f8b3dda644e1952824e5 ./packages-0.13.8-20200822.dhall
let overrides = let overrides =
{ thermite = { thermite =
......
...@@ -6,8 +6,10 @@ ...@@ -6,8 +6,10 @@
"aff-promise", "aff-promise",
"affjax", "affjax",
"argonaut", "argonaut",
"codec-argonaut",
"console", "console",
"css", "css",
"datetime",
"debug", "debug",
"dom-filereader", "dom-filereader",
"dom-simple", "dom-simple",
...@@ -23,6 +25,7 @@ ...@@ -23,6 +25,7 @@
"maybe", "maybe",
"milkis", "milkis",
"nonempty", "nonempty",
"now",
"numbers", "numbers",
"prelude", "prelude",
"psci-support", "psci-support",
......
...@@ -7,10 +7,14 @@ module Gargantext.Components.GraphExplorer.Button ...@@ -7,10 +7,14 @@ module Gargantext.Components.GraphExplorer.Button
import Prelude import Prelude
import Data.Enum (fromEnum)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import DOM.Simple.Console (log2) import Data.DateTime as DDT
import Data.DateTime.Instant as DDI
import Data.String as DS
import Effect (Effect) import Effect (Effect)
import Effect.Aff (launchAff_) import Effect.Aff (launchAff_)
import Effect.Now as EN
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
...@@ -55,7 +59,17 @@ cameraButton session id sigmaRef = simpleButton { ...@@ -55,7 +59,17 @@ cameraButton session id sigmaRef = simpleButton {
let sigma = R.readRef sigmaRef let sigma = R.readRef sigmaRef
Sigmax.dependOnSigma sigma "[cameraButton] sigma: Nothing" $ \s -> do Sigmax.dependOnSigma sigma "[cameraButton] sigma: Nothing" $ \s -> do
screen <- Sigma.takeScreenshot s screen <- Sigma.takeScreenshot s
now <- EN.now
let nowdt = DDI.toDateTime now
nowd = DDT.date nowdt
nowt = DDT.time nowdt
nowStr = DS.joinWith "-" [ show $ fromEnum $ DDT.year nowd
, show $ fromEnum $ DDT.month nowd
, show $ fromEnum $ DDT.day nowd
, show $ fromEnum $ DDT.hour nowt
, show $ fromEnum $ DDT.minute nowt
, show $ fromEnum $ DDT.second nowt ]
launchAff_ $ do launchAff_ $ do
uploadArbitraryDataURL session id (Just "screenshot.png") screen uploadArbitraryDataURL session id (Just $ nowStr <> "-" <> "screenshot.png") screen
, text: "Screenshot" , text: "Screenshot"
} }
...@@ -61,6 +61,7 @@ import Prelude ...@@ -61,6 +61,7 @@ import Prelude
import Control.Monad.Cont.Trans (lift) import Control.Monad.Cont.Trans (lift)
import Control.Monad.State (class MonadState, execState) import Control.Monad.State (class MonadState, execState)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.:), (.:!), (.:?), (:=), (:=?), (~>), (~>?)) import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.:), (.:!), (.:?), (:=), (:=?), (~>), (~>?))
import Data.Argonaut.Decode.Error (JsonDecodeError(..))
import Data.Array (head) import Data.Array (head)
import Data.Array as A import Data.Array as A
import Data.Bifunctor (lmap) import Data.Bifunctor (lmap)
...@@ -409,7 +410,7 @@ instance decodeJsonReplace :: (DecodeJson a, Eq a) => DecodeJson (Replace a) whe ...@@ -409,7 +410,7 @@ instance decodeJsonReplace :: (DecodeJson a, Eq a) => DecodeJson (Replace a) whe
case Tuple mold mnew of case Tuple mold mnew of
Tuple (Just old) (Just new) -> pure $ replace old new Tuple (Just old) (Just new) -> pure $ replace old new
Tuple Nothing Nothing -> pure Keep Tuple Nothing Nothing -> pure Keep
_ -> Left "decodeJsonReplace" _ -> Left $ TypeMismatch "decodeJsonReplace"
-- Representing a PatchSet as `Map a Boolean` would have the advantage -- Representing a PatchSet as `Map a Boolean` would have the advantage
-- of enforcing rem and add to be disjoint. -- of enforcing rem and add to be disjoint.
......
module Gargantext.Components.Nodes.Corpus.Types where module Gargantext.Components.Nodes.Corpus.Types where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, (.:), (:=), (~>), jsonEmptyObject) import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, (.:), (:=), (~>), jsonEmptyObject)
import Data.Argonaut.Decode.Error (JsonDecodeError(..))
import Data.List as List import Data.List as List
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
...@@ -124,7 +125,7 @@ instance decodeFTField :: DecodeJson (Field FieldType) where ...@@ -124,7 +125,7 @@ instance decodeFTField :: DecodeJson (Field FieldType) where
tag <- data_ .: "tag" tag <- data_ .: "tag"
text <- data_ .: "text" text <- data_ .: "text"
pure $ Markdown {tag, text} pure $ Markdown {tag, text}
_ -> Left $ "Unsupported 'type' " <> type_ _ -> Left $ TypeMismatch $ "Unsupported 'type' " <> type_
pure $ Field {name, typ} pure $ Field {name, typ}
instance encodeFTField :: EncodeJson (Field FieldType) where instance encodeFTField :: EncodeJson (Field FieldType) where
......
module Gargantext.Config.REST where module Gargantext.Config.REST where
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printError, request)
import Affjax.RequestBody (RequestBody(..), formData, formURLEncoded) import Affjax.RequestBody (RequestBody(..), formData, formURLEncoded)
import Affjax.RequestHeader as ARH import Affjax.RequestHeader as ARH
import Affjax.ResponseFormat as ResponseFormat import Affjax.ResponseFormat as ResponseFormat
...@@ -49,16 +49,16 @@ send m mtoken url reqbody = do ...@@ -49,16 +49,16 @@ send m mtoken url reqbody = do
Just token -> liftEffect $ do Just token -> liftEffect $ do
let cookie = "JWT-Cookie=" <> token <> "; Path=/;" --" HttpOnly; Secure; SameSite=Lax" let cookie = "JWT-Cookie=" <> token <> "; Path=/;" --" HttpOnly; Secure; SameSite=Lax"
R2.setCookie cookie R2.setCookie cookie
case affResp.body of case affResp of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- liftEffect $ log $ printError err
throwError $ error $ printResponseFormatError err throwError $ error $ printError err
Right json -> do Right resp -> do
--_ <- liftEffect $ log json.status --_ <- liftEffect $ log json.status
--_ <- liftEffect $ log json.headers --_ <- liftEffect $ log json.headers
--_ <- liftEffect $ log json.body --_ <- liftEffect $ log json.body
case decodeJson json of case decodeJson resp.body of
Left err -> throwError $ error $ "decodeJson affResp.body: " <> err Left err -> throwError $ error $ "decodeJson affResp.body: " <> show err
Right b -> pure b Right b -> pure b
noReqBody :: Maybe Unit noReqBody :: Maybe Unit
...@@ -101,16 +101,16 @@ postWwwUrlencoded mtoken url bodyParams = do ...@@ -101,16 +101,16 @@ postWwwUrlencoded mtoken url bodyParams = do
) mtoken ) mtoken
, content = Just $ formURLEncoded urlEncodedBody , content = Just $ formURLEncoded urlEncodedBody
} }
case affResp.body of case affResp of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- liftEffect $ log $ printError err
throwError $ error $ printResponseFormatError err throwError $ error $ printError err
Right json -> do Right resp -> do
--_ <- liftEffect $ log json.status --_ <- liftEffect $ log json.status
--_ <- liftEffect $ log json.headers --_ <- liftEffect $ log json.headers
--_ <- liftEffect $ log json.body --_ <- liftEffect $ log json.body
case decodeJson json of case decodeJson resp.body of
Left err -> throwError $ error $ "decodeJson affResp.body: " <> err Left err -> throwError $ error $ "decodeJson affResp.body: " <> show err
Right b -> pure b Right b -> pure b
where where
urlEncodedBody = FormURLEncoded.fromArray bodyParams urlEncodedBody = FormURLEncoded.fromArray bodyParams
...@@ -131,12 +131,12 @@ postMultipartFormData mtoken url body = do ...@@ -131,12 +131,12 @@ postMultipartFormData mtoken url body = do
) mtoken ) mtoken
, content = Just $ formData fd , content = Just $ formData fd
} }
case affResp.body of case affResp of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err _ <- liftEffect $ log $ printError err
throwError $ error $ printResponseFormatError err throwError $ error $ printError err
Right json -> do Right resp -> do
case decodeJson json of case decodeJson resp.body of
Left err -> throwError $ error $ "decodeJson affResp.body: " <> err Left err -> throwError $ error $ "decodeJson affResp.body: " <> show err
Right b -> pure b Right b -> pure b
...@@ -5,7 +5,8 @@ import Prelude ...@@ -5,7 +5,8 @@ import Prelude
import Data.Nullable (Nullable) import Data.Nullable (Nullable)
import Effect (Effect) import Effect (Effect)
import Effect.Uncurried (EffectFn1, runEffectFn1) import Effect.Uncurried (EffectFn1, runEffectFn1)
import React (ReactRef, SyntheticEventHandler) import React (SyntheticEventHandler)
import React.Ref as RR
import Record.Unsafe (unsafeGet) import Record.Unsafe (unsafeGet)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Types (class Optional) import Gargantext.Types (class Optional)
...@@ -109,7 +110,7 @@ type SigmaProps = ...@@ -109,7 +110,7 @@ type SigmaProps =
, settings :: SigmaSettings , settings :: SigmaSettings
, style :: SigmaStyle , style :: SigmaStyle
, graph :: SigmaGraphData , graph :: SigmaGraphData
, ref :: SyntheticEventHandler (Nullable ReactRef) , ref :: RR.RefHandler RR.ReactInstance
, onClickNode :: SigmaNodeEvent -> Unit , onClickNode :: SigmaNodeEvent -> Unit
, onOverNode :: SigmaNodeEvent -> Unit , onOverNode :: SigmaNodeEvent -> Unit
, onOutNode :: SigmaNodeEvent -> Effect Unit , onOutNode :: SigmaNodeEvent -> Effect Unit
......
...@@ -4,6 +4,7 @@ module Gargantext.Sessions where ...@@ -4,6 +4,7 @@ module Gargantext.Sessions where
import DOM.Simple.Console (log2) import DOM.Simple.Console (log2)
import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), (.:)) import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), (.:))
import Data.Argonaut.Core (Json, fromArray, jsonEmptyObject, stringify) import Data.Argonaut.Core (Json, fromArray, jsonEmptyObject, stringify)
import Data.Argonaut.Decode.Error (JsonDecodeError(..))
import Data.Argonaut.Parser (jsonParser) import Data.Argonaut.Parser (jsonParser)
import Data.Array as A import Data.Array as A
import Data.Either (Either(..)) import Data.Either (Either(..))
...@@ -94,7 +95,7 @@ instance decodeJsonSessions :: DecodeJson Sessions where ...@@ -94,7 +95,7 @@ instance decodeJsonSessions :: DecodeJson Sessions where
pure (Sessions {sessions:Seq.fromFoldable ss}) pure (Sessions {sessions:Seq.fromFoldable ss})
where where
decodeSessions :: Json -> Either String (Array Session) decodeSessions :: Json -> Either JsonDecodeError (Array Session)
decodeSessions json2 = decodeJson json2 decodeSessions json2 = decodeJson json2
>>= \obj -> obj .: "sessions" >>= \obj -> obj .: "sessions"
>>= traverse decodeJson >>= traverse decodeJson
......
module Gargantext.Types where module Gargantext.Types where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.:), (:=), (~>)) import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Argonaut.Decode.Error (JsonDecodeError(..))
import Data.Array as A import Data.Array as A
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
...@@ -85,7 +86,7 @@ instance decodeJsonTermList :: DecodeJson TermList where ...@@ -85,7 +86,7 @@ instance decodeJsonTermList :: DecodeJson TermList where
"MapTerm" -> pure MapTerm "MapTerm" -> pure MapTerm
"StopTerm" -> pure StopTerm "StopTerm" -> pure StopTerm
"CandidateTerm" -> pure CandidateTerm "CandidateTerm" -> pure CandidateTerm
_ -> Left "Unexpected list name" s -> Left $ AtKey s $ TypeMismatch "Unexpected list name"
type ListTypeId = Int type ListTypeId = Int
...@@ -604,7 +605,7 @@ instance decodeJsonAsyncTaskType :: DecodeJson AsyncTaskType where ...@@ -604,7 +605,7 @@ instance decodeJsonAsyncTaskType :: DecodeJson AsyncTaskType where
"GraphT" -> pure GraphT "GraphT" -> pure GraphT
"Query" -> pure Query "Query" -> pure Query
"AddNode" -> pure AddNode "AddNode" -> pure AddNode
s -> Left ("Unknown string " <> s) s -> Left $ AtKey s $ TypeMismatch "Unknown string"
asyncTaskTypePath :: AsyncTaskType -> String asyncTaskTypePath :: AsyncTaskType -> String
asyncTaskTypePath Form = "add/form/async/" asyncTaskTypePath Form = "add/form/async/"
......
...@@ -5,6 +5,7 @@ import Prelude ...@@ -5,6 +5,7 @@ import Prelude
import Control.Alt ((<|>)) import Control.Alt ((<|>))
import Data.Argonaut (Json) import Data.Argonaut (Json)
import Data.Argonaut as Argonaut import Data.Argonaut as Argonaut
import Data.Argonaut.Decode.Error (JsonDecodeError(..))
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Generic.Rep as GR import Data.Generic.Rep as GR
import Data.Symbol (class IsSymbol, SProxy(..), reflectSymbol) import Data.Symbol (class IsSymbol, SProxy(..), reflectSymbol)
...@@ -15,7 +16,7 @@ genericSumDecodeJson ...@@ -15,7 +16,7 @@ genericSumDecodeJson
. GR.Generic a rep . GR.Generic a rep
=> GenericSumDecodeJsonRep rep => GenericSumDecodeJsonRep rep
=> Json => Json
-> Either String a -> Either JsonDecodeError a
genericSumDecodeJson f = genericSumDecodeJson f =
GR.to <$> genericSumDecodeJsonRep f GR.to <$> genericSumDecodeJsonRep f
...@@ -30,7 +31,7 @@ genericSumEncodeJson f = ...@@ -30,7 +31,7 @@ genericSumEncodeJson f =
genericSumEncodeJsonRep $ GR.from f genericSumEncodeJsonRep $ GR.from f
class GenericSumDecodeJsonRep rep where class GenericSumDecodeJsonRep rep where
genericSumDecodeJsonRep :: Json -> Either String rep genericSumDecodeJsonRep :: Json -> Either JsonDecodeError rep
class GenericSumEncodeJsonRep rep where class GenericSumEncodeJsonRep rep where
genericSumEncodeJsonRep :: rep -> Json genericSumEncodeJsonRep :: rep -> Json
...@@ -97,13 +98,13 @@ genericEnumDecodeJson :: forall a rep ...@@ -97,13 +98,13 @@ genericEnumDecodeJson :: forall a rep
. GR.Generic a rep . GR.Generic a rep
=> GenericEnumDecodeJson rep => GenericEnumDecodeJson rep
=> Json => Json
-> Either String a -> Either JsonDecodeError a
genericEnumDecodeJson f = genericEnumDecodeJson f =
GR.to <$> genericEnumDecodeJsonRep f GR.to <$> genericEnumDecodeJsonRep f
-- | Generic Enum Sum Representations, with constructor names as strings -- | Generic Enum Sum Representations, with constructor names as strings
class GenericEnumDecodeJson rep where class GenericEnumDecodeJson rep where
genericEnumDecodeJsonRep :: Json -> Either String rep genericEnumDecodeJsonRep :: Json -> Either JsonDecodeError rep
instance sumEnumDecodeJsonRep :: instance sumEnumDecodeJsonRep ::
( GenericEnumDecodeJson a ( GenericEnumDecodeJson a
...@@ -120,7 +121,7 @@ instance constructorEnumSumRep :: ...@@ -120,7 +121,7 @@ instance constructorEnumSumRep ::
s <- Argonaut.decodeJson f s <- Argonaut.decodeJson f
if s == name if s == name
then pure $ GR.Constructor GR.NoArguments then pure $ GR.Constructor GR.NoArguments
else Left $ "Enum string " <> s <> " did not match expected string " <> name else Left $ Named s $ TypeMismatch $ "Enum did not match expected string " <> name
where where
name = reflectSymbol (SProxy :: SProxy name) name = reflectSymbol (SProxy :: SProxy name)
......
...@@ -31,7 +31,7 @@ get cache session p = do ...@@ -31,7 +31,7 @@ get cache session p = do
j <- M.json res j <- M.json res
case decodeJson (F.unsafeFromForeign j) of case decodeJson (F.unsafeFromForeign j) of
Left err -> throwError $ error $ "decodeJson affResp.body: " <> err Left err -> throwError $ error $ "decodeJson affResp.body: " <> show err
Right b -> pure b Right b -> pure b
foreign import data Cache :: Type foreign import data Cache :: Type
...@@ -97,7 +97,7 @@ cachedJson cache req = do ...@@ -97,7 +97,7 @@ cachedJson cache req = do
j <- M.json res j <- M.json res
case decodeJson (F.unsafeFromForeign j) of case decodeJson (F.unsafeFromForeign j) of
Left err -> throwError $ error $ "[cachedJson] decodeJson affResp.body: " <> err Left err -> throwError $ error $ "[cachedJson] decodeJson affResp.body: " <> show err
Right b -> pure b Right b -> pure b
delete :: Cache -> Request -> Aff Unit delete :: Cache -> Request -> Aff Unit
...@@ -116,7 +116,7 @@ pureJson req = do ...@@ -116,7 +116,7 @@ pureJson req = do
res <- fetch req res <- fetch req
j <- M.json res j <- M.json res
case decodeJson (F.unsafeFromForeign j) of case decodeJson (F.unsafeFromForeign j) of
Left err -> throwError $ error $ "[pureJson] decodeJson affResp.body: " <> err Left err -> throwError $ error $ "[pureJson] decodeJson affResp.body: " <> show err
Right b -> pure b Right b -> pure b
......
...@@ -3,6 +3,7 @@ module Gargantext.Utils.DecodeMaybe where ...@@ -3,6 +3,7 @@ module Gargantext.Utils.DecodeMaybe where
import Prelude import Prelude
import Data.Argonaut (class DecodeJson, Json, getFieldOptional) import Data.Argonaut (class DecodeJson, Json, getFieldOptional)
import Data.Argonaut.Decode.Error (JsonDecodeError(..))
import Data.Either (Either) import Data.Either (Either)
import Data.Maybe (Maybe(..), fromMaybe) import Data.Maybe (Maybe(..), fromMaybe)
import Foreign.Object (Object) import Foreign.Object (Object)
...@@ -10,7 +11,7 @@ import Foreign.Object (Object) ...@@ -10,7 +11,7 @@ import Foreign.Object (Object)
foreign import isNull :: forall a. a -> Boolean foreign import isNull :: forall a. a -> Boolean
getFieldOptional' :: forall a. DecodeJson a => getFieldOptional' :: forall a. DecodeJson a =>
Object Json -> String -> Either String (Maybe a) Object Json -> String -> Either JsonDecodeError (Maybe a)
getFieldOptional' o s = (case _ of getFieldOptional' o s = (case _ of
Just v -> if isNull v then Nothing else v Just v -> if isNull v then Nothing else v
Nothing -> Nothing Nothing -> Nothing
...@@ -19,7 +20,7 @@ getFieldOptional' o s = (case _ of ...@@ -19,7 +20,7 @@ getFieldOptional' o s = (case _ of
infix 7 getFieldOptional' as .?| infix 7 getFieldOptional' as .?|
getFieldOptionalAsMempty :: forall a. DecodeJson a => getFieldOptionalAsMempty :: forall a. DecodeJson a =>
Monoid a => Object Json -> String -> Either String a Monoid a => Object Json -> String -> Either JsonDecodeError a
getFieldOptionalAsMempty o s = getFieldOptionalAsMempty o s =
fromMaybe mempty <$> (getFieldOptional' o s) fromMaybe mempty <$> (getFieldOptional' o s)
......
...@@ -3,6 +3,7 @@ module Gargantext.Utils.Spec where ...@@ -3,6 +3,7 @@ module Gargantext.Utils.Spec where
import Prelude import Prelude
import Data.Argonaut as Argonaut import Data.Argonaut as Argonaut
import Data.Argonaut.Decode.Error (JsonDecodeError)
import Data.Either (Either(..), isLeft) import Data.Either (Either(..), isLeft)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
...@@ -65,14 +66,14 @@ spec = ...@@ -65,14 +66,14 @@ spec =
GUM.log10 10.0 `shouldEqual` 1.0 GUM.log10 10.0 `shouldEqual` 1.0
it "genericSumDecodeJson works" do it "genericSumDecodeJson works" do
let result1 = Argonaut.decodeJson =<< Argonaut.jsonParser """{"Boat":{"hi":1}}""" let result1 = Argonaut.decodeJson =<< Argonaut.parseJson """{"Boat":{"hi":1}}"""
result1 `shouldEqual` Right (Boat { hi: 1 }) result1 `shouldEqual` Right (Boat { hi: 1 })
let result2 = Argonaut.decodeJson =<< Argonaut.jsonParser """{"Gravy":"hi"}""" let result2 = Argonaut.decodeJson =<< Argonaut.parseJson """{"Gravy":"hi"}"""
result2 `shouldEqual` Right (Gravy "hi") result2 `shouldEqual` Right (Gravy "hi")
let result3 = Argonaut.decodeJson =<< Argonaut.jsonParser """{"Boat":123}""" let result3 = Argonaut.decodeJson =<< Argonaut.parseJson """{"Boat":123}"""
isLeft (result3 :: Either String Fruit) `shouldEqual` true isLeft (result3 :: Either JsonDecodeError Fruit) `shouldEqual` true
it "genericSumEncodeJson works and loops back with decode" do it "genericSumEncodeJson works and loops back with decode" do
let input1 = Boat { hi: 1 } let input1 = Boat { hi: 1 }
...@@ -88,14 +89,14 @@ spec = ...@@ -88,14 +89,14 @@ spec =
result2' `shouldEqual` Right input2 result2' `shouldEqual` Right input2
it "genericEnumDecodeJson works" do it "genericEnumDecodeJson works" do
let result1 = Argonaut.decodeJson =<< Argonaut.jsonParser "\"Member1\"" let result1 = Argonaut.decodeJson =<< Argonaut.parseJson "\"Member1\""
result1 `shouldEqual` Right Member1 result1 `shouldEqual` Right Member1
let result2 = Argonaut.decodeJson =<< Argonaut.jsonParser "\"Member2\"" let result2 = Argonaut.decodeJson =<< Argonaut.parseJson "\"Member2\""
result2 `shouldEqual` Right Member2 result2 `shouldEqual` Right Member2
let result3 = Argonaut.decodeJson =<< Argonaut.jsonParser "\"Failure\"" let result3 = Argonaut.decodeJson =<< Argonaut.parseJson "\"Failure\""
isLeft (result3 :: Either String EnumTest) `shouldEqual` true isLeft (result3 :: Either JsonDecodeError EnumTest) `shouldEqual` true
it "genericSumEncodeJson works and loops back with decode" do it "genericSumEncodeJson works and loops back with decode" do
let input1 = Member1 let input1 = Member1
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment