Skip to content

Commit

Permalink
Write a failing test for eval
Browse files Browse the repository at this point in the history
  • Loading branch information
omnibs committed May 22, 2024
1 parent 05f10d4 commit 367691b
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 2 deletions.
5 changes: 4 additions & 1 deletion nri-redis/src/Redis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,8 @@ module Redis
setex,
setnx,
eval,
script,
ScriptParam (..),

-- * Running Redis queries
Internal.query,
Expand All @@ -62,6 +64,7 @@ import qualified NonEmptyDict
import qualified Redis.Codec as Codec
import qualified Redis.Handler as Handler
import qualified Redis.Internal as Internal
import Redis.Script (ScriptParam (..), script)
import qualified Redis.Script as Script
import qualified Redis.Settings as Settings
import qualified Prelude
Expand Down Expand Up @@ -189,5 +192,5 @@ makeApi Codec.Codec {Codec.codecEncoder, Codec.codecDecoder} toKey =
set = \key value -> Internal.Set (toKey key) (codecEncoder value),
setex = \key seconds value -> Internal.Setex (toKey key) seconds (codecEncoder value),
setnx = \key value -> Internal.Setnx (toKey key) (codecEncoder value),
eval = \script -> Internal.Eval script
eval = \script' -> Internal.Eval script'
}
11 changes: 10 additions & 1 deletion nri-redis/test/Spec/Redis.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE QuasiQuotes #-}

module Spec.Redis (tests) where

import qualified Control.Concurrent.MVar as MVar
Expand Down Expand Up @@ -369,7 +371,11 @@ queryTests redisHandler =
|> Expect.equal (List.length expectedKeys)
keySet
|> Set.toList
|> Expect.equal expectedKeys
|> Expect.equal expectedKeys,
Test.test "eval runs and returns something" <| \() -> do
let script = [Redis.script|return 1|]
result <- Redis.eval intJsonApi script |> Redis.query testNS |> Expect.succeeds
Expect.equal result 1
]
where
testNS = addNamespace "testNamespace" redisHandler
Expand All @@ -396,6 +402,9 @@ sortedSetApi = Redis.SortedSet.textApi identity
jsonApi' :: Redis.Api Text [Int]
jsonApi' = Redis.jsonApi identity

intJsonApi :: Redis.Api Text Prelude.Integer
intJsonApi = Redis.jsonApi identity

-- | Timestamps recorded in spans would make each test result different from the
-- last. This helper sets all timestamps to zero to prevent this.
--
Expand Down

0 comments on commit 367691b

Please sign in to comment.