Migrate to Purescript 0.12.

This commit is contained in:
adamczykm 2018-07-15 19:51:17 +02:00
parent bceb1e399d
commit bead426f14
5 changed files with 113 additions and 122 deletions

View File

@ -2,32 +2,32 @@
"name": "purescript-postgresql-client",
"license": "BSD-3-Clause",
"dependencies": {
"purescript-prelude": "^3.0.0",
"purescript-transformers": "^3.2.0",
"purescript-lists": "^4.0.1",
"purescript-foreign": "^4.0.0",
"purescript-aff": "^4.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": "^5.0.1",
"purescript-arrays": "^4.0.1",
"purescript-datetime": "^3.0.0",
"purescript-bifunctors": "^3.0.0",
"purescript-eff": "^3.1.0",
"purescript-exceptions": "^3.0.0",
"purescript-decimals": "^3.4.0",
"purescript-js-date": "^5.2.0"
"purescript-prelude": "^4.0.1",
"purescript-transformers": "^4.1.0",
"purescript-lists": "^5.0.0",
"purescript-foreign": "^5.0.0",
"purescript-aff": "^5.0.1",
"purescript-either": "^4.0.0",
"purescript-maybe": "^4.0.0",
"purescript-foldable-traversable": "^4.0.0",
"purescript-newtype": "^3.0.0",
"purescript-bytestrings": "adamczykm/purescript-bytestrings#7.0.0",
"purescript-arrays": "^5.0.0",
"purescript-datetime": "^4.0.0",
"purescript-bifunctors": "^4.0.0",
"purescript-effect": "^2.0.0",
"purescript-exceptions": "^4.0.0",
"purescript-decimals": "^4.0.0",
"purescript-js-date": "^6.0.0"
},
"repository": {
"type": "git",
"url": "https://github.com/rightfold/purescript-postgresql-client.git"
},
"devDependencies": {
"purescript-assert": "^3.0.0",
"purescript-eff": "^3.1.0",
"purescript-debug": "^3.0.0",
"purescript-test-unit": "^13.0.0"
"purescript-assert": "^4.0.0",
"purescript-effect": "^2.0.0",
"purescript-debug": "^4.0.0",
"purescript-test-unit": "^14.0.0"
}
}

View File

@ -1,7 +1,10 @@
{
"name": "purescript-postgresql-client",
"dependencies": {
"bower-dependency-tree": "^0.1.2",
"decimal.js": "^10.0.0",
"g": "^2.0.1",
"global": "^4.3.2",
"pg": "^6.1.2"
}
}

View File

