Skip to content

Commit

Permalink
fix persistent-qq tests
Browse files Browse the repository at this point in the history
  • Loading branch information
curranosaurus committed Dec 31, 2024
1 parent 035075a commit a4e8af3
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 3 deletions.
10 changes: 9 additions & 1 deletion persistent-qq/test/PersistentTestModels.hs
Original file line number Diff line number Diff line change
Expand Up @@ -110,8 +110,16 @@ share
~no Int
def Int

-- copied from 'Person'
AnimalPerson json schema=animals
name Text
age Int "some ignored -- \" attribute"
color Text Maybe -- this is a comment sql=foobarbaz
AnimalPersonNameKey name -- this is a comment sql=foobarbaz
deriving Show Eq

PetAnimal schema=animals
ownerId PersonId
ownerId AnimalPersonId
name Text
|]

Expand Down
8 changes: 6 additions & 2 deletions persistent-qq/test/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,16 +1,19 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

import Control.Monad (when)
import Control.Monad.Logger (LoggingT, runLoggingT)
import Control.Monad.Reader
import Control.Monad.Trans.Resource
import qualified Data.ByteString.Char8 as B
import Data.Int (Int64)
import Data.List (sort)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Text (Text)
import System.Log.FastLogger (fromLogStr)
import System.IO.Unsafe (unsafePerformIO)
import Test.Hspec
import Test.HUnit ((@?=))

Expand All @@ -37,6 +40,7 @@ runConn f = do
db :: SqlPersistT (LoggingT (ResourceT IO)) a -> IO a
db actions = do
runResourceT $ runConn $ do
rawSql @(Single Int64) ("attach 'animals.db' as animals") []
_ <- runMigrationSilent testMigrate
actions <* transactionUndo

Expand Down Expand Up @@ -116,15 +120,15 @@ spec = describe "persistent-qq" $ do
liftIO $ ret2 @?= [Entity (RFOKey $ unPersonKey p1k) (RFO p1)]

it "sqlQQ/entity in schema" $ db $ do
let person = Person "Zacarias" 93 Nothing
let person = AnimalPerson "Zacarias" 93 Nothing
personKey <- insert person
let pet = PetAnimal personKey "Fluffy"
petKey <- insert pet
let runQueryQuoted, runQueryRaw
:: (RawSql a, Functor m, MonadIO m)
=> ReaderT SqlBackend m [a]
runQueryQuoted = [sqlQQ| SELECT ?? FROM ^{PetAnimal} |]
runQueryRaw = [sqlQQ| SELECT ?? FROM animals.pet_animal |]
runQueryRaw = [sqlQQ| SELECT ?? FROM animals.PetAnimal |]
retQuoted <- runQueryQuoted
retRaw <- runQueryRaw
liftIO $ retQuoted @?= [Entity petKey pet]
Expand Down

0 comments on commit a4e8af3

Please sign in to comment.