Skip to content

Commit

Permalink
Add test cases for #64 and #66
Browse files Browse the repository at this point in the history
  • Loading branch information
Mitsutoshi Aoe authored and maoe committed Jun 17, 2020
1 parent 1105cf0 commit cd19c0d
Show file tree
Hide file tree
Showing 2 changed files with 67 additions and 12 deletions.
2 changes: 2 additions & 0 deletions influxdb.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -115,10 +115,12 @@ test-suite regressions
base
, containers
, influxdb
, lens
, tasty
, tasty-hunit
, time
, raw-strings-qq >= 1.1 && < 1.2
, vector
ghc-options: -Wall -threaded
hs-source-dirs: tests
default-language: Haskell2010
Expand Down
77 changes: 65 additions & 12 deletions tests/regressions.hs
Original file line number Diff line number Diff line change
@@ -1,34 +1,79 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
import Data.Time.Clock (UTCTime)
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
import Control.Exception (bracket_, try)

import Control.Lens
import Data.Time
import Test.Tasty
import Test.Tasty.HUnit
import Text.RawString.QQ (r)
import qualified Data.Map as M
import qualified Data.Map.Strict as Map
import qualified Data.Vector as V
import qualified Text.RawString.QQ as Raw (r)

import Database.InfluxDB
import Database.InfluxDB.Line
import qualified Database.InfluxDB.Format as F

main :: IO ()
main = defaultMain tests

tests :: TestTree
tests = testGroup "regression tests"
[ issue75
main = defaultMain $ testGroup "regression tests"
[ testCase "issue #64" case_issue64
, testCase "issue #66" case_issue66
, test_issue75
]

-- https://github.com/maoe/influxdb-haskell/issues/75
-- https://github.com/maoe/influxdb-haskell/issues/64
case_issue64 :: Assertion
case_issue64 = withDatabase dbName $ do
write wp $ Line "count" Map.empty
(Map.fromList [("value", FieldInt 1)])
(Nothing :: Maybe UTCTime)
r <- try $ query qp "SELECT value FROM count"
case r of
Left err -> case err of
UnexpectedResponse message _ _ ->
message @?=
"BUG: parsing Int failed, expected Number, but encountered String in Database.InfluxDB.Query.query"
_ ->
assertFailure $ got ++ show err
Right (v :: (V.Vector (Tagged "time" Int, Tagged "value" Int))) ->
-- NOTE: The time columns should be UTCTime, Text, or String
assertFailure $ got ++ "no errors: " ++ show v
where
dbName = "case_issue64"
qp = queryParams dbName & precision .~ RFC3339
wp = writeParams dbName
got = "expeted an UnexpectedResponse but got "

issue75 :: TestTree
issue75 = testCaseSteps "issue #75" $ \step -> do
-- https://github.com/maoe/influxdb-haskell/issues/66
case_issue66 :: Assertion
case_issue66 = do
r <- try $ query (queryParams "_internal") "SELECT time FROM dummy"
case r of
Left err -> case err of
UnexpectedResponse message _ _ ->
message @?=
"BUG: at least 1 non-time field must be queried in Database.InfluxDB.Query.query"
_ ->
assertFailure $ got ++ show err
Right (v :: V.Vector (Tagged "time" Int)) ->
assertFailure $ got ++ "no errors: " ++ show v
where
got = "expected an UnexpectedResponse but got "

-- https://github.com/maoe/influxdb-haskell/issues/75
test_issue75 :: TestTree
test_issue75 = testCaseSteps "issue #75" $ \step -> do
step "Checking encoded value"
let string = [r|bl\"a|]
let string = [Raw.r|bl\"a|]
let encoded = encodeLine (scaleTo Nanosecond)
$ Line "testing" mempty
(M.singleton "test" $ FieldString string)
(Nothing :: Maybe UTCTime)
encoded @?= [r|testing test="bl\\\"a"|]
encoded @?= [Raw.r|testing test="bl\\\"a"|]

step "Preparing a test database"
let db = "issue75"
Expand All @@ -39,3 +84,11 @@ issue75 = testCaseSteps "issue #75" $ \step -> do
step "Checking server response"
let wp = writeParams db
writeByteString wp encoded

withDatabase :: Database -> IO a -> IO a
withDatabase dbName f = bracket_
(manage q (formatQuery ("CREATE DATABASE "%F.database) dbName))
(manage q (formatQuery ("DROP DATABASE "%F.database) dbName))
f
where
q = queryParams dbName

0 comments on commit cd19c0d

Please sign in to comment.