Remove tuple machinery in favour of row types

These are more efficient and provide better error messages.
This commit is contained in:
rightfold 2017-06-03 13:10:15 +02:00
parent 64c84351ec
commit c1f9391701
No known key found for this signature in database
GPG Key ID: 199D0373AC917A8F
9 changed files with 856 additions and 134 deletions

13
Makefile Normal file
View File

@ -0,0 +1,13 @@
all: build test
.PHONY: build
build: src/Database/PostgreSQL/Row.purs
pulp build
.PHONY: test
test: src/Database/PostgreSQL/Row.purs
pulp test
src/Database/PostgreSQL/Row.purs: Rows.pl
mkdir -p $(dir $@)
perl Rows.pl $@

121
Rows.pl Normal file
View File

@ -0,0 +1,121 @@
use strict;
use warnings;
sub vars {
my @as;
for (my $a = 'a', my $i = 0; $i < $_; ++$a, ++$i) {
push @as, $a;
}
@as
}
if (@ARGV != 1) {
die 'Usage: perl Rows.perl src/Database/PostgreSQL/Row.purs';
}
open my $out, '>', $ARGV[0]
or die $!;
print $out <<'EOF';
module Database.PostgreSQL.Row where
import Data.Array as Array
import Data.Either (Either(..))
import Data.Foreign (Foreign)
import Database.PostgreSQL.Value (class FromSQLValue, class ToSQLValue, fromSQLValue, toSQLValue)
import Prelude
-- | Convert things to SQL rows.
class ToSQLRow a where
toSQLRow :: a -> Array Foreign
-- | Convert things from SQL rows.
class FromSQLRow a where
fromSQLRow :: Array Foreign -> Either String a
EOF
for (0 .. 19) {
print $out "\n";
print $out "-- | A row with $_ field" . ($_ == 1 ? '' : 's') . ".\n";
print $out "data Row$_";
print $out map { " $_" } vars($_);
print $out " = Row$_";
print $out map { " $_" } vars($_);
print $out "\n\n";
if ($_ == 0) {
print $out "derive instance eqRow$_ :: Eq Row$_";
} else {
print $out "derive instance eqRow$_ :: (";
print $out join(', ', map { "Eq $_" } vars($_));
print $out ") => Eq (Row$_" . join('', map { " $_" } vars($_)) . ")";
}
print $out "\n\n";
if ($_ == 0) {
print $out "derive instance ordRow$_ :: Ord Row$_";
} else {
print $out "derive instance ordRow$_ :: (";
print $out join(', ', map { "Ord $_" } vars($_));
print $out ") => Ord (Row$_" . join('', map { " $_" } vars($_)) . ")";
}
print $out "\n\n";
if ($_ == 0) {
print $out "instance showRow$_ :: Show Row$_";
} else {
print $out "instance showRow$_ :: (";
print $out join(', ', map { "Show $_" } vars($_));
print $out ") => Show (Row$_" . join('', map { " $_" } vars($_)) . ')';
}
print $out " where\n";
if ($_ == 0) {
print $out " show Row$_ =\n";
print $out " \"Row$_\"";
} else {
print $out " show (Row$_" . join('', map { " $_" } vars($_)) . ") = \n";
print $out " \"(Row$_ \" <> ";
print $out join(' <> " " <> ', map { "show $_" } vars($_));
print $out " <> \")\"";
}
print $out "\n\n";
if ($_ == 0) {
print $out "instance fromSQLRowRow$_ :: FromSQLRow Row$_";
} else {
print $out "instance fromSQLRowRow$_ :: (";
print $out join(', ', map { "FromSQLValue $_" } vars($_));
print $out ") => FromSQLRow (Row$_" . join('', map { " $_" } vars($_)) . ')';
}
print $out " where\n";
print $out ' fromSQLRow [' . join(', ', vars($_)) . "] =\n";
print $out " pure Row$_\n";
for (vars($_)) {
print $out " <*> fromSQLValue $_\n";
}
print $out ' fromSQLRow xs = Left $ "Row has " <> show n <> " fields,';
print $out " expecting $_.\"\n";
print $out ' where n = Array.length xs';
print $out "\n\n";
if ($_ == 0) {
print $out "instance toSQLRowRow$_ :: ToSQLRow Row$_";
} else {
print $out "instance toSQLRowRow$_ :: (";
print $out join(', ', map { "ToSQLValue $_" } vars($_));
print $out ") => ToSQLRow (Row$_" . join('', map { " $_" } vars($_)) . ')';
}
print $out " where\n";
if ($_ == 0) {
print $out " toSQLRow Row$_ = []";
} else {
print $out " toSQLRow (Row$_" . join('', map { " $_" } vars($_)) . ") = \n";
print $out ' [' . join(', ', map { "toSQLValue $_" } vars($_)) . ']';
}
}

