isNothing, just, nothing.

This commit is contained in:
Felipe Lessa 2012-09-04 18:12:25 -03:00
parent 8a601551e4
commit c601613162
4 changed files with 38 additions and 4 deletions

View File

@ -16,7 +16,8 @@
-- @
module Database.Esqueleto
( -- * Esqueleto's Language
Esqueleto( where_, sub, (^.), val, not_, (==.), (>=.)
Esqueleto( where_, sub, (^.), val, isNothing, just, nothing
, not_, (==.), (>=.)
, (>.), (<=.), (<.), (!=.), (&&.), (||.)
, (+.), (-.), (/.), (*.) )
, from

View File

@ -30,6 +30,17 @@ class (Functor query, Applicative query, Monad query) =>
-- | Lift a constant value from Haskell-land to the query.
val :: PersistField typ => typ -> expr (Single typ)
-- | @IS NULL@ comparison.
isNothing :: PersistField typ => expr (Single (Maybe typ)) -> expr (Single Bool)
-- | Analog to 'Just', promotes a value of type @typ@ into one
-- of type @Maybe typ@. It should hold that @val . Just ===
-- just . val@.
just :: expr (Single typ) -> expr (Single (Maybe typ))
-- | @NULL@ value.
nothing :: expr (Single (Maybe typ))
not_ :: expr (Single Bool) -> expr (Single Bool)
(==.) :: PersistField typ => expr (Single typ) -> expr (Single typ) -> expr (Single Bool)

View File

@ -117,6 +117,12 @@ instance Esqueleto SqlQuery SqlExpr SqlPersist where
val = ERaw . const . (,) "?" . return . toPersistValue
isNothing (ERaw f) = ERaw $ first ((<> " IS NULL") . parens) . f
isNothing _ = error "Esqueleto/Sql/isNothing: never here (see GHC #6124)"
just (ERaw f) = ERaw f
just _ = error "Esqueleto/Sql/just: never here (see GHC #6124)"
nothing = ERaw $ \_ -> ("NULL", mempty)
not_ (ERaw f) = ERaw $ \esc -> let (b, vals) = f esc
in ("NOT " <> parens b, vals)
not_ _ = error "Esqueleto/Sql/not_: never here (see GHC #6124)"

View File

@ -50,6 +50,11 @@ main = do
ret <- select $ return $ val (3 :: Int)
liftIO $ ret `shouldBe` [ Single 3 ]
it "works for a single NULL value" $
run $ do
ret <- select $ return $ nothing
liftIO $ ret `shouldBe` [ Single (Nothing :: Maybe Int) ]
describe "select/from" $ do
it "works for a simple example" $
run $ do
@ -124,7 +129,7 @@ main = do
return p
liftIO $ ret `shouldBe` [ Entity p1k p1, Entity p2k p2 ]
it "works for a simple example with (>.)" $
it "works for a simple example with (>.) [uses val . Just]" $
run $ do
p1k <- insert p1
_ <- insert p2
@ -135,17 +140,28 @@ main = do
return p
liftIO $ ret `shouldBe` [ Entity p1k p1 ]
it "works for a simple example with (>.) and not_" $
it "works for a simple example with (>.) and not_ [uses just . val]" $
run $ do
_ <- insert p1
_ <- insert p2
p3k <- insert p3
ret <- select $
from $ \p -> do
where_ (not_ $ p ^. PersonAge >. val (Just 17))
where_ (not_ $ p ^. PersonAge >. just (val 17))
return p
liftIO $ ret `shouldBe` [ Entity p3k p3 ]
it "works with isNothing" $
run $ do
_ <- insert p1
p2k <- insert p2
_ <- insert p3
ret <- select $
from $ \p -> do
where_ $ isNothing (p ^. PersonAge)
return p
liftIO $ ret `shouldBe` [ Entity p2k p2 ]
----------------------------------------------------------------------