diff --git a/src/Database/Esqueleto.hs b/src/Database/Esqueleto.hs index 3b2dcad..deed682 100644 --- a/src/Database/Esqueleto.hs +++ b/src/Database/Esqueleto.hs @@ -214,8 +214,8 @@ import qualified Database.Persist -- In @esqueleto@, we may write the same query above as: -- -- @ --- select $ --- from $ \\p -> do +-- 'select' $ +-- 'from' $ \\p -> do -- 'where_' (p '^.' PersonName '==.' 'val' \"John\") -- return p -- @ @@ -238,14 +238,14 @@ import qualified Database.Persist -- In @esqueleto@, we may write the same query above as: -- -- @ --- select $ --- from $ \\p -> do --- where_ (p ^. PersonAge '>=.' 'just' (val 18)) +-- 'select' $ +-- 'from' $ \\p -> do +-- 'where_' (p '^.' PersonAge '>=.' 'just' ('val' 18)) -- return p -- @ -- -- Since @age@ is an optional @Person@ field, we use 'just' lift --- @val 18 :: SqlExpr (Value Int)@ into @just (val 18) :: +-- @'val' 18 :: SqlExpr (Value Int)@ into @just ('val' 18) :: -- SqlExpr (Value (Maybe Int))@. -- -- Implicit joins are represented by tuples. For example, to get @@ -261,10 +261,10 @@ import qualified Database.Persist -- In @esqueleto@, we may write the same query above as: -- -- @ --- select $ --- from $ \\(b, p) -> do --- where_ (b ^. BlogPostAuthorId ==. p ^. PersonId) --- 'orderBy' ['asc' (b ^. BlogPostTitle)] +-- 'select' $ +-- 'from' $ \\(b, p) -> do +-- 'where_' (b '^.' BlogPostAuthorId '==.' p '^.' PersonId) +-- 'orderBy' ['asc' (b '^.' BlogPostTitle)] -- return (b, p) -- @ -- @@ -281,10 +281,10 @@ import qualified Database.Persist -- In @esqueleto@, we may write the same query above as: -- -- @ --- select $ --- from $ \\(p `'LeftOuterJoin`` mb) -> do --- 'on' (just (p ^. PersonId) ==. mb '?.' BlogPostAuthorId) --- orderBy [asc (p ^. PersonName), asc (mb '?.' BlogPostTitle)] +-- 'select' $ +-- 'from' $ \\(p `'LeftOuterJoin`` mb) -> do +-- 'on' ('just' (p '^.' PersonId) '==.' mb '?.' BlogPostAuthorId) +-- 'orderBy' ['asc' (p '^.' PersonName), 'asc' (mb '?.' BlogPostTitle)] -- return (p, mb) -- @ -- @@ -310,10 +310,10 @@ import qualified Database.Persist -- In @esqueleto@, we may write the same query above as: -- -- @ --- select $ --- from $ \\(p1 `'InnerJoin`` f `'InnerJoin`` p2) -> do --- on (p2 ^. PersonId ==. f ^. FollowFollowed) --- on (p1 ^. PersonId ==. f ^. FollowFollower) +-- 'select' $ +-- 'from' $ \\(p1 `'InnerJoin`` f `'InnerJoin`` p2) -> do +-- 'on' (p2 '^.' PersonId '==.' f '^.' FollowFollowed) +-- 'on' (p1 '^.' PersonId '==.' f '^.' FollowFollower) -- return (p1, f, p2) -- @ -- @@ -327,11 +327,11 @@ import qualified Database.Persist -- -- @ -- do 'update' $ \\p -> do --- 'set' p [ PersonName '=.' val \"João\" ] --- where_ (p ^. PersonName ==. val \"Joao\") +-- 'set' p [ PersonName '=.' 'val' \"João\" ] +-- 'where_' (p '^.' PersonName '==.' 'val' \"Joao\") -- 'delete' $ --- from $ \\p -> do --- where_ (p ^. PersonAge <. just (val 14)) +-- 'from' $ \\p -> do +-- 'where_' (p '^.' PersonAge '<.' 'just' ('val' 14)) -- @ -- -- The results of queries can also be used for insertions. @@ -347,8 +347,8 @@ import qualified Database.Persist -- In @esqueleto@, we may write the same query above as: -- -- @ --- insertSelect $ from $ \\p-> --- return $ BlogPost \<# \"Group Blog Post\" \<&\> (p ^. PersonId) +-- 'insertSelect' $ 'from' $ \\p-> +-- return $ BlogPost '<#' \"Group Blog Post\" '<&>' (p '^.' PersonId) -- @ -- -- Individual insertions can be performed through Persistent's diff --git a/src/Database/Esqueleto/Internal/Language.hs b/src/Database/Esqueleto/Internal/Language.hs index c77b6c3..541955c 100644 --- a/src/Database/Esqueleto/Internal/Language.hs +++ b/src/Database/Esqueleto/Internal/Language.hs @@ -99,8 +99,8 @@ class (Functor query, Applicative query, Monad query) => -- -- @ -- select $ - -- from $ \\(foo `'InnerJoin`` bar) -> do - -- on (foo ^. FooId ==. bar ^. BarFooId) + -- 'from' $ \\(foo `'InnerJoin`` bar) -> do + -- 'on' (foo '^.' FooId '==.' bar '^.' BarFooId) -- ... -- @ -- @@ -111,9 +111,9 @@ class (Functor query, Applicative query, Monad query) => -- -- @ -- select $ - -- from $ \\(foo `'InnerJoin`` bar `'InnerJoin`` baz) -> do - -- on (baz ^. BazId ==. bar ^. BarBazId) - -- on (foo ^. FooId ==. bar ^. BarFooId) + -- 'from' $ \\(foo `'InnerJoin`` bar `'InnerJoin`` baz) -> do + -- 'on' (baz '^.' BazId '==.' bar '^.' BarBazId) + -- 'on' (foo '^.' FooId '==.' bar '^.' BarFooId) -- ... -- @ -- @@ -122,11 +122,11 @@ class (Functor query, Applicative query, Monad query) => -- -- @ -- let query1 = - -- from $ \\(foo `'InnerJoin`` bar) -> do - -- on (foo ^. FooId ==. bar ^. BarFooId) + -- 'from' $ \\(foo `'InnerJoin`` bar) -> do + -- 'on' (foo '^.' FooId '==.' bar '^.' BarFooId) -- query2 = - -- from $ \\(mbaz `'LeftOuterJoin`` quux) -> do - -- return (mbaz ?. BazName, quux) + -- 'from' $ \\(mbaz `'LeftOuterJoin`` quux) -> do + -- return (mbaz '?.' BazName, quux) -- test1 = (,) \<$\> query1 \<*\> query2 -- test2 = flip (,) \<$\> query2 \<*\> query1 -- @ @@ -140,10 +140,10 @@ class (Functor query, Applicative query, Monad query) => -- in a tuple. -- -- @ - -- select $ from \\(foo `'InnerJoin`` bar) -> do - -- on (foo ^. FooBarId ==. bar ^. BarId) - -- groupBy (bar ^. BarId, bar ^. BarName) - -- return (bar ^. BarId, bar ^. BarName, countRows) + -- select $ 'from' \\(foo `'InnerJoin`` bar) -> do + -- 'on' (foo '^.' FooBarId '==.' bar '^.' BarId) + -- 'groupBy' (bar '^.' BarId, bar '^.' BarName) + -- return (bar '^.' BarId, bar '^.' BarName, countRows) -- @ -- -- With groupBy you can sort by aggregate functions, like so @@ -152,13 +152,13 @@ class (Functor query, Applicative query, Monad query) => -- 'countRows' has its type restricted by the @:: Int@ below): -- -- @ - -- r \<- select $ from \\(foo `'InnerJoin`` bar) -> do - -- on (foo ^. FooBarId ==. bar ^. BarId) - -- groupBy $ bar ^. BarName - -- let countRows' = countRows - -- orderBy [asc countRows'] - -- return (bar ^. BarName, countRows') - -- forM_ r $ \\((Value name), (Value count)) -> do + -- r \<- select $ 'from' \\(foo `'InnerJoin`` bar) -> do + -- 'on' (foo '^.' FooBarId '==.' bar '^.' BarId) + -- 'groupBy' $ bar '^.' BarName + -- let countRows' = 'countRows' + -- 'orderBy' ['asc' countRows'] + -- return (bar '^.' BarName, countRows') + -- forM_ r $ \\('Value' name, 'Value' count) -> do -- print name -- print (count :: Int) -- @ @@ -212,8 +212,8 @@ class (Functor query, Applicative query, Monad query) => isNothing :: PersistField typ => expr (Value (Maybe typ)) -> expr (Value Bool) -- | Analogous to 'Just', promotes a value of type @typ@ into - -- one of type @Maybe typ@. It should hold that @val . Just - -- === just . val@. + -- one of type @Maybe typ@. It should hold that @'val' . Just + -- === just . 'val'@. just :: expr (Value typ) -> expr (Value (Maybe typ)) -- | @NULL@ value. @@ -282,7 +282,7 @@ class (Functor query, Applicative query, Monad query) => -- for example: -- -- @ - -- name `'like`` (%) ++. val \"John\" ++. (%) + -- name `'like`` (%) ++. 'val' \"John\" ++. (%) -- @ (%) :: (PersistField s, IsString s) => expr (Value s) -- | The @CONCAT@ function with a variable number of @@ -313,10 +313,10 @@ class (Functor query, Applicative query, Monad query) => -- -- @ -- select $ - -- from $ \\person -> do - -- where_ $ exists $ - -- from $ \\post -> do - -- where_ (post ^. BlogPostAuthorId ==. person ^. PersonId) + -- 'from' $ \\person -> do + -- 'where_' $ 'exists' $ + -- 'from' $ \\post -> do + -- 'where_' (post '^.' BlogPostAuthorId '==.' person '^.' PersonId) -- return person -- @ exists :: query () -> expr (Value Bool) @@ -346,21 +346,21 @@ class (Functor query, Applicative query, Monad query) => -- @ -- select $ -- return $ - -- case_ - -- [ when_ - -- (exists $ - -- from $ \\p -> do - -- where_ (p ^. PersonName ==. val \"Mike\")) - -- then_ - -- (sub_select $ - -- from $ \\v -> do + -- 'case_' + -- [ 'when_' + -- ('exists' $ + -- 'from' $ \\p -> do + -- 'where_' (p '^.' PersonName '==.' 'val' \"Mike\")) + -- 'then_' + -- ('sub_select' $ + -- 'from' $ \\v -> do -- let sub = - -- from $ \\c -> do - -- where_ (c ^. PersonName ==. val \"Mike\") - -- return (c ^. PersonFavNum) - -- where_ (v ^. PersonFavNum >. sub_select sub) - -- return $ count (v ^. PersonName) +. val (1 :: Int)) ] - -- (else_ $ val (-1)) + -- 'from' $ \\c -> do + -- 'where_' (c '^.' PersonName '==.' 'val' \"Mike\") + -- return (c '^.' PersonFavNum) + -- 'where_' (v '^.' PersonFavNum >. 'sub_select' sub) + -- return $ 'count' (v '^.' PersonName) +. 'val' (1 :: Int)) ] + -- ('else_' $ 'val' (-1)) -- @ -- -- This query is a bit complicated, but basically it checks if a person @@ -444,8 +444,8 @@ data SomeValue expr where SomeValue :: Esqueleto query expr backend => expr (Value a) -> SomeValue expr -- | A class of things that can be converted into a list of SomeValue. It has --- instances for tuples and is the reason why groupBy can take tuples, like --- @groupBy (foo ^. FooId, foo ^. FooName, foo ^. FooType)@. +-- instances for tuples and is the reason why 'groupBy' can take tuples, like +-- @'groupBy' (foo '^.' FooId, foo '^.' FooName, foo '^.' FooType)@. class ToSomeValues expr a where toSomeValues :: a -> [SomeValue expr] @@ -523,7 +523,7 @@ data CrossJoin a b = a `CrossJoin` b -- -- @ -- select $ --- from $ \\(person `'LeftOuterJoin`` pet) -> +-- 'from' $ \\(person `'LeftOuterJoin`` pet) -> -- ... -- @ -- @@ -637,11 +637,11 @@ data Insertion a -- of the arguments of the lambda are inside square brackets): -- -- @ --- from $ \\person -> ... --- from $ \\(person, blogPost) -> ... --- from $ \\(p `'LeftOuterJoin`` mb) -> ... --- from $ \\(p1 `'InnerJoin`` f `'InnerJoin`` p2) -> ... --- from $ \\((p1 `'InnerJoin`` f) `'InnerJoin`` p2) -> ... +-- 'from' $ \\person -> ... +-- 'from' $ \\(person, blogPost) -> ... +-- 'from' $ \\(p `'LeftOuterJoin`` mb) -> ... +-- 'from' $ \\(p1 `'InnerJoin`` f `'InnerJoin`` p2) -> ... +-- 'from' $ \\((p1 `'InnerJoin`` f) `'InnerJoin`` p2) -> ... -- @ -- -- The types of the arguments to the lambdas above are, diff --git a/src/Database/Esqueleto/Internal/Sql.hs b/src/Database/Esqueleto/Internal/Sql.hs index ff09906..9da7d90 100644 --- a/src/Database/Esqueleto/Internal/Sql.hs +++ b/src/Database/Esqueleto/Internal/Sql.hs @@ -712,12 +712,12 @@ selectSource query = do -- allow type information to flow both from @a@ to @r@ and -- vice-versa. This means that you'll almost never have to give -- any type signatures for @esqueleto@ queries. For example, the --- query @select $ from $ \\p -> return p@ alone is ambiguous, but +-- query @'select' $ from $ \\p -> return p@ alone is ambiguous, but -- in the context of -- -- @ --- do ps <- select $ --- from $ \\p -> +-- do ps <- 'select' $ +-- 'from' $ \\p -> -- return p -- liftIO $ mapM_ (putStrLn . personName . entityVal) ps -- @ @@ -791,9 +791,9 @@ rawEsqueleto mode query = do -- Example of usage: -- -- @ --- delete $ --- from $ \\appointment -> --- where_ (appointment ^. AppointmentDate <. val now) +-- 'delete' $ +-- 'from' $ \\appointment -> +-- 'where_' (appointment '^.' AppointmentDate '<.' 'val' now) -- @ -- -- Unlike 'select', there is a useful way of using 'delete' that @@ -801,8 +801,8 @@ rawEsqueleto mode query = do -- (i.e., no 'where_' clause), you'll have to use a type signature: -- -- @ --- delete $ --- from $ \\(appointment :: SqlExpr (Entity Appointment)) -> +-- 'delete' $ +-- 'from' $ \\(appointment :: 'SqlExpr' ('Entity' Appointment)) -> -- return () -- @ delete :: ( MonadIO m ) @@ -826,9 +826,9 @@ deleteCount = rawEsqueleto DELETE -- Example of usage: -- -- @ --- update $ \p -> do --- set p [ PersonAge =. just (val thisYear) -. p ^. PersonBorn ] --- where_ $ isNothing (p ^. PersonAge) +-- 'update' $ \p -> do +-- 'set' p [ PersonAge '=.' 'just' ('val' thisYear) -. p '^.' PersonBorn ] +-- 'where_' $ isNothing (p '^.' PersonAge) -- @ update :: ( MonadIO m , SqlEntity val )