View File

@ -6,15 +6,17 @@
"purescript-transformers": "^3.1.0",
"purescript-lists": "^4.0.1",
"purescript-foreign": "^4.0.0",
"purescript-tuples": "^4.0.0",
"purescript-aff": "^3.0.0",
"purescript-either": "^3.0.0",
"purescript-maybe": "^3.0.0",
"purescript-foldable-traversable": "^3.0.0",
"purescript-newtype": "^2.0.0",
"purescript-bytestrings": "^3.0.1",
"purescript-bytestrings": "^5.0.1",
"purescript-arrays": "^4.0.1",
"purescript-datetime": "^3.0.0"
"purescript-datetime": "^3.0.0",
"purescript-bifunctors": "^3.0.0",
"purescript-eff": "^3.1.0",
"purescript-exceptions": "^3.0.0"
},
"repository": {
"type": "git",

View File

@ -51,13 +51,3 @@ exports._query = function(client) {
};
};
};
exports.instantToString = function(i) {
return new Date(i).toUTCString();
};
exports.unsafeIsBuffer = function(x) {
return x instanceof Buffer;
};
exports['null'] = null;

View File

@ -1,17 +1,11 @@
module Database.PostgreSQL
( POSTGRESQL
( module Row
, module Value
, POSTGRESQL
, PoolConfiguration
, Pool
, Connection
, Query(..)
, class ToSQLRow
, class FromSQLRow
, class ToSQLValue
, class FromSQLValue
, toSQLRow
, fromSQLRow
, toSQLValue
, fromSQLValue
, newPool
, withConnection
, withTransaction
@ -24,20 +18,16 @@ import Control.Monad.Aff (Aff)
import Control.Monad.Eff (kind Effect)
import Control.Monad.Eff.Exception (error)
import Control.Monad.Error.Class (catchError, throwError)
import Control.Monad.Except (runExcept)
import Data.Array (head, uncons)
import Data.Bifunctor (lmap)
import Data.ByteString (ByteString)
import Data.DateTime.Instant (Instant)
import Data.Array (head)
import Data.Either (Either(..))
import Data.Foreign (Foreign, isNull, readArray, readBoolean, readChar, readInt, readNumber, readString, toForeign, unsafeFromForeign)
import Data.List (List)
import Data.List as List
import Data.Foreign (Foreign)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Traversable (traverse)
import Data.Tuple (fst, Tuple)
import Data.Tuple.Nested ((/\))
import Database.PostgreSQL.Row (class FromSQLRow, class ToSQLRow, Row0(..), Row1(..), fromSQLRow, toSQLRow)
import Database.PostgreSQL.Row as Row
import Database.PostgreSQL.Value (class FromSQLValue)
import Database.PostgreSQL.Value as Value
import Prelude
foreign import data POSTGRESQL :: Effect
@ -53,8 +43,6 @@ type PoolConfiguration =
, idleTimeoutMillis :: Int
}
foreign import null :: Foreign
-- | PostgreSQL connection pool.
foreign import data Pool :: Type
@ -66,95 +54,6 @@ newtype Query i o = Query String
derive instance newtypeQuery :: Newtype (Query i o) _
-- | Convert things to SQL rows.
class ToSQLRow a where
toSQLRow :: a -> Array Foreign
-- | Convert things from SQL rows.
class FromSQLRow a where
fromSQLRow :: Array Foreign -> Either String a
-- | Convert things to SQL values.
class ToSQLValue a where
toSQLValue :: a -> Foreign
-- | Convert things from SQL values.
class FromSQLValue a where
fromSQLValue :: Foreign -> Either String a
instance toSQLRowUnit :: ToSQLRow Unit where
toSQLRow _ = []
instance toSQLRowTuple :: (ToSQLValue a, ToSQLRow b) => ToSQLRow (Tuple a b) where
toSQLRow (a /\ b) = [toSQLValue a] <> toSQLRow b
instance fromSQLRowUnit :: FromSQLRow Unit where
fromSQLRow [] = pure unit
fromSQLRow _ = throwError "FromSQLRow: row has too many columns"
instance fromSQLRowTuple :: (FromSQLValue a, FromSQLRow b) => FromSQLRow (Tuple a b) where
fromSQLRow = uncons >>> case _ of
Just {head, tail} -> (/\) <$> fromSQLValue head <*> fromSQLRow tail
Nothing -> throwError "FromSQLRow: row has too few columns"
instance toSQLValueBoolean :: ToSQLValue Boolean where
toSQLValue = toForeign
instance fromSQLValueBoolean :: FromSQLValue Boolean where
fromSQLValue = lmap show <<< runExcept <<< readBoolean
instance toSQLValueChar :: ToSQLValue Char where
toSQLValue = toForeign
instance fromSQLValueChar :: FromSQLValue Char where
fromSQLValue = lmap show <<< runExcept <<< readChar
instance toSQLValueInt :: ToSQLValue Int where
toSQLValue = toForeign
instance fromSQLValueInt :: FromSQLValue Int where
fromSQLValue = lmap show <<< runExcept <<< readInt
instance toSQLValueNumber :: ToSQLValue Number where
toSQLValue = toForeign
instance fromSQLValueNumber :: FromSQLValue Number where
fromSQLValue = lmap show <<< runExcept <<< readNumber
instance toSQLValueString :: ToSQLValue String where
toSQLValue = toForeign
instance fromSQLValueString :: FromSQLValue String where
fromSQLValue = lmap show <<< runExcept <<< readString
instance fromSQLValueArray :: (FromSQLValue a) => FromSQLValue (Array a) where
fromSQLValue = traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
instance fromSQLValueList :: (FromSQLValue a) => FromSQLValue (List a) where
fromSQLValue = map List.fromFoldable <<< traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
instance toSQLValueByteString :: ToSQLValue ByteString where
toSQLValue = toForeign
instance fromSQLValueByteString :: FromSQLValue ByteString where
fromSQLValue x
| unsafeIsBuffer x = pure $ unsafeFromForeign x
| otherwise = throwError "FromSQLValue ByteString: not a buffer"
instance toSQLValueInstant :: ToSQLValue Instant where
toSQLValue = instantToString
instance toSQLValueMaybe :: (ToSQLValue a) => ToSQLValue (Maybe a) where
toSQLValue Nothing = null
toSQLValue (Just x) = toSQLValue x
instance fromSQLValueMaybe :: (FromSQLValue a) => FromSQLValue (Maybe a) where
fromSQLValue x | isNull x = pure Nothing
| otherwise = Just <$> fromSQLValue x
foreign import instantToString :: Instant -> Foreign
foreign import unsafeIsBuffer :: a. a -> Boolean
-- | Create a new connection pool.
foreign import newPool
:: eff
@ -179,10 +78,10 @@ withTransaction
-> Aff (postgreSQL :: POSTGRESQL | eff) a
-> Aff (postgreSQL :: POSTGRESQL | eff) a
withTransaction conn action =
execute conn (Query "BEGIN TRANSACTION") unit
execute conn (Query "BEGIN TRANSACTION") Row0
*> catchError (Right <$> action) (pure <<< Left) >>= case _ of
Right a -> execute conn (Query "COMMIT TRANSACTION") unit $> a
Left e -> execute conn (Query "ROLLBACK TRANSACTION") unit *> throwError e
Right a -> execute conn (Query "COMMIT TRANSACTION") Row0 $> a
Left e -> execute conn (Query "ROLLBACK TRANSACTION") Row0 *> throwError e
-- | Execute a PostgreSQL query and discard its results.
execute
@ -215,12 +114,12 @@ scalar
. ToSQLRow i
=> FromSQLValue o
=> Connection
-> Query i (Tuple o Unit)
-> Query i (Row1 o)
-> i
-> Aff (postgreSQL :: POSTGRESQL | eff) (Maybe o)
scalar conn sql values =
query conn sql values
<#> map fst <<< head
<#> map (case _ of Row1 a -> a) <<< head
foreign import _query
:: eff

View File

@ -0,0 +1,605 @@
module Database.PostgreSQL.Row where
import Data.Array as Array
import Data.Either (Either(..))
import Data.Foreign (Foreign)
import Database.PostgreSQL.Value (class FromSQLValue, class ToSQLValue, fromSQLValue, toSQLValue)
import Prelude
-- | Convert things to SQL rows.
class ToSQLRow a where
toSQLRow :: a -> Array Foreign
-- | Convert things from SQL rows.
class FromSQLRow a where
fromSQLRow :: Array Foreign -> Either String a
-- | A row with 0 fields.
data Row0 = Row0
derive instance eqRow0 :: Eq Row0
derive instance ordRow0 :: Ord Row0
instance showRow0 :: Show Row0 where
show Row0 =
"Row0"
instance fromSQLRowRow0 :: FromSQLRow Row0 where
fromSQLRow [] =
pure Row0
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 0."
where n = Array.length xs
instance toSQLRowRow0 :: ToSQLRow Row0 where
toSQLRow Row0 = []
-- | A row with 1 field.
data Row1 a = Row1 a
derive instance eqRow1 :: (Eq a) => Eq (Row1 a)
derive instance ordRow1 :: (Ord a) => Ord (Row1 a)
instance showRow1 :: (Show a) => Show (Row1 a) where
show (Row1 a) =
"(Row1 " <> show a <> ")"
instance fromSQLRowRow1 :: (FromSQLValue a) => FromSQLRow (Row1 a) where
fromSQLRow [a] =
pure Row1
<*> fromSQLValue a
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 1."
where n = Array.length xs
instance toSQLRowRow1 :: (ToSQLValue a) => ToSQLRow (Row1 a) where
toSQLRow (Row1 a) =
[toSQLValue a]
-- | A row with 2 fields.
data Row2 a b = Row2 a b
derive instance eqRow2 :: (Eq a, Eq b) => Eq (Row2 a b)
derive instance ordRow2 :: (Ord a, Ord b) => Ord (Row2 a b)
instance showRow2 :: (Show a, Show b) => Show (Row2 a b) where
show (Row2 a b) =
"(Row2 " <> show a <> " " <> show b <> ")"
instance fromSQLRowRow2 :: (FromSQLValue a, FromSQLValue b) => FromSQLRow (Row2 a b) where
fromSQLRow [a, b] =
pure Row2
<*> fromSQLValue a
<*> fromSQLValue b
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 2."
where n = Array.length xs
instance toSQLRowRow2 :: (ToSQLValue a, ToSQLValue b) => ToSQLRow (Row2 a b) where
toSQLRow (Row2 a b) =
[toSQLValue a, toSQLValue b]
-- | A row with 3 fields.
data Row3 a b c = Row3 a b c
derive instance eqRow3 :: (Eq a, Eq b, Eq c) => Eq (Row3 a b c)
derive instance ordRow3 :: (Ord a, Ord b, Ord c) => Ord (Row3 a b c)
instance showRow3 :: (Show a, Show b, Show c) => Show (Row3 a b c) where
show (Row3 a b c) =
"(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] =
pure Row3
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 3."
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]
-- | A row with 4 fields.
data Row4 a b c d = Row4 a b c d
derive instance eqRow4 :: (Eq a, Eq b, Eq c, Eq d) => Eq (Row4 a b c d)
derive instance ordRow4 :: (Ord a, Ord b, Ord c, Ord d) => Ord (Row4 a b c d)
instance showRow4 :: (Show a, Show b, Show c, Show d) => Show (Row4 a b c d) where
show (Row4 a b c d) =
"(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] =
pure Row4
<*> fromSQLValue a
<*> fromSQLValue b
<*> fromSQLValue c
<*> fromSQLValue d
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 4."
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]
-- | A row with 5 fields.
data Row5 a b c d e = Row5 a b c d e
derive instance eqRow5 :: (Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (Row5 a b c d e)
derive instance ordRow5 :: (Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (Row5 a b c d e)
instance showRow5 :: (Show a, Show b, Show c, Show d, Show e) => Show (Row5 a b c d e) where
show (Row5 a b c d e) =
"(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] =
pure Row5
<*> 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
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]
-- | A row with 6 fields.
data Row6 a b c d e f = Row6 a b c d e f
derive instance eqRow6 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (Row6 a b c d e f)
derive instance ordRow6 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (Row6 a b c d e f)
instance showRow6 :: (Show a, Show b, Show c, Show d, Show e, Show f) => Show (Row6 a b c d e f) where
show (Row6 a b c d e f) =
"(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] =
pure Row6
<*> 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
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]
-- | A row with 7 fields.
data Row7 a b c d e f g = Row7 a b c d e f g
derive instance eqRow7 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (Row7 a b c d e f g)
derive instance ordRow7 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (Row7 a b c d e f g)
instance showRow7 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (Row7 a b c d e f g) where
show (Row7 a b c d e f 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] =
pure Row7
<*> 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
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]
-- | A row with 8 fields.
data Row8 a b c d e f g h = Row8 a b c d e f g h
derive instance eqRow8 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (Row8 a b c d e f g h)
derive instance ordRow8 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (Row8 a b c d e f g h)
instance showRow8 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (Row8 a b c d e f g h) where
show (Row8 a b c d e f g h) =
"(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] =
pure Row8
<*> 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
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]
-- | 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
derive instance eqRow9 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (Row9 a b c d e f g h i)
derive instance ordRow9 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (Row9 a b c d e f g h i)
instance showRow9 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (Row9 a b c d e f g h i) where
show (Row9 a b c d e f g h i) =
"(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] =
pure Row9
<*> 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
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]
-- | 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
derive instance eqRow10 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (Row10 a b c d e f g h i j)
derive instance ordRow10 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (Row10 a b c d e f g h i j)
instance showRow10 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (Row10 a b c d e f g h i j) where
show (Row10 a b c d e f g h i j) =
"(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] =
pure Row10
<*> 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
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]
-- | 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
derive instance eqRow11 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (Row11 a b c d e f g h i j k)
derive instance ordRow11 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (Row11 a b c d e f g h i j k)
instance showRow11 :: (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (Row11 a b c d e f g h i j k) where
show (Row11 a b c d e f g h i j k) =
"(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] =
pure Row11
<*> 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
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]
-- | 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
derive instance eqRow12 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (Row12 a b c d e f g h i j k l)
derive instance ordRow12 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (Row12 a b c d e f g h i j k l)
instance showRow12 :: (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 (Row12 a b c d e f g h i j k l) where
show (Row12 a b c d e f g h i j k l) =
"(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] =
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
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 12."
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]
-- | 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
derive instance eqRow13 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (Row13 a b c d e f g h i j k l m)
derive instance ordRow13 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (Row13 a b c d e f g h i j k l m)
instance showRow13 :: (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 (Row13 a b c d e f g h i j k l m) where
show (Row13 a b c d e f g h i j k l m) =
"(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] =
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
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 13."
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]
-- | 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
derive instance eqRow14 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (Row14 a b c d e f g h i j k l m n)
derive instance ordRow14 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (Row14 a b c d e f g h i j k l m n)
instance showRow14 :: (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 (Row14 a b c d e f g h i j k l m n) where
show (Row14 a b c d e f g h i j k l m n) =
"(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] =
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
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 14."
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]
-- | 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
derive instance eqRow15 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (Row15 a b c d e f g h i j k l m n o)
derive instance ordRow15 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (Row15 a b c d e f g h i j k l m n o)
instance showRow15 :: (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 (Row15 a b c d e f g h i j k l m n o) where
show (Row15 a b c d e f g h i j k l m n o) =
"(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] =
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
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 15."
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]
-- | 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
derive instance eqRow16 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p) => Eq (Row16 a b c d e f g h i j k l m n o p)
derive instance ordRow16 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o, Ord p) => Ord (Row16 a b c d e f g h i j k l m n o p)
instance showRow16 :: (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 (Row16 a b c d e f g h i j k l m n o p) where
show (Row16 a b c d e f g h i j k l m n o p) =
"(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] =
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
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 16."
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]
-- | 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
derive instance eqRow17 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p, Eq q) => Eq (Row17 a b c d e f g h i j k l m n o p q)
derive instance ordRow17 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o, Ord p, Ord q) => Ord (Row17 a b c d e f g h i j k l m n o p q)
instance showRow17 :: (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 (Row17 a b c d e f g h i j k l m n o p q) where
show (Row17 a b c d e f g h i j k l m n o p q) =
"(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] =
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
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 17."
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]
-- | 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
derive instance eqRow18 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p, Eq q, Eq r) => Eq (Row18 a b c d e f g h i j k l m n o p q r)
derive instance ordRow18 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o, Ord p, Ord q, Ord r) => Ord (Row18 a b c d e f g h i j k l m n o p q r)
instance showRow18 :: (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 (Row18 a b c d e f g h i j k l m n o p q r) where
show (Row18 a b c d e f g h i j k l m n o p q r) =
"(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] =
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
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 18."
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]
-- | 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
derive instance eqRow19 :: (Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p, Eq q, Eq r, Eq s) => Eq (Row19 a b c d e f g h i j k l m n o p q r s)
derive instance ordRow19 :: (Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o, Ord p, Ord q, Ord r, Ord s) => Ord (Row19 a b c d e f g h i j k l m n o p q r s)
instance showRow19 :: (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) => Show (Row19 a b c d e f g h i j k l m n o p q r s) where
show (Row19 a b c d e f g h i j k l m n o p q r 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] =
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
fromSQLRow xs = Left $ "Row has " <> show n <> " fields, expecting 19."
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]

View File

@ -0,0 +1,11 @@
'use strict';
exports['null'] = null;
exports.instantToString = function(i) {
return new Date(i).toUTCString();
};
exports.unsafeIsBuffer = function(x) {
return x instanceof Buffer;
};

View File

@ -0,0 +1,82 @@
module Database.PostgreSQL.Value where
import Control.Monad.Eff (kind Effect)
import Control.Monad.Error.Class (throwError)
import Control.Monad.Except (runExcept)
import Data.Bifunctor (lmap)
import Data.ByteString (ByteString)
import Data.DateTime.Instant (Instant)
import Data.Either (Either)
import Data.Foreign (Foreign, isNull, readArray, readBoolean, readChar, readInt, readNumber, readString, toForeign, unsafeFromForeign)
import Data.List (List)
import Data.List as List
import Data.Maybe (Maybe(..))
import Data.Traversable (traverse)
import Prelude
-- | Convert things to SQL values.
class ToSQLValue a where
toSQLValue :: a -> Foreign
-- | Convert things from SQL values.
class FromSQLValue a where
fromSQLValue :: Foreign -> Either String a
instance toSQLValueBoolean :: ToSQLValue Boolean where
toSQLValue = toForeign
instance fromSQLValueBoolean :: FromSQLValue Boolean where
fromSQLValue = lmap show <<< runExcept <<< readBoolean
instance toSQLValueChar :: ToSQLValue Char where
toSQLValue = toForeign
instance fromSQLValueChar :: FromSQLValue Char where
fromSQLValue = lmap show <<< runExcept <<< readChar
instance toSQLValueInt :: ToSQLValue Int where
toSQLValue = toForeign
instance fromSQLValueInt :: FromSQLValue Int where
fromSQLValue = lmap show <<< runExcept <<< readInt
instance toSQLValueNumber :: ToSQLValue Number where
toSQLValue = toForeign
instance fromSQLValueNumber :: FromSQLValue Number where
fromSQLValue = lmap show <<< runExcept <<< readNumber
instance toSQLValueString :: ToSQLValue String where
toSQLValue = toForeign
instance fromSQLValueString :: FromSQLValue String where
fromSQLValue = lmap show <<< runExcept <<< readString
instance fromSQLValueArray :: (FromSQLValue a) => FromSQLValue (Array a) where
fromSQLValue = traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
instance fromSQLValueList :: (FromSQLValue a) => FromSQLValue (List a) where
fromSQLValue = map List.fromFoldable <<< traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
instance toSQLValueByteString :: ToSQLValue ByteString where
toSQLValue = toForeign
instance fromSQLValueByteString :: FromSQLValue ByteString where
fromSQLValue x
| unsafeIsBuffer x = pure $ unsafeFromForeign x
| otherwise = throwError "FromSQLValue ByteString: not a buffer"
instance toSQLValueInstant :: ToSQLValue Instant where
toSQLValue = instantToString
instance toSQLValueMaybe :: (ToSQLValue a) => ToSQLValue (Maybe a) where
toSQLValue Nothing = null
toSQLValue (Just x) = toSQLValue x
instance fromSQLValueMaybe :: (FromSQLValue a) => FromSQLValue (Maybe a) where
fromSQLValue x | isNull x = pure Nothing
| otherwise = Just <$> fromSQLValue x
foreign import null :: Foreign
foreign import instantToString :: Instant -> Foreign
foreign import unsafeIsBuffer :: a. a -> Boolean

View File

@ -6,8 +6,7 @@ import Control.Monad.Aff (launchAff)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Exception (EXCEPTION)
import Data.Tuple.Nested ((/\))
import Database.PostgreSQL (POSTGRESQL, PoolConfiguration, Query(..), execute, newPool, query, withConnection)
import Database.PostgreSQL (POSTGRESQL, PoolConfiguration, Query(..), Row0(..), Row1(..), Row6(..), execute, newPool, query, withConnection)
import Prelude
import Test.Assert (ASSERT, assert)
@ -21,20 +20,20 @@ main = void $ launchAff do
delicious boolean NOT NULL,
PRIMARY KEY (name)
)
""") unit
""") Row0
execute conn (Query """
INSERT INTO foods (name, delicious)
VALUES ($1, $2), ($3, $4), ($5, $6)
""") ("pork" /\ true /\ "sauerkraut" /\ false /\ "rookworst" /\ true /\ unit)
""") (Row6 "pork" true "sauerkraut" false "rookworst" true)
query conn (Query """
SELECT name
FROM foods
WHERE delicious
ORDER BY name ASC
""") unit
>>= liftEff <<< assert <<< (==) ["pork" /\ unit, "rookworst" /\ unit]
""") Row0
>>= liftEff <<< assert <<< (==) [Row1 "pork", Row1 "rookworst"]
pure unit