Use purs-tidy to format code

This commit is contained in:
Tomasz Rybarczyk 2023-02-25 19:20:16 +01:00
parent d3880f11db
commit 55075095ed
6 changed files with 606 additions and 561 deletions

10
.tidyrc.json Normal file
View File

@ -0,0 +1,10 @@
{
"importSort": "source",
"importWrap": "source",
"indent": 2,
"operatorsFile": null,
"ribbon": 1,
"typeArrowPlacement": "first",
"unicode": "never",
"width": null
}

View File

@ -51,8 +51,7 @@ import Unsafe.Coerce (unsafeCoerce)
-- | PostgreSQL connection.
foreign import data Client :: Type
newtype Connection
= Connection (Either Pool Client)
newtype Connection = Connection (Either Pool Client)
derive instance newtypeConnection :: Newtype Connection _
@ -63,19 +62,18 @@ fromClient :: Client -> Connection
fromClient client = Connection (Right client)
-- | PostgreSQL query with parameter (`$1`, `$2`, …) and return types.
newtype Query ik ok. ik ok Type
newtype Query i o
= Query String
newtype Query :: forall ik ok. ik -> ok -> Type
newtype Query i o = Query String
derive instance newtypeQuery :: Newtype (Query i o) _
-- | Run an action with a client. The client is released to the pool
-- | when the action returns.
withClient ::
forall a.
Pool ->
(Either PGError Client -> Aff a) ->
Aff a
withClient
:: forall a
. Pool
-> (Either PGError Client -> Aff a)
-> Aff a
withClient p k = bracket (connect p) cleanup run
where
cleanup (Left _) = pure unit
@ -88,42 +86,42 @@ withClient p k = bracket (connect p) cleanup run
-- | Trivial helper / shortcut which also wraps
-- | the connection to provide `Connection`.
withConnection ::
forall a.
Pool ->
(Either PGError Connection -> Aff a) ->
Aff a
withConnection
:: forall a
. Pool
-> (Either PGError Connection -> Aff a)
-> Aff a
withConnection p k = withClient p (lcmap (map fromClient) k)
connect ::
Pool ->
Aff (Either PGError ConnectResult)
connect
:: Pool
-> Aff (Either PGError ConnectResult)
connect =
fromEffectFnAff
<<< ffiConnect
{ nullableLeft: toNullable <<< map Left <<< convertError
, right: Right
}
{ nullableLeft: toNullable <<< map Left <<< convertError
, right: Right
}
type ConnectResult
= { client :: Client
, done :: Effect Unit
}
type ConnectResult =
{ client :: Client
, done :: Effect Unit
}
foreign import ffiConnect ::
forall a.
{ nullableLeft :: Error -> Nullable (Either PGError ConnectResult)
, right :: a -> Either PGError ConnectResult
} ->
Pool ->
EffectFnAff (Either PGError ConnectResult)
foreign import ffiConnect
:: forall a
. { nullableLeft :: Error -> Nullable (Either PGError ConnectResult)
, right :: a -> Either PGError ConnectResult
}
-> Pool
-> EffectFnAff (Either PGError ConnectResult)
-- | TODO: Provide docs
withTransaction ::
forall a.
Pool ->
(Connection -> Aff a) ->
Aff (Either PGError a)
withTransaction
:: forall a
. Pool
-> (Connection -> Aff a)
-> Aff (Either PGError a)
withTransaction pool action =
withClient pool case _ of
Right client ->
@ -137,26 +135,26 @@ withTransaction pool action =
-- | `PGError` or a JavaScript exception in the Aff context). If you want to
-- | change the transaction mode, issue a separate `SET TRANSACTION` statement
-- | within the transaction.
withClientTransaction ::
forall a.
Client ->
Aff a ->
Aff (Either PGError a)
withClientTransaction
:: forall a
. Client
-> Aff a
-> Aff (Either PGError a)
withClientTransaction client action =
begin
>>= case _ of
Nothing -> do
a <-
action
`catchError`
\jsErr -> do
void $ rollback
throwError jsErr
commit
>>= case _ of
Just pgError -> pure (Left pgError)
Nothing -> pure (Right a)
Just pgError -> pure (Left pgError)
Nothing -> do
a <-
action
`catchError`
\jsErr -> do
void $ rollback
throwError jsErr
commit
>>= case _ of
Just pgError -> pure (Left pgError)
Nothing -> pure (Right a)
Just pgError -> pure (Left pgError)
where
conn = fromClient client
@ -171,88 +169,88 @@ withClientTransaction client action =
foreign import data UntaggedConnection :: Type
-- | Execute a PostgreSQL query and discard its results.
execute ::
forall i o.
(ToSQLRow i) =>
Connection ->
Query i o ->
i ->
Aff (Maybe PGError)
execute
:: forall i o
. (ToSQLRow i)
=> Connection
-> Query i o
-> i
-> Aff (Maybe PGError)
execute conn (Query sql) values = either Just (const $ Nothing) <$> unsafeQuery conn sql (toSQLRow values)
execute' ::
forall o.
Connection ->
Query Row0 o ->
Aff (Maybe PGError)
execute'
:: forall o
. Connection
-> Query Row0 o
-> Aff (Maybe PGError)
execute' conn (Query sql) = either Just (const $ Nothing) <$> unsafeQuery conn sql (toSQLRow Row0)
-- | Execute a PostgreSQL query and return its results.
query ::
forall i o.
ToSQLRow i =>
FromSQLRow o =>
Connection ->
Query i o ->
i ->
Aff (Either PGError (Array o))
query
:: forall i o
. ToSQLRow i
=> FromSQLRow o
=> Connection
-> Query i o
-> i
-> Aff (Either PGError (Array o))
query conn (Query sql) values = do
r <- unsafeQuery conn sql (toSQLRow values)
pure $ r >>= _.rows >>> traverse (fromSQLRow >>> lmap ConversionError)
query' ::
forall i o.
ToSQLRow i =>
FromSQLRow o =>
Connection ->
Query Row0 o ->
Aff (Either PGError (Array o))
query'
:: forall i o
. ToSQLRow i
=> FromSQLRow o
=> Connection
-> Query Row0 o
-> Aff (Either PGError (Array o))
query' conn (Query sql) = do
r <- unsafeQuery conn sql (toSQLRow Row0)
pure $ r >>= _.rows >>> traverse (fromSQLRow >>> lmap ConversionError)
-- | Execute a PostgreSQL query and return the first field of the first row in
-- | the result.
scalar ::
forall i o.
ToSQLRow i =>
FromSQLValue o =>
Connection ->
Query i (Row1 o) ->
i ->
Aff (Either PGError (Maybe o))
scalar
:: forall i o
. ToSQLRow i
=> FromSQLValue o
=> Connection
-> Query i (Row1 o)
-> i
-> Aff (Either PGError (Maybe o))
scalar conn sql values = query conn sql values <#> map (head >>> map (case _ of Row1 a -> a))
scalar' ::
forall o.
FromSQLValue o =>
Connection ->
Query Row0 (Row1 o) ->
Aff (Either PGError (Maybe o))
scalar'
:: forall o
. FromSQLValue o
=> Connection
-> Query Row0 (Row1 o)
-> Aff (Either PGError (Maybe o))
scalar' conn sql = query conn sql Row0 <#> map (head >>> map (case _ of Row1 a -> a))
-- | Execute a PostgreSQL query and return its command tag value
-- | (how many rows were affected by the query). This may be useful
-- | for example with `DELETE` or `UPDATE` queries.
command ::
forall i.
ToSQLRow i =>
Connection ->
Query i Int ->
i ->
Aff (Either PGError Int)
command
:: forall i
. ToSQLRow i
=> Connection
-> Query i Int
-> i
-> Aff (Either PGError Int)
command conn (Query sql) values = map _.rowCount <$> unsafeQuery conn sql (toSQLRow values)
type QueryResult
= { rows :: Array (Array Foreign)
, rowCount :: Int
}
type QueryResult =
{ rows :: Array (Array Foreign)
, rowCount :: Int
}
unsafeQuery ::
Connection ->
String ->
Array Foreign ->
Aff (Either PGError QueryResult)
unsafeQuery
:: Connection
-> String
-> Array Foreign
-> Aff (Either PGError QueryResult)
unsafeQuery conn s = fromEffectFnAff <<< ffiUnsafeQuery p (toUntaggedHandler conn) s
where
toUntaggedHandler :: Connection -> UntaggedConnection
@ -265,14 +263,14 @@ unsafeQuery conn s = fromEffectFnAff <<< ffiUnsafeQuery p (toUntaggedHandler con
, right: Right
}
foreign import ffiUnsafeQuery ::
{ nullableLeft :: Error -> Nullable (Either PGError QueryResult)
, right :: QueryResult -> Either PGError QueryResult
} ->
UntaggedConnection ->
String ->
Array Foreign ->
EffectFnAff (Either PGError QueryResult)
foreign import ffiUnsafeQuery
:: { nullableLeft :: Error -> Nullable (Either PGError QueryResult)
, right :: QueryResult -> Either PGError QueryResult
}
-> UntaggedConnection
-> String
-> Array Foreign
-> EffectFnAff (Either PGError QueryResult)
data PGError
= ClientError Error String
@ -312,26 +310,26 @@ derive instance genericPGError :: Generic PGError _
instance showPGError :: Show PGError where
show = genericShow
type PGErrorDetail
= { severity :: String
, code :: String
, message :: String
, detail :: String
, error :: Error
, hint :: String
, position :: String
, internalPosition :: String
, internalQuery :: String
, where_ :: String
, schema :: String
, table :: String
, column :: String
, dataType :: String
, constraint :: String
, file :: String
, line :: String
, routine :: String
}
type PGErrorDetail =
{ severity :: String
, code :: String
, message :: String
, detail :: String
, error :: Error
, hint :: String
, position :: String
, internalPosition :: String
, internalQuery :: String
, where_ :: String
, schema :: String
, table :: String
, column :: String
, dataType :: String
, constraint :: String
, file :: String
, line :: String
, routine :: String
}
foreign import ffiSQLState :: Error -> Nullable String

