Skip to content

Instantly share code, notes, and snippets.

@danclien
Forked from willxeric/gist:011490de26b5b4da3a1c
Last active August 29, 2015 14:05
Show Gist options
  • Save danclien/e5181ebc3a2008621793 to your computer and use it in GitHub Desktop.
Save danclien/e5181ebc3a2008621793 to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
import Control.Applicative
import Control.Monad
import Control.Monad.IO.Class (liftIO)
import Database.PostgreSQL.Simple
import Database.PostgreSQL.Simple.FromRow
import Database.PostgreSQL.Simple.Types (Null(..))
import Data.Word
import qualified Data.Text as T
connInfo = ConnectInfo "localhost" (15432 :: Word16) "schoolobjects" "schoolobjects" "schoolobjects"
data Course = Course { title :: T.Text
, description :: Maybe T.Text
, creditid :: Maybe Int
, status :: T.Text
} deriving Show
data Activity = Activity { title' :: T.Text
, courseid' :: Int
, status' :: T.Text
} deriving Show
instance FromRow Course where
fromRow = Course <$> field <*> field <*> field <*> field
instance FromRow Activity where
fromRow = Activity <$> field <*> field <*> field
instance FromRow (Maybe Activity) where
fromRow = (null *> null *> null *> pure Nothing) <|> (Just <$> fromRow)
where null = field :: RowParser Null
main :: IO ()
main = do
conn <- connect connInfo
c <- query_ conn "SELECT c.title,\
\ c.description,\
\ c.creditid,\
\ c.status,\
\ a.title,\
\ a.courseid,\
\ a.status\
\ FROM course c\
\ LEFT JOIN activity a on a.courseid = c.id\
\ limit 10" :: (IO [Course :. Maybe Activity])
putStrLn $ show c
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment