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

View File

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

View File

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

View File

@ -31,7 +31,7 @@ else instance toSQLRowTupleTwo :: (ToSQLValue a, ToSQLValue b) => ToSQLRow (Tupl
instance fromSQLRowTuple :: (FromSQLValue a, FromSQLRow (Tuple b t)) => FromSQLRow (Tuple a (Tuple b t)) where instance fromSQLRowTuple :: (FromSQLValue a, FromSQLRow (Tuple b t)) => FromSQLRow (Tuple a (Tuple b t)) where
fromSQLRow r = do 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 Tuple <$> fromSQLValue head <*> fromSQLRow tail
else instance fromSQLRowTupleOne :: FromSQLValue a => FromSQLRow (Tuple a Unit) where else instance fromSQLRowTupleOne :: FromSQLValue a => FromSQLRow (Tuple a Unit) where
fromSQLRow [ a ] = Tuple <$> fromSQLValue a <@> unit fromSQLRow [ a ] = Tuple <$> fromSQLValue a <@> unit
@ -55,10 +55,12 @@ instance fromSQLRowRow0 :: FromSQLRow Row0 where
fromSQLRow [] = fromSQLRow [] =
pure Row0 pure Row0
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 0." 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 instance toSQLRowRow0 :: ToSQLRow Row0 where
toSQLRow Row0 = [] toSQLRow Row0 = []
-- | A row with 1 field. -- | A row with 1 field.
data Row1 a = Row1 a data Row1 a = Row1 a
@ -75,11 +77,13 @@ instance fromSQLRowRow1 :: (FromSQLValue a) => FromSQLRow (Row1 a) where
pure Row1 pure Row1
<*> fromSQLValue a <*> fromSQLValue a
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 1." 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 instance toSQLRowRow1 :: (ToSQLValue a) => ToSQLRow (Row1 a) where
toSQLRow (Row1 a) = toSQLRow (Row1 a) =
[ toSQLValue a ] [ toSQLValue a ]
-- | A row with 2 fields. -- | A row with 2 fields.
data Row2 a b = Row2 a b data Row2 a b = Row2 a b
@ -97,11 +101,13 @@ instance fromSQLRowRow2 :: (FromSQLValue a, FromSQLValue b) => FromSQLRow (Row2
<*> fromSQLValue a <*> fromSQLValue a
<*> fromSQLValue b <*> fromSQLValue b
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 2." 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 instance toSQLRowRow2 :: (ToSQLValue a, ToSQLValue b) => ToSQLRow (Row2 a b) where
toSQLRow (Row2 a b) = toSQLRow (Row2 a b) =
[ toSQLValue a, toSQLValue b ] [ toSQLValue a, toSQLValue b ]
-- | A row with 3 fields. -- | A row with 3 fields.
data Row3 a b c = Row3 a b c data Row3 a b c = Row3 a b c
@ -120,11 +126,13 @@ instance fromSQLRowRow3 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c) => F
<*> fromSQLValue b <*> fromSQLValue b
<*> fromSQLValue c <*> fromSQLValue c
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 3." 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 instance toSQLRowRow3 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c) => ToSQLRow (Row3 a b c) where
toSQLRow (Row3 a b c) = toSQLRow (Row3 a b c) =
[ toSQLValue a, toSQLValue b, toSQLValue c ] [ toSQLValue a, toSQLValue b, toSQLValue c ]
-- | A row with 4 fields. -- | A row with 4 fields.
data Row4 a b c d = Row4 a b c d data Row4 a b c d = Row4 a b c d
@ -144,11 +152,13 @@ instance fromSQLRowRow4 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, From
<*> fromSQLValue c <*> fromSQLValue c
<*> fromSQLValue d <*> fromSQLValue d
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 4." 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 instance toSQLRowRow4 :: (ToSQLValue a, ToSQLValue b, ToSQLValue c, ToSQLValue d) => ToSQLRow (Row4 a b c d) where
toSQLRow (Row4 a b c d) = 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. -- | A row with 5 fields.
data Row5 a b c d e = Row5 a b c d e data Row5 a b c d e = Row5 a b c d e
@ -169,11 +179,13 @@ instance fromSQLRowRow5 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, From
<*> fromSQLValue d <*> fromSQLValue d
<*> fromSQLValue e <*> fromSQLValue e
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 5." 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 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) = 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. -- | A row with 6 fields.
data Row6 a b c d e f = Row6 a b c d e f data Row6 a b c d e f = Row6 a b c d e f
@ -195,11 +207,13 @@ instance fromSQLRowRow6 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, From
<*> fromSQLValue e <*> fromSQLValue e
<*> fromSQLValue f <*> fromSQLValue f
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 6." 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 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) = 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. -- | A row with 7 fields.
data Row7 a b c d e f g = Row7 a b c d e f g data Row7 a b c d e f g = Row7 a b c d e f g
@ -222,11 +236,13 @@ instance fromSQLRowRow7 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, From
<*> fromSQLValue f <*> fromSQLValue f
<*> fromSQLValue g <*> fromSQLValue g
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 7." 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 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) = 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. -- | A row with 8 fields.
data Row8 a b c d e f g h = Row8 a b c d e f g h data Row8 a b c d e f g h = Row8 a b c d e f g h
@ -250,11 +266,13 @@ instance fromSQLRowRow8 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, From
<*> fromSQLValue g <*> fromSQLValue g
<*> fromSQLValue h <*> fromSQLValue h
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 8." 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 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) = 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. -- | 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 data Row9 a b c d e f g h i = Row9 a b c d e f g h i
@ -279,11 +297,13 @@ instance fromSQLRowRow9 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, From
<*> fromSQLValue h <*> fromSQLValue h
<*> fromSQLValue i <*> fromSQLValue i
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 9." 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 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) = 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. -- | 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 data Row10 a b c d e f g h i j = Row10 a b c d e f g h i j
@ -309,11 +329,13 @@ instance fromSQLRowRow10 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue i <*> fromSQLValue i
<*> fromSQLValue j <*> fromSQLValue j
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 10." 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 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) = 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. -- | 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 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
@ -340,11 +362,13 @@ instance fromSQLRowRow11 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue j <*> fromSQLValue j
<*> fromSQLValue k <*> fromSQLValue k
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 11." 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 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) = 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. -- | 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 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
@ -372,11 +396,13 @@ instance fromSQLRowRow12 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue k <*> fromSQLValue k
<*> fromSQLValue l <*> fromSQLValue l
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 12." 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 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) = 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. -- | 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 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
@ -405,11 +431,13 @@ instance fromSQLRowRow13 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue l <*> fromSQLValue l
<*> fromSQLValue m <*> fromSQLValue m
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 13." 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 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) = 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. -- | 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 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
@ -439,11 +467,13 @@ instance fromSQLRowRow14 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue m <*> fromSQLValue m
<*> fromSQLValue n <*> fromSQLValue n
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 14." 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 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) = 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. -- | 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 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
@ -474,11 +504,13 @@ instance fromSQLRowRow15 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue n <*> fromSQLValue n
<*> fromSQLValue o <*> fromSQLValue o
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 15." 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 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) = 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. -- | 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 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
@ -510,11 +542,13 @@ instance fromSQLRowRow16 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue o <*> fromSQLValue o
<*> fromSQLValue p <*> fromSQLValue p
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 16." 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 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) = 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. -- | 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 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
@ -547,11 +581,13 @@ instance fromSQLRowRow17 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue p <*> fromSQLValue p
<*> fromSQLValue q <*> fromSQLValue q
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 17." 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 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) = 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. -- | 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 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
@ -585,11 +621,13 @@ instance fromSQLRowRow18 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue q <*> fromSQLValue q
<*> fromSQLValue r <*> fromSQLValue r
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 18." 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 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) = 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. -- | 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 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
@ -624,7 +662,8 @@ instance fromSQLRowRow19 :: (FromSQLValue a, FromSQLValue b, FromSQLValue c, Fro
<*> fromSQLValue r <*> fromSQLValue r
<*> fromSQLValue s <*> fromSQLValue s
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 19." 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 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) = toSQLRow (Row19 a b c d e f g h i j k l m n o p q r s) =

View File

@ -93,20 +93,22 @@ else instance fromSQLValueJSDate :: FromSQLValue JSDate where
fromSQLValue = Right <<< unsafeFromForeign fromSQLValue = Right <<< unsafeFromForeign
else instance fromSQLValueMaybe :: (FromSQLValue a) => FromSQLValue (Maybe a) where else instance fromSQLValueMaybe :: (FromSQLValue a) => FromSQLValue (Maybe a) where
fromSQLValue x | isNull x = pure Nothing fromSQLValue x
| isNull x = pure Nothing
| otherwise = Just <$> fromSQLValue x | otherwise = Just <$> fromSQLValue x
else instance fromSQLValueForeign :: FromSQLValue Foreign where 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 fromSQLValue sql = lmap showErr $ unwrap $ runExceptT main
where where
showErr MultipleErrors String showErr :: MultipleErrors -> String
showErr e = foldl (\a x a <> renderForeignError x <> " ") "" e showErr e = foldl (\a x -> a <> renderForeignError x <> " ") "" e
main ExceptT MultipleErrors Identity (Object a)
main :: ExceptT MultipleErrors Identity (Object a)
main = do main = do
objF Object Foreign <- readObject sql objF :: Object Foreign <- readObject sql
let eso = sequence $ map fromSQLValue objF let eso = sequence $ map fromSQLValue objF
let emo = lmap (singleton <<< ForeignError) eso let emo = lmap (singleton <<< ForeignError) eso
except emo except emo
@ -119,7 +121,7 @@ else instance fromSQLValueDecimal :: FromSQLValue Decimal where
else instance fromSQLValueJson :: FromSQLValue Json where else instance fromSQLValueJson :: FromSQLValue Json where
fromSQLValue = Right <<< unsafeFromForeign 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 newtypeFromSQLValue = map wrap <<< fromSQLValue
instance toSQLValueBoolean :: ToSQLValue Boolean where instance toSQLValueBoolean :: ToSQLValue Boolean where
@ -168,7 +170,7 @@ else instance toSQLValueMaybe :: (ToSQLValue a) => ToSQLValue (Maybe a) where
else instance toSQLValueForeign :: ToSQLValue Foreign where 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 toSQLValue = unsafeToForeign
else instance toSQLValueDecimal :: ToSQLValue Decimal where else instance toSQLValueDecimal :: ToSQLValue Decimal where
@ -180,7 +182,7 @@ else instance toSQLValueJson :: ToSQLValue Json where
-- | https://github.com/brianc/node-postgres/issues/1383 -- | https://github.com/brianc/node-postgres/issues/1383
toSQLValue = Argonaut.stringify >>> unsafeToForeign 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 newtypeToSQLValue = unwrap >>> toSQLValue
null :: Foreign null :: Foreign
@ -189,4 +191,4 @@ null = null_
foreign import null_ :: Foreign foreign import null_ :: Foreign
foreign import instantToString :: Instant -> Foreign foreign import instantToString :: Instant -> Foreign
foreign import instantFromString :: (String -> Either String Number) -> (Number -> Either String Number) -> Foreign -> Either String Number 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