Skip to content

Commit 8fb828c

Browse files
authored
Format with fourmolu (#70)
* Format with fourmolu * Make examples compile
1 parent c21cc23 commit 8fb828c

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

45 files changed

+6818
-2655
lines changed

.github/workflows/fourmolu.yaml

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
name: Fourmolu
2+
on: push
3+
jobs:
4+
format:
5+
runs-on: ubuntu-latest
6+
steps:
7+
- uses: actions/checkout@v3
8+
- uses: haskell-actions/run-fourmolu@v10
9+
with:
10+
version: "0.15.0.0"

examples/Catalog.hs

Lines changed: 81 additions & 69 deletions
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,18 @@
1-
{-# LANGUAGE FlexibleContexts, OverloadedStrings, RecordWildCards
2-
, ScopedTypeVariables, TypeFamilies #-}
3-
{-# OPTIONS_GHC -Wall #-}
1+
module Catalog (catalog) where
42

53
import Control.Arrow (second)
64
import Control.Monad
75
import Control.Monad.Base
86
import Control.Monad.Catch
97
import Data.Function
108
import Data.Int
11-
import Data.Monoid
129
import Data.Monoid.Utils
10+
import Data.Pool
11+
import Data.Text qualified as T
1312
import Database.PostgreSQL.PQTypes
1413
import Database.PostgreSQL.PQTypes.Internal.Utils (mread)
1514
import System.Console.Readline
1615
import System.Environment
17-
import qualified Data.ByteString.Char8 as BS
1816

1917
-- | Generic 'putStrLn'.
2018
printLn :: MonadBase IO m => String -> m ()
@@ -25,7 +23,7 @@ getConnSettings :: IO ConnectionSettings
2523
getConnSettings = do
2624
args <- getArgs
2725
case args of
28-
[conninfo] -> return def { csConnInfo = BS.pack conninfo }
26+
[conninfo] -> return defaultConnectionSettings {csConnInfo = T.pack conninfo}
2927
_ -> do
3028
prog <- getProgName
3129
error $ "Usage:" <+> prog <+> "<connection info>"
@@ -34,10 +32,11 @@ getConnSettings = do
3432

3533
-- | Representation of a book.
3634
data Book = Book
37-
{ bookID :: Int64
38-
, bookName :: String
39-
, bookYear :: Int32
40-
} deriving (Read, Show)
35+
{ bookID :: Int64
36+
, bookName :: String
37+
, bookYear :: Int32
38+
}
39+
deriving (Read, Show)
4140

4241
-- | Intermediate representation of 'Book'.
4342
type instance CompositeRow Book = (Int64, String, Int32)
@@ -46,78 +45,87 @@ instance PQFormat Book where
4645
pqFormat = "%book_"
4746

4847
instance CompositeFromSQL Book where
49-
toComposite (bid, name, year) = Book {
50-
bookID = bid
51-
, bookName = name
52-
, bookYear = year
53-
}
48+
toComposite (bid, name, year) =
49+
Book
50+
{ bookID = bid
51+
, bookName = name
52+
, bookYear = year
53+
}
5454

5555
withCatalog :: ConnectionSettings -> IO () -> IO ()
56-
withCatalog cs = bracket_ createStructure dropStructure
56+
withCatalog settings = bracket_ createStructure dropStructure
5757
where
58-
-- | Create needed tables and types.
59-
createStructure = runDBT (simpleSource cs) def $ do
58+
ConnectionSource cs = simpleSource settings
59+
60+
-- Create needed tables and types.
61+
createStructure = runDBT cs defaultTransactionSettings $ do
6062
printLn "Creating tables..."
61-
runSQL_ $ mconcat [
62-
"CREATE TABLE authors_ ("
63-
, " id BIGSERIAL NOT NULL"
64-
, ", name TEXT NOT NULL"
65-
, ", PRIMARY KEY (id)"
66-
, ")"
67-
]
68-
runSQL_ $ mconcat [
69-
"CREATE TABLE books_ ("
70-
, " id BIGSERIAL NOT NULL"
71-
, ", name TEXT NOT NULL"
72-
, ", year INTEGER NOT NULL"
73-
, ", author_id BIGINT NOT NULL"
74-
, ", PRIMARY KEY (id)"
75-
, ", FOREIGN KEY (author_id) REFERENCES authors_ (id)"
76-
, ")"
77-
]
78-
runSQL_ $ mconcat [
79-
"CREATE TYPE book_ AS ("
80-
, " id BIGINT"
81-
, ", name TEXT"
82-
, ", year INTEGER"
83-
, ")"
84-
]
85-
-- | Drop previously created database structures.
86-
dropStructure = runDBT (simpleSource cs) def $ do
63+
runSQL_ $
64+
mconcat
65+
[ "CREATE TABLE authors_ ("
66+
, " id BIGSERIAL NOT NULL"
67+
, ", name TEXT NOT NULL"
68+
, ", PRIMARY KEY (id)"
69+
, ")"
70+
]
71+
runSQL_ $
72+
mconcat
73+
[ "CREATE TABLE books_ ("
74+
, " id BIGSERIAL NOT NULL"
75+
, ", name TEXT NOT NULL"
76+
, ", year INTEGER NOT NULL"
77+
, ", author_id BIGINT NOT NULL"
78+
, ", PRIMARY KEY (id)"
79+
, ", FOREIGN KEY (author_id) REFERENCES authors_ (id)"
80+
, ")"
81+
]
82+
runSQL_ $
83+
mconcat
84+
[ "CREATE TYPE book_ AS ("
85+
, " id BIGINT"
86+
, ", name TEXT"
87+
, ", year INTEGER"
88+
, ")"
89+
]
90+
-- Drop previously created database structures.
91+
dropStructure = runDBT cs defaultTransactionSettings $ do
8792
printLn "Dropping tables..."
8893
runSQL_ "DROP TYPE book_"
8994
runSQL_ "DROP TABLE books_"
9095
runSQL_ "DROP TABLE authors_"
9196

9297
----------------------------------------
9398

94-
processCommand :: ConnectionSource -> String -> IO ()
99+
processCommand :: ConnectionSourceM IO -> String -> IO ()
95100
processCommand cs cmd = case parse cmd of
96-
-- | Display authors.
97-
("authors", "") -> runDBT cs def $ do
101+
-- Display authors.
102+
("authors", "") -> runDBT cs defaultTransactionSettings $ do
98103
runSQL_ "SELECT * FROM authors_ ORDER BY name"
99-
mapDB_ $ \(aid::Int64, name) -> printLn $ show aid <> ":" <+> name
100-
-- | Display books.
101-
("books", "") -> runDBT cs def $ do
104+
mapDB_ $ \(aid :: Int64, name) -> printLn $ show aid <> ":" <+> name
105+
-- Display books.
106+
("books", "") -> runDBT cs defaultTransactionSettings $ do
102107
runSQL_ "SELECT a.name, ARRAY(SELECT (b.id, b.name, b.year)::book_ FROM books_ b WHERE b.author_id = a.id) FROM authors_ a ORDER BY a.name"
103-
mapDB_ $ \(author, CompositeArray1 (books::[Book])) -> do
108+
mapDB_ $ \(author, CompositeArray1 (books :: [Book])) -> do
104109
printLn $ author <> ":"
105110
forM_ books $ \book -> printLn $ "*" <+> show book
106-
-- | Insert an author.
111+
-- Insert an author.
107112
("insert_author", mname) -> case mread mname of
108-
Just (name::String) -> runDBT cs def . runQuery_ $
109-
"INSERT INTO authors_ (name) VALUES (" <?> name <+> ")"
113+
Just (name :: String) ->
114+
runDBT cs defaultTransactionSettings . runQuery_ $
115+
"INSERT INTO authors_ (name) VALUES (" <?> name <+> ")"
110116
Nothing -> printLn $ "Invalid name"
111-
-- | Insert a book.
117+
-- Insert a book.
112118
("insert_book", mbook) -> case mread mbook of
113-
Just record -> runDBT cs def . runQuery_ $ rawSQL
114-
"INSERT INTO books_ (name, year, author_id) VALUES ($1, $2, $3)"
115-
(record::(String, Int32, Int64))
119+
Just record ->
120+
runDBT cs defaultTransactionSettings . runQuery_ $
121+
rawSQL
122+
"INSERT INTO books_ (name, year, author_id) VALUES ($1, $2, $3)"
123+
(record :: (String, Int32, Int64))
116124
Nothing -> printLn $ "Invalid book record"
117-
-- | Handle unknown commands.
125+
-- Handle unknown commands.
118126
_ -> printLn $ "Unknown command:" <+> cmd
119127
where
120-
parse = second (drop 1) . break (==' ')
128+
parse = second (drop 1) . break (== ' ')
121129

122130
-- | Example chain of commands:
123131
--
@@ -131,14 +139,18 @@ processCommand cs cmd = case parse cmd of
131139
--
132140
-- If you want to check out exceptions in action,
133141
-- try inserting a book with invalid author id.
134-
main :: IO ()
135-
main = do
142+
catalog :: IO ()
143+
catalog = do
136144
cs <- getConnSettings
137145
withCatalog cs $ do
138-
pool <- poolSource (cs { csComposites = ["book_"] }) 1 10 4
139-
fix $ \next -> readline "> " >>= maybe (printLn "") (\cmd -> do
140-
when (cmd /= "quit") $ do
141-
processCommand pool cmd
142-
addHistory cmd
143-
next
144-
)
146+
ConnectionSource pool <- poolSource (cs {csComposites = ["book_"]}) (\connect disconnect -> defaultPoolConfig connect disconnect 1 10)
147+
fix $ \next ->
148+
readline "> "
149+
>>= maybe
150+
(printLn "")
151+
( \cmd -> do
152+
when (cmd /= "quit") $ do
153+
processCommand pool cmd
154+
addHistory cmd
155+
next
156+
)

0 commit comments

Comments
 (0)