@ -1,7 +1,6 @@
module Database.PostgreSQL
( module Row
, module Value
, POSTGRESQL
, PoolConfiguration
, Pool
, Connection
@ -17,24 +16,23 @@ module Database.PostgreSQL
import Prelude
import Control.Monad.Aff (Aff, bracket)
import Control.Monad.Aff.Compat (EffFnAff, fromEffFnAff)
import Control.Monad.Eff (kind Effect, Eff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Exception (error)
import Effect.Aff (Aff, bracket)
import Effect.Aff.Compat (EffectFnAff, fromEffectFnAff)
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Control.Monad.Error.Class (catchError, throwError)
import Data.Array (head)
import Data.Either (Either(..))
import Data.Foreign (Foreign)
import Foreign (Foreign)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Traversable (traverse)
import Database.PostgreSQL.Row (class FromSQLRow, class ToSQLRow, Row0(..), Row1(..), fromSQLRow, toSQLRow)
import Database.PostgreSQL.Row as Row
import Database.PostgreSQL.Row (class FromSQLRow, class ToSQLRow, Row0(..), Row1(..), Row10(..), Row11(..), Row12(..), Row13(..), Row14(..), Row15(..), Row16(..), Row17(..), Row18(..), Row19(..), Row2(..), Row3(..), Row4(..), Row5(..), Row6(..), Row7(..), Row8(..), Row9(..), fromSQLRow, toSQLRow) as Row
import Database.PostgreSQL.Value (class FromSQLValue)
import Database.PostgreSQL.Value as Value
import Database.PostgreSQL.Value (class FromSQLValue, class ToSQLValue, fromSQLValue, instantFromString, instantToString, null, toSQLValue, unsafeIsBuffer) as Value
foreign import data POSTGRESQL :: Effect
-- | PostgreSQL connection pool configuration.
type PoolConfiguration =
@ -59,46 +57,39 @@ newtype Query i o = Query String
derive instance newtypeQuery :: Newtype (Query i o) _
-- | Create a new connection pool.
newPool :: eff. PoolConfiguration -> Aff (postgreSQL :: POSTGRESQL | eff) Pool
newPool = liftEff <<< ffiNewPool
newPool :: PoolConfiguration -> Aff Pool
newPool = liftEffect <<< ffiNewPool
foreign import ffiNewPool
:: eff
. PoolConfiguration
-> Eff (postgreSQL :: POSTGRESQL | eff) Pool
:: PoolConfiguration
-> Effect Pool
-- | Run an action with a connection. The connection is released to the pool
-- | when the action returns.
withConnection
:: eff a
:: a
. Pool
-> (Connection -> Aff (postgreSQL :: POSTGRESQL | eff) a)
-> Aff (postgreSQL :: POSTGRESQL | eff) a
-> (Connection -> Aff a)
-> Aff a
withConnection p k =
bracket
(connect p)
(liftEff <<< _.done)
(liftEffect <<< _.done)
(k <<< _.connection)
type PostgreSqlEff eff = (postgreSQL :: POSTGRESQL | eff)
connect
:: eff
. Pool
:: Pool
-> Aff
(postgreSQL :: POSTGRESQL | eff)
{ connection :: Connection
, done :: Eff (PostgreSqlEff eff) Unit
, done :: Effect Unit
}
connect = fromEffFnAff <<< ffiConnect
connect = fromEffectFnAff <<< ffiConnect
foreign import ffiConnect
:: eff
. Pool
-> EffFnAff
(PostgreSqlEff eff)
:: Pool
-> EffectFnAff
{ connection :: Connection
, done :: Eff (PostgreSqlEff eff) Unit
, done :: Effect Unit
}
-- | Run an action within a transaction. The transaction is committed if the
@ -106,10 +97,10 @@ foreign import ffiConnect
-- | change the transaction mode, issue a separate `SET TRANSACTION` statement
-- | within the transaction.
withTransaction
:: eff a
:: a
. Connection
-> Aff (postgreSQL :: POSTGRESQL | eff) a
-> Aff (postgreSQL :: POSTGRESQL | eff) a
-> Aff a
-> Aff a
withTransaction conn action =
execute conn (Query "BEGIN TRANSACTION") Row0
*> catchError (Right <$> action) (pure <<< Left) >>= case _ of
@ -118,24 +109,24 @@ withTransaction conn action =
-- | Execute a PostgreSQL query and discard its results.
execute
:: i o eff
:: i o
. (ToSQLRow i)
=> Connection
-> Query i o
-> i
-> Aff (postgreSQL :: POSTGRESQL | eff) Unit
-> Aff Unit
execute conn (Query sql) values =
void $ unsafeQuery conn sql (toSQLRow values)
-- | Execute a PostgreSQL query and return its results.
query
:: i o eff
:: i o
. ToSQLRow i
=> FromSQLRow o
=> Connection
-> Query i o
-> i
-> Aff (postgreSQL :: POSTGRESQL | eff) (Array o)
-> Aff (Array o)
query conn (Query sql) values =
unsafeQuery conn sql (toSQLRow values)
>>= traverse (fromSQLRow >>> case _ of
@ -145,31 +136,29 @@ query conn (Query sql) values =
-- | Execute a PostgreSQL query and return the first field of the first row in
-- | the result.
scalar
:: i o eff
:: i o
. ToSQLRow i
=> FromSQLValue o
=> Connection
-> Query i (Row1 o)
-> i
-> Aff (postgreSQL :: POSTGRESQL | eff) (Maybe o)
-> Aff (Maybe o)
scalar conn sql values =
query conn sql values
<#> map (case _ of Row1 a -> a) <<< head
unsafeQuery
:: eff
. Connection
:: Connection
-> String
-> Array Foreign
-> Aff (postgreSQL :: POSTGRESQL | eff) (Array (Array Foreign))
unsafeQuery c s = fromEffFnAff <<< ffiUnsafeQuery c s
-> Aff (Array (Array Foreign))
unsafeQuery c s = fromEffectFnAff <<< ffiUnsafeQuery c s
foreign import ffiUnsafeQuery
:: eff
. Connection
:: Connection
-> String
-> Array Foreign
-> EffFnAff (postgreSQL :: POSTGRESQL | eff) (Array (Array Foreign))
-> EffectFnAff (Array (Array Foreign))
fromRight :: a b. Either a b -> Maybe b
fromRight (Left _) = Nothing

View File

@ -2,7 +2,7 @@ module Database.PostgreSQL.Row where
import Data.Array as Array
import Data.Either (Either(..))
import Data.Foreign (Foreign)
import Foreign (Foreign)
import Database.PostgreSQL.Value (class FromSQLValue, class ToSQLValue, fromSQLValue, toSQLValue)
import Prelude
@ -15,7 +15,7 @@ class FromSQLRow a where
fromSQLRow :: Array Foreign -> Either String a
instance toSQLRowForeignArray :: ToSQLRow (Array Foreign) where
toSQLRow = id
toSQLRow = identity
-- | A row with 0 fields.
data Row0 = Row0

View File

@ -2,7 +2,6 @@ module Database.PostgreSQL.Value where
import Prelude
import Control.Monad.Eff (kind Effect)
import Control.Monad.Error.Class (throwError)
import Control.Monad.Except (runExcept)
import Data.Array as Array
@ -14,7 +13,7 @@ import Data.Decimal (Decimal)
import Data.Decimal as Decimal
import Data.Either (Either(..), note)
import Data.Enum (fromEnum, toEnum)
import Data.Foreign (Foreign, isNull, readArray, readBoolean, readChar, readInt, readNumber, readString, toForeign, unsafeFromForeign)
import Foreign (Foreign, isNull, readArray, readBoolean, readChar, readInt, readNumber, readString, unsafeToForeign, unsafeFromForeign)
import Data.Int (fromString)
import Data.List (List)
import Data.List as List
@ -32,49 +31,49 @@ class FromSQLValue a where
fromSQLValue :: Foreign -> Either String a
instance toSQLValueBoolean :: ToSQLValue Boolean where
toSQLValue = toForeign
toSQLValue = unsafeToForeign
instance fromSQLValueBoolean :: FromSQLValue Boolean where
fromSQLValue = lmap show <<< runExcept <<< readBoolean
instance toSQLValueChar :: ToSQLValue Char where
toSQLValue = toForeign
toSQLValue = unsafeToForeign
instance fromSQLValueChar :: FromSQLValue Char where
fromSQLValue = lmap show <<< runExcept <<< readChar
instance toSQLValueInt :: ToSQLValue Int where
toSQLValue = toForeign
toSQLValue = unsafeToForeign
instance fromSQLValueInt :: FromSQLValue Int where
fromSQLValue = lmap show <<< runExcept <<< readInt
instance toSQLValueNumber :: ToSQLValue Number where
toSQLValue = toForeign
toSQLValue = unsafeToForeign
instance fromSQLValueNumber :: FromSQLValue Number where
fromSQLValue = lmap show <<< runExcept <<< readNumber
instance toSQLValueString :: ToSQLValue String where
toSQLValue = toForeign
toSQLValue = unsafeToForeign
instance fromSQLValueString :: FromSQLValue String where
fromSQLValue = lmap show <<< runExcept <<< readString
instance toSQLValueArray :: (ToSQLValue a) => ToSQLValue (Array a) where
toSQLValue = toForeign <<< map toSQLValue
toSQLValue = unsafeToForeign <<< map toSQLValue
instance fromSQLValueArray :: (FromSQLValue a) => FromSQLValue (Array a) where
fromSQLValue = traverse fromSQLValue <=< lmap show <<< runExcept <<< readArray
instance toSQLValueList :: (ToSQLValue a) => ToSQLValue (List a) where
toSQLValue = toForeign <<< Array.fromFoldable <<< map toSQLValue
toSQLValue = unsafeToForeign <<< Array.fromFoldable <<< map toSQLValue
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
toSQLValue = unsafeToForeign
instance fromSQLValueByteString :: FromSQLValue ByteString where
fromSQLValue x
@ -96,7 +95,7 @@ instance toSQLValueDate :: ToSQLValue Date where
m = fromEnum $ month date
d = fromEnum $ day date
in
toForeign $ show y <> "-" <> show m <> "-" <> show d
unsafeToForeign $ show y <> "-" <> show m <> "-" <> show d
instance fromSQLValueDate :: FromSQLValue Date where
fromSQLValue v = do
@ -122,13 +121,13 @@ instance fromSQLValueMaybe :: (FromSQLValue a) => FromSQLValue (Maybe a) where
| otherwise = Just <$> fromSQLValue x
instance toSQLValueForeign :: ToSQLValue Foreign where
toSQLValue = id
toSQLValue = identity
instance fromSQLValueForeign :: FromSQLValue Foreign where
fromSQLValue = pure
instance toSQLValueDecimal :: ToSQLValue Decimal where
toSQLValue = Decimal.toString >>> toForeign
toSQLValue = Decimal.toString >>> unsafeToForeign
instance fromSQLValueDecimal :: FromSQLValue Decimal where
fromSQLValue v = do