Commit cdae18ff authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ngrams] fixes to ngrams PUT JSON response

parent 5e12ef58
......@@ -45,9 +45,10 @@ instance Eq RESTError where
eq _ _ = false
logRESTError :: R2.Here -> String -> RESTError -> Effect Unit
logRESTError here prefix (SendResponseError e) = here.warn2 (prefix <> " SendResponseError ") e -- TODO: No show
logRESTError here prefix (ReadJSONError e) = here.warn2 (prefix <> " ReadJSONError ") $ show e
logRESTError here prefix (CustomError e) = here.warn2 (prefix <> " CustomError ") $ e
logRESTError here prefix e = here.warn2 (prefix <> " " <> show e) e
-- logRESTError here prefix (SendResponseError e) = here.warn2 (prefix <> " SendResponseError ") e -- TODO: No show
-- logRESTError here prefix (ReadJSONError e) = here.warn2 (prefix <> " ReadJSONError ") $ show e
-- logRESTError here prefix (CustomError e) = here.warn2 (prefix <> " CustomError ") $ e
type AffRESTError a = Aff (Either RESTError a)
......
......@@ -35,7 +35,7 @@ import Effect.Class (liftEffect)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Table as T
import Gargantext.Components.Table.Types as T
import Gargantext.Config.REST (AffRESTError, RESTError)
import Gargantext.Config.REST (AffRESTError, RESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Core.NgramsTable.Types
import Gargantext.Routes (SessionRoute(..))
......@@ -375,7 +375,7 @@ syncPatches props state callback = do
launchAff_ $ do
ePatches <- putNgramsPatches props pt
case ePatches of
Left err -> liftEffect $ here.warn2 "[syncPatches] RESTError" err
Left err -> liftEffect $ logRESTError here "[syncPatches]" err
Right (Versioned { data: newPatch, version: newVersion }) -> do
callback unit
liftEffect $ do
......
......@@ -13,9 +13,10 @@ import Data.Lens.Index (class Index, ix)
import Data.Lens.Iso.Newtype (_Newtype)
import Data.Lens.Record (prop)
import Data.List (List)
import Data.List.Types (NonEmptyList(..))
import Data.Map (Map)
import Data.Map as Map
import Data.Maybe (Maybe(..), isJust)
import Data.Maybe (Maybe(..), fromJust, isJust)
import Data.Newtype (class Newtype)
import Data.Ord.Generic (genericCompare)
import Data.Show.Generic (genericShow)
......@@ -32,6 +33,7 @@ import Gargantext.Components.Table.Types as T
import Gargantext.Prelude
import Gargantext.Sessions (Session)
import Gargantext.Types as GT
import Gargantext.Utils.SimpleJSON as USJ
import Simple.JSON as JSON
import Reactix as R
import Type.Proxy (Proxy(..))
......@@ -207,14 +209,17 @@ instance JSON.ReadForeign NgramsPatch where
readImpl f = do
inst :: { patch_old :: Maybe NgramsRepoElement
, patch_new :: Maybe NgramsRepoElement
, patch_children :: PatchSet NgramsTerm
, patch_list :: Replace GT.TermList } <- JSON.readImpl f
, patch_children :: Maybe (PatchSet NgramsTerm)
, patch_list :: Maybe (Replace GT.TermList) } <- JSON.readImpl f
-- TODO handle empty fields
-- TODO handle patch_new
if isJust inst.patch_new || isJust inst.patch_old then
pure $ NgramsReplace { patch_old: inst.patch_old, patch_new: inst.patch_new }
else do
pure $ NgramsPatch { patch_list: inst.patch_list, patch_children: inst.patch_children }
pure $ NgramsReplace { patch_old: inst.patch_old
, patch_new: inst.patch_new }
else case (Tuple inst.patch_children inst.patch_list) of
Tuple (Just patch_children) (Just patch_list) ->
pure $ NgramsPatch { patch_list, patch_children }
_ -> USJ.throwJSONError $ F.ForeignError "[readForeign NgramsPatch] patch_children or patch_list undefined"
-----------------------------------------------------
newtype NgramsTerm = NormNgramsTerm String
......
......@@ -3,9 +3,12 @@ module Gargantext.Utils.SimpleJSON where
import Prelude
import Control.Alt ((<|>))
import Control.Monad.Except (withExcept)
import Control.Monad.Except (throwError, withExcept)
import Data.Generic.Rep as GR
import Data.List as L
import Data.List.Types (NonEmptyList(..))
import Data.Maybe (Maybe(..))
import Data.NonEmpty (NonEmpty(..))
import Data.Tuple (Tuple(..))
import Foreign (Foreign, ForeignError(..), fail)
import Foreign as Foreign
......@@ -86,3 +89,8 @@ instance untaggedSumRepArgument ::
( JSON.ReadForeign a
) => UntaggedSumRep (GR.Argument a) where
untaggedSumRep f = GR.Argument <$> JSON.readImpl f
throwJSONError :: forall a. Foreign.ForeignError -> Foreign.F a
throwJSONError err =
throwError $ NonEmptyList $ NonEmpty err L.Nil
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