View File

@ -24,20 +24,19 @@ import Database.PostgreSQL.Value (class FromSQLValue)
import Effect.Aff (Aff)
import Effect.Aff.Class (class MonadAff, liftAff)
type PG a
= Aff (Either PGError a)
type PG a = Aff (Either PGError a)
hoistPG :: a m. MonadAff m => MonadError PGError m => PG a -> m a
hoistPG :: forall a m. MonadAff m => MonadError PGError m => PG a -> m a
hoistPG m = liftAff m >>= either throwError pure
withClient ::
a m.
MonadError PGError m =>
MonadAff m =>
(m a -> Aff (Either PGError a)) ->
Pool ->
(Client -> m a) ->
m a
withClient
:: forall a m
. MonadError PGError m
=> MonadAff m
=> (m a -> Aff (Either PGError a))
-> Pool
-> (Client -> m a)
-> m a
withClient f p k = do
res <-
liftAff
@ -46,24 +45,24 @@ withClient f p k = do
Left pgErr -> pure $ Left pgErr
either throwError pure res
withConnection ::
a m.
MonadError PGError m =>
MonadAff m =>
(m a -> Aff (Either PGError a)) ->
Pool ->
(Connection -> m a) ->
m a
withConnection
:: forall a m
. MonadError PGError m
=> MonadAff m
=> (m a -> Aff (Either PGError a))
-> Pool
-> (Connection -> m a)
-> m a
withConnection f p k = withClient f p (lcmap fromClient k)
withTransaction ::
a m.
MonadAff m =>
MonadError PGError m =>
(m a -> Aff (Either PGError a)) ->
Pool ->
(Connection -> m a) ->
m a
withTransaction
:: forall a m
. MonadAff m
=> MonadError PGError m
=> (m a -> Aff (Either PGError a))
-> Pool
-> (Connection -> m a)
-> m a
withTransaction f pool action = do
res <-
liftAff
@ -71,79 +70,79 @@ withTransaction f pool action = do
(f (action client))
either throwError pure $ join res
withClientTransaction ::
a m.
MonadAff m =>
MonadError PGError m =>
(m a -> Aff (Either PGError a)) ->
Client ->
m a ->
m a
withClientTransaction
:: forall a m
. MonadAff m
=> MonadError PGError m
=> (m a -> Aff (Either PGError a))
-> Client
-> m a
-> m a
withClientTransaction f client action = do
res <- liftAff $ Aff.withClientTransaction client (f action)
either throwError pure $ join res
-- | Execute a PostgreSQL query and discard its results.
execute ::
i o m.
ToSQLRow i =>
MonadError PGError m =>
MonadAff m =>
Connection ->
Query i o ->
i ->
m Unit
execute
:: forall i o m
. ToSQLRow i
=> MonadError PGError m
=> MonadAff m
=> Connection
-> Query i o
-> i
-> m Unit
execute h sql values = do
err <- liftAff $ Aff.execute h sql values
maybe (pure unit) throwError err
-- | Execute a PostgreSQL query and return its results.
query ::
i o m.
ToSQLRow i =>
FromSQLRow o =>
MonadError PGError m =>
MonadAff m =>
Connection ->
Query i o ->
i ->
m (Array o)
query
:: forall i o m
. ToSQLRow i
=> FromSQLRow o
=> MonadError PGError m
=> MonadAff m
=> Connection
-> Query i o
-> i
-> m (Array o)
query h sql = hoistPG <<< Aff.query h sql
-- | Execute a PostgreSQL query and return the first field of the first row in
-- | the result.
scalar ::
i o m.
ToSQLRow i =>
FromSQLValue o =>
MonadError PGError m =>
MonadAff m =>
Connection ->
Query i (Row1 o) ->
i ->
m (Maybe o)
scalar
:: forall i o m
. ToSQLRow i
=> FromSQLValue o
=> MonadError PGError m
=> MonadAff m
=> Connection
-> Query i (Row1 o)
-> i
-> m (Maybe o)
scalar h sql = hoistPG <<< Aff.scalar h sql
-- | Execute a PostgreSQL query and return its command tag value
-- | (how many rows were affected by the query). This may be useful
-- | for example with `DELETE` or `UPDATE` queries.
command ::
i m.
ToSQLRow i =>
MonadError PGError m =>
MonadAff m =>
Connection ->
Query i Int ->
i ->
m Int
command
:: forall i m
. ToSQLRow i
=> MonadError PGError m
=> MonadAff m
=> Connection
-> Query i Int
-> i
-> m Int
command h sql = hoistPG <<< Aff.command h sql
onIntegrityError ::
a m.
MonadError PGError m =>
m a ->
m a ->
m a
onIntegrityError
:: forall a m
. MonadError PGError m
=> m a
-> m a
-> m a
onIntegrityError errorResult db = catchError db handleError
where
handleError e = case e of

