Skip to content

Instantly share code, notes, and snippets.

@mstksg
Last active December 20, 2015 19:19
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 1 You must be signed in to fork a gist
  • Save mstksg/6182519 to your computer and use it in GitHub Desktop.
Save mstksg/6182519 to your computer and use it in GitHub Desktop.
Runtime error on selectDistinct on many-to-many join with sorting. No error if ran with sqlite bindings. Also, select (not distinct) works fine.
main.hs: user error (Postgresql.withStmt': bad result status FatalError (("PGRES_FATAL_ERROR","ERROR: for SELECT DISTINCT, ORDER BY expressions must appear in select list\nLINE 3: ORDER BY \"entry\".\"day_posted\" DESC, \"tag\".\"label\" ASC\n ^\n")))
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE OverloadedStrings #-}
import Database.Persist.TH
import Database.Persist.Postgresql
import qualified Database.Esqueleto as E
import qualified Data.Text as T
import Control.Monad.IO.Class
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Entry
dayPosted Int
deriving Show
Tag
label T.Text
deriving Show
EntryTag
entryId EntryId
tagId TagId
UniqueEntryTag entryId tagId
deriving Show
|]
main :: IO ()
main = runDB $ do
runMigration migrateAll
setupSchema
tags <- E.selectDistinct $
E.from $ \(t `E.InnerJoin` et `E.InnerJoin` e) -> do
E.on (e E.^. EntryId E.==. et E.^. EntryTagEntryId)
E.on (et E.^. EntryTagTagId E.==. t E.^. TagId)
E.orderBy [ E.desc (e E.^. EntryDayPosted), E.asc (t E.^. TagLabel) ]
return t
liftIO $ print $ map (tagLabel . entityVal) tags
runDB :: SqlPersistM a -> IO a
runDB commands = withPostgresqlPool connStr 10 $ \pool ->
runSqlPersistMPool commands pool
setupSchema :: SqlPersistM ()
setupSchema = do
entry1 <- insert $ Entry 1
entry2 <- insert $ Entry 2
entry3 <- insert $ Entry 3
tag1 <- insert $ Tag "Apple"
tag2 <- insert $ Tag "Boat"
tag3 <- insert $ Tag "Car"
insert_ $ EntryTag entry1 tag1
insert_ $ EntryTag entry1 tag2
insert_ $ EntryTag entry2 tag2
insert_ $ EntryTag entry3 tag3
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment