[tests] fix tests for removal of servant-job

parent 33da4e06
Pipeline #7064 passed with stages
in 46 minutes and 19 seconds
......@@ -21,6 +21,8 @@ module Gargantext.Core.Utils (
, randomString
, groupWithCounts
, addTuples
, (?!)
, (?|)
) where
import Data.List qualified as List
......@@ -30,6 +32,7 @@ import Data.Text qualified as T
import Gargantext.Core.Utils.Prefix
import Gargantext.Prelude
import Prelude ((!!))
import Prelude qualified
import System.Random (initStdGen, uniformR)
......@@ -71,3 +74,16 @@ groupWithCounts = map f
addTuples :: (Num a, Num b) => (a, b) -> (a, b) -> (a, b)
addTuples (a1, b1) (a2, b2) = (a1 + a2, b1 + b2)
infixr 4 ?!
-- Reverse infix form of "fromJust" with a custom error message
(?!) :: Maybe a -> Prelude.String -> a
(?!) ma msg = ma ?| errorTrace msg
infixr 4 ?|
-- Reverse infix form of "fromMaybe"
(?|) :: Maybe a -> a -> a
(?|) = flip fromMaybe
......@@ -19,6 +19,7 @@ import Data.Swagger.Declare qualified as S
import Data.Swagger.Internal.Schema qualified as S
import Data.Swagger.Internal.TypeShape qualified as S
import Data.Text qualified as T
import Gargantext.Core.Utils ((?!))
import Gargantext.Prelude
import Prelude qualified
......@@ -45,15 +46,3 @@ swaggerOptions pref = defaultSchemaOptions
modifier :: Text -> Prelude.String -> Prelude.String
modifier pref field = T.unpack $ T.stripPrefix pref (T.pack field) ?! "Expecting prefix " <> T.unpack pref
infixr 4 ?!
-- Reverse infix form of "fromJust" with a custom error message
(?!) :: Maybe a -> Prelude.String -> a
(?!) ma msg = ma ?| errorTrace msg
infixr 4 ?|
-- Reverse infix form of "fromMaybe"
(?|) :: Maybe a -> a -> a
(?|) = flip fromMaybe
......@@ -41,6 +41,7 @@ import Gargantext.API.Routes.Named
import Gargantext.API.Routes.Named.List (updateListJSONEp, updateListTSVEp)
import Gargantext.API.Routes.Named.Node hiding (treeAPI)
import Gargantext.API.Routes.Named.Private hiding (tableNgramsAPI)
import Gargantext.API.Routes.Named.Publish (PublishAPI(..))
import Gargantext.API.Routes.Named.Publish (PublishRequest(..))
import Gargantext.API.Routes.Named.Table
import Gargantext.API.Routes.Named.Tree (nodeTreeEp)
......@@ -61,8 +62,6 @@ import Servant.Auth.Client qualified as S
import Servant.Client (ClientM)
import Servant.Client.Core (RunClient, HasClient(..), Request)
import Servant.Client.Generic ( genericClient, AsClientT )
import Servant.Job.Async
import Gargantext.API.Routes.Named.Publish (PublishAPI(..))
instance RunClient m => HasClient m WS.WebSocketPending where
......
......@@ -56,8 +56,6 @@ import Gargantext.Database.Admin.Types.Hyperdata qualified as Hyperdata
import Gargantext.Database.Admin.Types.Node (NodeId(..), UserId(..), NodeType(..))
import Gargantext.Database.Query.Facet (OrderBy(..))
import Gargantext.Prelude hiding (replace, Location)
import Servant.Job.Core qualified as SJ
import Servant.Job.Types qualified as SJ
import Text.Parsec.Error (ParseError, Message(..), newErrorMessage)
import Text.Parsec.Pos
import Test.QuickCheck
......@@ -305,24 +303,24 @@ instance Arbitrary RenameNode where
-- Servant job
instance Arbitrary a => Arbitrary (SJ.JobOutput a) where
arbitrary = SJ.JobOutput <$> arbitrary
instance Arbitrary SJ.States where arbitrary = genericArbitrary
instance Arbitrary (SJ.ID 'SJ.Safe k) where
arbitrary = do
_id_type <- arbitrary
_id_number <- arbitrary
_id_time <- arbitrary
_id_token <- arbitrary
pure $ SJ.PrivateID { .. }
instance Arbitrary a => Arbitrary (SJ.JobStatus 'SJ.Safe a) where
arbitrary = do
_job_id <- arbitrary
_job_log <- arbitrary
_job_status <- arbitrary
_job_error <- arbitrary
pure $ SJ.JobStatus { .. }
deriving instance Eq a => Eq (SJ.JobStatus 'SJ.Safe a)
-- instance Arbitrary a => Arbitrary (SJ.JobOutput a) where
-- arbitrary = SJ.JobOutput <$> arbitrary
-- instance Arbitrary SJ.States where arbitrary = genericArbitrary
-- instance Arbitrary (SJ.ID 'SJ.Safe k) where
-- arbitrary = do
-- _id_type <- arbitrary
-- _id_number <- arbitrary
-- _id_time <- arbitrary
-- _id_token <- arbitrary
-- pure $ SJ.PrivateID { .. }
-- instance Arbitrary a => Arbitrary (SJ.JobStatus 'SJ.Safe a) where
-- arbitrary = do
-- _job_id <- arbitrary
-- _job_log <- arbitrary
-- _job_status <- arbitrary
-- _job_error <- arbitrary
-- pure $ SJ.JobStatus { .. }
-- deriving instance Eq a => Eq (SJ.JobStatus 'SJ.Safe a)
-- Notifications
......
......@@ -37,8 +37,6 @@ import Gargantext.Utils.Jobs.Monad hiding (withJob)
import Network.HTTP.Client (Manager)
import Network.HTTP.Client.TLS (newTlsManager)
import Prelude qualified
import Servant.Job.Core qualified as SJ
import Servant.Job.Types qualified as SJ
import System.IO.Unsafe
import System.Timeout (timeout)
import Test.Hspec
......
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