View File

@ -9,8 +9,7 @@ module Database.PostgreSQL.Pool
, Pool
, totalCount
, waitingCount
)
where
) where
import Prelude (bind, flip, pure, ($))
@ -28,33 +27,31 @@ import StringParser.Combinators (many, manyTill)
-- | PostgreSQL connection pool.
foreign import data Pool :: Type
type Database
= String
type Database = String
-- | Configuration which we actually pass to FFI.
type Configuration'
= { user :: Nullable String
, password :: Nullable String
, host :: Nullable String
, port :: Nullable Int
, database :: String
, max :: Nullable Int
, idleTimeoutMillis :: Nullable Int
}
type Configuration' =
{ user :: Nullable String
, password :: Nullable String
, host :: Nullable String
, port :: Nullable Int
, database :: String
, max :: Nullable Int
, idleTimeoutMillis :: Nullable Int
}
-- | PostgreSQL connection pool configuration.
type Configuration
= { database :: Database
, host :: Maybe String
, idleTimeoutMillis :: Maybe Int
, max :: Maybe Int
, password :: Maybe String
, port :: Maybe Int
, user :: Maybe String
}
type Configuration =
{ database :: Database
, host :: Maybe String
, idleTimeoutMillis :: Maybe Int
, max :: Maybe Int
, password :: Maybe String
, port :: Maybe Int
, user :: Maybe String
}
type PGConnectionURI
= String
type PGConnectionURI = String
-- | Get the default pool configuration from postgres connection uri
-- | TODO:
@ -95,9 +92,9 @@ defaultConfiguration database =
, user: Nothing
}
foreign import ffiNew ::
Configuration' ->
Effect Pool
foreign import ffiNew
:: Configuration'
-> Effect Pool
-- | Create a new connection pool.
new :: Configuration -> Effect Pool

View File

@ -11,11 +11,11 @@ import Foreign (Foreign)
-- | Convert things to SQL rows.
class ToSQLRow a where
toSQLRow :: a -> Array Foreign
toSQLRow :: a -> Array Foreign
-- | Convert things from SQL rows.
class FromSQLRow a where
fromSQLRow :: Array Foreign -> Either String a
fromSQLRow :: Array Foreign -> Either String a
instance toSQLRowForeignArray :: ToSQLRow (Array Foreign) where
toSQLRow = identity
@ -31,13 +31,13 @@ else instance toSQLRowTupleTwo :: (ToSQLValue a, ToSQLValue b) => ToSQLRow (Tupl
instance fromSQLRowTuple :: (FromSQLValue a, FromSQLRow (Tuple b t)) => FromSQLRow (Tuple a (Tuple b t)) where
fromSQLRow r = do
{head, tail} note "Expecting more fields in a row" $ uncons r
{ head, tail } <- note "Expecting more fields in a row" $ uncons r
Tuple <$> fromSQLValue head <*> fromSQLRow tail
else instance fromSQLRowTupleOne :: FromSQLValue a => FromSQLRow (Tuple a Unit) where
fromSQLRow [a] = Tuple <$> fromSQLValue a <@> unit
fromSQLRow [ a ] = Tuple <$> fromSQLValue a <@> unit
fromSQLRow _ = Left "Expecting exactly one field."
else instance fromSQLRowTupleTwo :: (FromSQLValue a, FromSQLValue b) => FromSQLRow (Tuple a b) where
fromSQLRow [a, b] = Tuple <$> fromSQLValue a <*> fromSQLValue b
fromSQLRow [ a, b ] = Tuple <$> fromSQLValue a <*> fromSQLValue b
fromSQLRow _ = Left "Expecting exactly two more fields."
-- | A row with 0 fields.
@ -55,10 +55,12 @@ instance fromSQLRowRow0 :: FromSQLRow Row0 where
fromSQLRow [] =
pure Row0
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 0."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow0 :: ToSQLRow Row0 where
toSQLRow Row0 = []
-- | A row with 1 field.
data Row1 a = Row1 a
@ -71,15 +73,17 @@ instance showRow1 :: (Show a) => Show (Row1 a) where
"(Row1 " <> show a <> ")"
instance fromSQLRowRow1 :: (FromSQLValue a) => FromSQLRow (Row1 a) where
fromSQLRow [a] =
fromSQLRow [ a ] =
pure Row1
<*> fromSQLValue a
<*> fromSQLValue a
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 1."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow1 :: (ToSQLValue a) => ToSQLRow (Row1 a) where
toSQLRow (Row1 a) =
[toSQLValue a]
[ toSQLValue a ]
-- | A row with 2 fields.
data Row2 a b = Row2 a b
@ -92,16 +96,18 @@ instance showRow2 :: (Show a, Show b) => Show (Row2 a b) where
"(Row2 " <> show a <> " " <> show b <> ")"
instance fromSQLRowRow2 :: (FromSQLValue a, FromSQLValue b) => FromSQLRow (Row2 a b) where
fromSQLRow [a, b] =
fromSQLRow [ a, b ] =
pure Row2
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue a
<*> fromSQLValue b
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 2."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow2 :: (ToSQLValue a, ToSQLValue b) => ToSQLRow (Row2 a b) where
toSQLRow (Row2 a b) =
[toSQLValue a, toSQLValue b]
[ toSQLValue a, toSQLValue b ]
-- | A row with 3 fields.
data Row3 a b c = Row3 a b c
@ -114,17 +120,19 @@ instance showRow3 :: (Show a, Show b, Show c) => Show (Row3 a b c) where
"(Row3 " <> show a <> " " <> show b <> " " <> show c <> ")"
instance fromSQLRowRow3 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c) => FromSQLRow (Row3 a b c) where
fromSQLRow [a, b, c] =
fromSQLRow [ a, b, c ] =
pure Row3
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 3."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow3 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c) => ToSQLRow (Row3 a b c) where
toSQLRow (Row3 a b c) =
[toSQLValue a, toSQLValue b, toSQLValue c]
[ toSQLValue a, toSQLValue b, toSQLValue c ]
-- | A row with 4 fields.
data Row4 a b c d = Row4 a b c d
@ -137,18 +145,20 @@ instance showRow4 :: (Show a, Show b, Show c, Show d) => Show (Row4 a b c d) whe
"(Row4 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> ")"
instance fromSQLRowRow4 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d) => FromSQLRow (Row4 a b c d) where
fromSQLRow [a, b, c, d] =
fromSQLRow [ a, b, c, d ] =
pure Row4
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 4."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow4 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d) => ToSQLRow (Row4 a b c d) where
toSQLRow (Row4 a b c d) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d ]
-- | A row with 5 fields.
data Row5 a b c d e = Row5 a b c d e
@ -161,19 +171,21 @@ instance showRow5 :: (Show a, Show b, Show c, Show d, Show e) => Show (Row5 a b
"(Row5 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> ")"
instance fromSQLRowRow5 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e) => FromSQLRow (Row5 a b c d e) where
fromSQLRow [a, b, c, d, e] =
fromSQLRow [ a, b, c, d, e ] =
pure Row5
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 5."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow5 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e) => ToSQLRow (Row5 a b c d e) where
toSQLRow (Row5 a b c d e) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e ]
-- | A row with 6 fields.
data Row6 a b c d e f = Row6 a b c d e f
@ -186,20 +198,22 @@ instance showRow6 :: (Show a, Show b, Show c, Show d, Show e, Show f) => Show (R
"(Row6 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> ")"
instance fromSQLRowRow6 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f) => FromSQLRow (Row6 a b c d e f) where
fromSQLRow [a, b, c, d, e, f] =
fromSQLRow [ a, b, c, d, e, f ] =
pure Row6
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 6."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow6 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f) => ToSQLRow (Row6 a b c d e f) where
toSQLRow (Row6 a b c d e f) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f ]
-- | A row with 7 fields.
data Row7 a b c d e f g = Row7 a b c d e f g
@ -212,21 +226,23 @@ instance showRow7 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g) =>
"(Row7 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> ")"
instance fromSQLRowRow7 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g) => FromSQLRow (Row7 a b c d e f g) where
fromSQLRow [a, b, c, d, e, f, g] =
fromSQLRow [ a, b, c, d, e, f, g ] =
pure Row7
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 7."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow7 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g) => ToSQLRow (Row7 a b c d e f g) where
toSQLRow (Row7 a b c d e f g) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g ]
-- | A row with 8 fields.
data Row8 a b c d e f g h = Row8 a b c d e f g h
@ -239,22 +255,24 @@ instance showRow8 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Sh
"(Row8 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> ")"
instance fromSQLRowRow8 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h) => FromSQLRow (Row8 a b c d e f g h) where
fromSQLRow [a, b, c, d, e, f, g, h] =
fromSQLRow [ a, b, c, d, e, f, g, h ] =
pure Row8
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 8."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow8 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h) => ToSQLRow (Row8 a b c d e f g h) where
toSQLRow (Row8 a b c d e f g h) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h ]
-- | A row with 9 fields.
data Row9 a b c d e f g h i = Row9 a b c d e f g h i
@ -267,23 +285,25 @@ instance showRow9 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Sh
"(Row9 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> ")"
instance fromSQLRowRow9 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i) => FromSQLRow (Row9 a b c d e f g h i) where
fromSQLRow [a, b, c, d, e, f, g, h, i] =
fromSQLRow [ a, b, c, d, e, f, g, h, i ] =
pure Row9
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 9."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow9 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i) => ToSQLRow (Row9 a b c d e f g h i) where
toSQLRow (Row9 a b c d e f g h i) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i ]
-- | A row with 10 fields.
data Row10 a b c d e f g h i j = Row10 a b c d e f g h i j
@ -296,24 +316,26 @@ instance showRow10 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row10 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> ")"
instance fromSQLRowRow10 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j) => FromSQLRow (Row10 a b c d e f g h i j) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j ] =
pure Row10
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 10."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow10 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j) => ToSQLRow (Row10 a b c d e f g h i j) where
toSQLRow (Row10 a b c d e f g h i j) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j ]
-- | A row with 11 fields.
data Row11 a b c d e f g h i j k = Row11 a b c d e f g h i j k
@ -326,25 +348,27 @@ instance showRow11 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row11 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> ")"
instance fromSQLRowRow11 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k) => FromSQLRow (Row11 a b c d e f g h i j k) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k ] =
pure Row11
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 11."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow11 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k) => ToSQLRow (Row11 a b c d e f g h i j k) where
toSQLRow (Row11 a b c d e f g h i j k) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k ]
-- | A row with 12 fields.
data Row12 a b c d e f g h i j k l = Row12 a b c d e f g h i j k l
@ -357,26 +381,28 @@ instance showRow12 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row12 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> " " <> show l <> ")"
instance fromSQLRowRow12 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k, FromSQLValue l) => FromSQLRow (Row12 a b c d e f g h i j k l) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k, l] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k, l ] =
pure Row12
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 12."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow12 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k, ToSQLValue l) => ToSQLRow (Row12 a b c d e f g h i j k l) where
toSQLRow (Row12 a b c d e f g h i j k l) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l ]
-- | A row with 13 fields.
data Row13 a b c d e f g h i j k l m = Row13 a b c d e f g h i j k l m
@ -389,27 +415,29 @@ instance showRow13 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row13 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> " " <> show l <> " " <> show m <> ")"
instance fromSQLRowRow13 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k, FromSQLValue l, FromSQLValue m) => FromSQLRow (Row13 a b c d e f g h i j k l m) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k, l, m] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k, l, m ] =
pure Row13
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 13."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow13 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k, ToSQLValue l, ToSQLValue m) => ToSQLRow (Row13 a b c d e f g h i j k l m) where
toSQLRow (Row13 a b c d e f g h i j k l m) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m ]
-- | A row with 14 fields.
data Row14 a b c d e f g h i j k l m n = Row14 a b c d e f g h i j k l m n
@ -422,28 +450,30 @@ instance showRow14 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row14 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> " " <> show l <> " " <> show m <> " " <> show n <> ")"
instance fromSQLRowRow14 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k, FromSQLValue l, FromSQLValue m, FromSQLValue n) => FromSQLRow (Row14 a b c d e f g h i j k l m n) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k, l, m, n] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k, l, m, n ] =
pure Row14
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 14."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow14 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k, ToSQLValue l, ToSQLValue m, ToSQLValue n) => ToSQLRow (Row14 a b c d e f g h i j k l m n) where
toSQLRow (Row14 a b c d e f g h i j k l m n) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n ]
-- | A row with 15 fields.
data Row15 a b c d e f g h i j k l m n o = Row15 a b c d e f g h i j k l m n o
@ -456,29 +486,31 @@ instance showRow15 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row15 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> " " <> show l <> " " <> show m <> " " <> show n <> " " <> show o <> ")"
instance fromSQLRowRow15 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k, FromSQLValue l, FromSQLValue m, FromSQLValue n, FromSQLValue o) => FromSQLRow (Row15 a b c d e f g h i j k l m n o) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k, l, m, n, o] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k, l, m, n, o ] =
pure Row15
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 15."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow15 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k, ToSQLValue l, ToSQLValue m, ToSQLValue n, ToSQLValue o) => ToSQLRow (Row15 a b c d e f g h i j k l m n o) where
toSQLRow (Row15 a b c d e f g h i j k l m n o) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o ]
-- | A row with 16 fields.
data Row16 a b c d e f g h i j k l m n o p = Row16 a b c d e f g h i j k l m n o p
@ -491,30 +523,32 @@ instance showRow16 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row16 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> " " <> show l <> " " <> show m <> " " <> show n <> " " <> show o <> " " <> show p <> ")"
instance fromSQLRowRow16 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k, FromSQLValue l, FromSQLValue m, FromSQLValue n, FromSQLValue o, FromSQLValue p) => FromSQLRow (Row16 a b c d e f g h i j k l m n o p) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p ] =
pure Row16
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue p
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue p
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 16."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow16 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k, ToSQLValue l, ToSQLValue m, ToSQLValue n, ToSQLValue o, ToSQLValue p) => ToSQLRow (Row16 a b c d e f g h i j k l m n o p) where
toSQLRow (Row16 a b c d e f g h i j k l m n o p) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o, toSQLValue p]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o, toSQLValue p ]
-- | A row with 17 fields.
data Row17 a b c d e f g h i j k l m n o p q = Row17 a b c d e f g h i j k l m n o p q
@ -527,31 +561,33 @@ instance showRow17 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row17 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> " " <> show l <> " " <> show m <> " " <> show n <> " " <> show o <> " " <> show p <> " " <> show q <> ")"
instance fromSQLRowRow17 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k, FromSQLValue l, FromSQLValue m, FromSQLValue n, FromSQLValue o, FromSQLValue p, FromSQLValue q) => FromSQLRow (Row17 a b c d e f g h i j k l m n o p q) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q ] =
pure Row17
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue p
<*> fromSQLValue q
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue p
<*> fromSQLValue q
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 17."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow17 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k, ToSQLValue l, ToSQLValue m, ToSQLValue n, ToSQLValue o, ToSQLValue p, ToSQLValue q) => ToSQLRow (Row17 a b c d e f g h i j k l m n o p q) where
toSQLRow (Row17 a b c d e f g h i j k l m n o p q) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o, toSQLValue p, toSQLValue q]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o, toSQLValue p, toSQLValue q ]
-- | A row with 18 fields.
data Row18 a b c d e f g h i j k l m n o p q r = Row18 a b c d e f g h i j k l m n o p q r
@ -564,32 +600,34 @@ instance showRow18 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row18 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> " " <> show l <> " " <> show m <> " " <> show n <> " " <> show o <> " " <> show p <> " " <> show q <> " " <> show r <> ")"
instance fromSQLRowRow18 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k, FromSQLValue l, FromSQLValue m, FromSQLValue n, FromSQLValue o, FromSQLValue p, FromSQLValue q, FromSQLValue r) => FromSQLRow (Row18 a b c d e f g h i j k l m n o p q r) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r ] =
pure Row18
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue p
<*> fromSQLValue q
<*> fromSQLValue r
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue p
<*> fromSQLValue q
<*> fromSQLValue r
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 18."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow18 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k, ToSQLValue l, ToSQLValue m, ToSQLValue n, ToSQLValue o, ToSQLValue p, ToSQLValue q, ToSQLValue r) => ToSQLRow (Row18 a b c d e f g h i j k l m n o p q r) where
toSQLRow (Row18 a b c d e f g h i j k l m n o p q r) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o, toSQLValue p, toSQLValue q, toSQLValue r]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o, toSQLValue p, toSQLValue q, toSQLValue r ]
-- | A row with 19 fields.
data Row19 a b c d e f g h i j k l m n o p q r s = Row19 a b c d e f g h i j k l m n o p q r s
@ -602,30 +640,31 @@ instance showRow19 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, S
"(Row19 " <> show a <> " " <> show b <> " " <> show c <> " " <> show d <> " " <> show e <> " " <> show f <> " " <> show g <> " " <> show h <> " " <> show i <> " " <> show j <> " " <> show k <> " " <> show l <> " " <> show m <> " " <> show n <> " " <> show o <> " " <> show p <> " " <> show q <> " " <> show r <> " " <> show s <> ")"
instance fromSQLRowRow19 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, FromSQLValue d, FromSQLValue e, FromSQLValue f, FromSQLValue g, FromSQLValue h, FromSQLValue i, FromSQLValue j, FromSQLValue k, FromSQLValue l, FromSQLValue m, FromSQLValue n, FromSQLValue o, FromSQLValue p, FromSQLValue q, FromSQLValue r, FromSQLValue s) => FromSQLRow (Row19 a b c d e f g h i j k l m n o p q r s) where
fromSQLRow [a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s] =
fromSQLRow [ a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s ] =
pure Row19
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue p
<*> fromSQLValue q
<*> fromSQLValue r
<*> fromSQLValue s
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
<*> fromSQLValue e
<*> fromSQLValue f
<*> fromSQLValue g
<*> fromSQLValue h
<*> fromSQLValue i
<*> fromSQLValue j
<*> fromSQLValue k
<*> fromSQLValue l
<*> fromSQLValue m
<*> fromSQLValue n
<*> fromSQLValue o
<*> fromSQLValue p
<*> fromSQLValue q
<*> fromSQLValue r
<*> fromSQLValue s
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 19."
where n = Array.length xs
where
n = Array.length xs
instance toSQLRowRow19 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d, ToSQLValue e, ToSQLValue f, ToSQLValue g, ToSQLValue h, ToSQLValue i, ToSQLValue j, ToSQLValue k, ToSQLValue l, ToSQLValue m, ToSQLValue n, ToSQLValue o, ToSQLValue p, ToSQLValue q, ToSQLValue r, ToSQLValue s) => ToSQLRow (Row19 a b c d e f g h i j k l m n o p q r s) where
toSQLRow (Row19 a b c d e f g h i j k l m n o p q r s) =
[toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o, toSQLValue p, toSQLValue q, toSQLValue r, toSQLValue s]
[ toSQLValue a, toSQLValue b, toSQLValue c, toSQLValue d, toSQLValue e, toSQLValue f, toSQLValue g, toSQLValue h, toSQLValue i, toSQLValue j, toSQLValue k, toSQLValue l, toSQLValue m, toSQLValue n, toSQLValue o, toSQLValue p, toSQLValue q, toSQLValue r, toSQLValue s ]

View File

@ -37,138 +37,140 @@ import Foreign.Object (Object)
-- | Convert things to SQL values.
class ToSQLValue a where
toSQLValue :: a -> Foreign
toSQLValue :: a -> Foreign
-- | Convert things from SQL values.
class FromSQLValue a where
fromSQLValue :: Foreign -> Either String a
fromSQLValue :: Foreign -> Either String a
instance fromSQLValueBoolean :: FromSQLValue Boolean where
fromSQLValue = lmap show <<< runExcept <<< readBoolean
fromSQLValue = lmap show <<< runExcept <<< readBoolean
else instance fromSQLValueChar :: FromSQLValue Char where
fromSQLValue = lmap show <<< runExcept <<< readChar
fromSQLValue = lmap show <<< runExcept <<< readChar
else instance fromSQLValueInt :: FromSQLValue Int where
fromSQLValue = lmap show <<< runExcept <<< readInt
fromSQLValue = lmap show <<< runExcept <<< readInt
else instance fromSQLValueNumber :: FromSQLValue Number where
fromSQLValue = lmap show <<< runExcept <<< readNumber
fromSQLValue = lmap show <<< runExcept <<< readNumber
else instance fromSQLValueString :: FromSQLValue String where
fromSQLValue = lmap show <<< runExcept <<< readString
fromSQLValue = lmap show <<< runExcept <<< readString
else instance fromSQLValueArray :: (FromSQLValue a) => FromSQLValue (Array a) where
fromSQLValue = traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
fromSQLValue = traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
else instance fromSQLValueList :: (FromSQLValue a) => FromSQLValue (List a) where
fromSQLValue = map List.fromFoldable <<< traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
fromSQLValue = map List.fromFoldable <<< traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
else instance fromSQLValueByteString :: FromSQLValue ByteString where
fromSQLValue x
| unsafeIsBuffer x = pure $ unsafeFromForeign x
| otherwise = throwError "FromSQLValue ByteString: not a buffer"
fromSQLValue x
| unsafeIsBuffer x = pure $ unsafeFromForeign x
| otherwise = throwError "FromSQLValue ByteString: not a buffer"
else instance fromSQLValueInstant :: FromSQLValue Instant where
fromSQLValue v = do
t <- instantFromString Left Right v
note ("Instant construction failed for given timestamp: " <> show t) $ instant (Milliseconds t)
fromSQLValue v = do
t <- instantFromString Left Right v
note ("Instant construction failed for given timestamp: " <> show t) $ instant (Milliseconds t)
else instance fromSQLValueDate :: FromSQLValue Date where
fromSQLValue v = do
s <- lmap show $ runExcept (readString v)
fromSQLValue v = do
s <- lmap show $ runExcept (readString v)
let
msg = "Date parsing failed for value: " <> s
case split (Pattern "-") s of
[ y, m, d ] -> do
let
msg = "Date parsing failed for value: " <> s
case split (Pattern "-") s of
[y, m, d] -> do
let
result = canonicalDate
<$> (toEnum =<< fromString y)
<*> (toEnum =<< fromString m)
<*> (toEnum =<< fromString d)
note msg result
_ -> Left msg
result = canonicalDate
<$> (toEnum =<< fromString y)
<*> (toEnum =<< fromString m)
<*> (toEnum =<< fromString d)
note msg result
_ -> Left msg
else instance fromSQLValueJSDate :: FromSQLValue JSDate where
fromSQLValue = Right <<< unsafeFromForeign
fromSQLValue = Right <<< unsafeFromForeign
else instance fromSQLValueMaybe :: (FromSQLValue a) => FromSQLValue (Maybe a) where
fromSQLValue x | isNull x = pure Nothing
| otherwise = Just <$> fromSQLValue x
fromSQLValue x
| isNull x = pure Nothing
| otherwise = Just <$> fromSQLValue x
else instance fromSQLValueForeign :: FromSQLValue Foreign where
fromSQLValue = pure
fromSQLValue = pure
else instance fromSQLValueObject :: FromSQLValue a FromSQLValue (Object a) where
else instance fromSQLValueObject :: FromSQLValue a => FromSQLValue (Object a) where
fromSQLValue sql = lmap showErr $ unwrap $ runExceptT main
where
showErr MultipleErrors String
showErr e = foldl (\a x a <> renderForeignError x <> " ") "" e
main ExceptT MultipleErrors Identity (Object a)
showErr :: MultipleErrors -> String
showErr e = foldl (\a x -> a <> renderForeignError x <> " ") "" e
main :: ExceptT MultipleErrors Identity (Object a)
main = do
objF Object Foreign <- readObject sql
objF :: Object Foreign <- readObject sql
let eso = sequence $ map fromSQLValue objF
let emo = lmap (singleton <<< ForeignError) eso
except emo
else instance fromSQLValueDecimal :: FromSQLValue Decimal where
fromSQLValue v = do
s <- lmap show $ runExcept (readString v)
note ("Decimal literal parsing failed: " <> s) (Decimal.fromString s)
fromSQLValue v = do
s <- lmap show $ runExcept (readString v)
note ("Decimal literal parsing failed: " <> s) (Decimal.fromString s)
else instance fromSQLValueJson :: FromSQLValue Json where
fromSQLValue = Right <<< unsafeFromForeign
newtypeFromSQLValue a b. Newtype a b FromSQLValue b Foreign Either String a
newtypeFromSQLValue :: forall a b. Newtype a b => FromSQLValue b => Foreign -> Either String a
newtypeFromSQLValue = map wrap <<< fromSQLValue
instance toSQLValueBoolean :: ToSQLValue Boolean where
toSQLValue = unsafeToForeign
toSQLValue = unsafeToForeign
else instance toSQLValueChar :: ToSQLValue Char where
toSQLValue = unsafeToForeign
toSQLValue = unsafeToForeign
else instance toSQLValueInt :: ToSQLValue Int where
toSQLValue = unsafeToForeign
toSQLValue = unsafeToForeign
else instance toSQLValueNumber :: ToSQLValue Number where
toSQLValue = unsafeToForeign
toSQLValue = unsafeToForeign
else instance toSQLValueString :: ToSQLValue String where
toSQLValue = unsafeToForeign
toSQLValue = unsafeToForeign
else instance toSQLValueArray :: (ToSQLValue a) => ToSQLValue (Array a) where
toSQLValue = unsafeToForeign <<< map toSQLValue
toSQLValue = unsafeToForeign <<< map toSQLValue
else instance toSQLValueList :: (ToSQLValue a) => ToSQLValue (List a) where
toSQLValue = unsafeToForeign <<< Array.fromFoldable <<< map toSQLValue
toSQLValue = unsafeToForeign <<< Array.fromFoldable <<< map toSQLValue
else instance toSQLValueByteString :: ToSQLValue ByteString where
toSQLValue = unsafeToForeign
toSQLValue = unsafeToForeign
else instance toSQLValueInstant :: ToSQLValue Instant where
toSQLValue = instantToString
toSQLValue = instantToString
else instance toSQLValueDate :: ToSQLValue Date where
toSQLValue date =
let
y = fromEnum $ year date
m = fromEnum $ month date
d = fromEnum $ day date
in
unsafeToForeign $ show y <> "-" <> show m <> "-" <> show d
toSQLValue date =
let
y = fromEnum $ year date
m = fromEnum $ month date
d = fromEnum $ day date
in
unsafeToForeign $ show y <> "-" <> show m <> "-" <> show d
else instance toSQLValueJSDate :: ToSQLValue JSDate where
toSQLValue = unsafeToForeign
toSQLValue = unsafeToForeign
else instance toSQLValueMaybe :: (ToSQLValue a) => ToSQLValue (Maybe a) where
toSQLValue Nothing = null
toSQLValue (Just x) = toSQLValue x
toSQLValue Nothing = null
toSQLValue (Just x) = toSQLValue x
else instance toSQLValueForeign :: ToSQLValue Foreign where
toSQLValue = identity
toSQLValue = identity
else instance toSQLValueObject ToSQLValue a ToSQLValue (Object a) where
else instance toSQLValueObject :: ToSQLValue a => ToSQLValue (Object a) where
toSQLValue = unsafeToForeign
else instance toSQLValueDecimal :: ToSQLValue Decimal where
@ -180,7 +182,7 @@ else instance toSQLValueJson :: ToSQLValue Json where
-- | https://github.com/brianc/node-postgres/issues/1383
toSQLValue = Argonaut.stringify >>> unsafeToForeign
newtypeToSQLValue a b. Newtype a b ToSQLValue b a Foreign
newtypeToSQLValue :: forall a b. Newtype a b => ToSQLValue b => a -> Foreign
newtypeToSQLValue = unwrap >>> toSQLValue
null :: Foreign
@ -189,4 +191,4 @@ null = null_
foreign import null_ :: Foreign
foreign import instantToString :: Instant -> Foreign
foreign import instantFromString :: (String -> Either String Number) -> (Number -> Either String Number) -> Foreign -> Either String Number
foreign import unsafeIsBuffer :: a. a -> Boolean
foreign import unsafeIsBuffer :: forall a. a -> Boolean