{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
module Opaleye.Internal.Constant where
import Opaleye.Column (Column)
import qualified Opaleye.Column as C
import qualified Opaleye.SqlTypes as T
import qualified Data.Aeson as Ae
import qualified Data.CaseInsensitive as CI
import qualified Data.Int as Int
import qualified Data.Text as ST
import qualified Data.Text.Lazy as LT
import qualified Data.ByteString as SBS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Scientific as Sci
import qualified Data.Time as Time
import qualified Data.UUID as UUID
import qualified Data.Profunctor.Product as PP
import Data.Profunctor.Product (empty, (***!), (+++!))
import qualified Data.Profunctor.Product.Default as D
import qualified Data.Profunctor as P
import Control.Applicative (Applicative, pure, (<*>))
import Data.Functor ((<$>))
import qualified Database.PostgreSQL.Simple.Range as R
toFields :: D.Default ToFields haskells fields
=> haskells -> fields
toFields :: haskells -> fields
toFields = ToFields haskells fields -> haskells -> fields
forall haskells fields.
ToFields haskells fields -> haskells -> fields
constantExplicit ToFields haskells fields
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
{-# DEPRECATED constant "Use 'toFields' instead. Will be removed in version 0.8." #-}
constant :: D.Default ToFields haskells fields
=> haskells -> fields
constant :: haskells -> fields
constant = ToFields haskells fields -> haskells -> fields
forall haskells fields.
ToFields haskells fields -> haskells -> fields
constantExplicit ToFields haskells fields
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
newtype ToFields haskells fields =
ToFields { ToFields haskells fields -> haskells -> fields
constantExplicit :: haskells -> fields }
{-# DEPRECATED Constant "Use 'ToFields' instead. Will be removed in version 0.8." #-}
type Constant = ToFields
instance D.Default ToFields haskell (Column sql)
=> D.Default ToFields (Maybe haskell) (Column (C.Nullable sql)) where
def :: ToFields (Maybe haskell) (Column (Nullable sql))
def = (Maybe haskell -> Column (Nullable sql))
-> ToFields (Maybe haskell) (Column (Nullable sql))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields (Maybe (Column sql) -> Column (Nullable sql)
forall a. Maybe (Column a) -> Column (Nullable a)
C.maybeToNullable (Maybe (Column sql) -> Column (Nullable sql))
-> (Maybe haskell -> Maybe (Column sql))
-> Maybe haskell
-> Column (Nullable sql)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (haskell -> Column sql) -> Maybe haskell -> Maybe (Column sql)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap haskell -> Column sql
f)
where ToFields haskell -> Column sql
f = ToFields haskell (Column sql)
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def
toToFields :: (haskells -> fields) -> ToFields haskells fields
toToFields :: (haskells -> fields) -> ToFields haskells fields
toToFields = (haskells -> fields) -> ToFields haskells fields
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields
instance D.Default ToFields (Column a) (Column a) where
def :: ToFields (Column a) (Column a)
def = (Column a -> Column a) -> ToFields (Column a) (Column a)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Column a -> Column a
forall a. a -> a
id
instance D.Default ToFields String (Column T.SqlText) where
def :: ToFields String (Column SqlText)
def = (String -> Column SqlText) -> ToFields String (Column SqlText)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields String -> Column SqlText
String -> Field SqlText
T.sqlString
instance D.Default ToFields LBS.ByteString (Column T.SqlBytea) where
def :: ToFields ByteString (Column SqlBytea)
def = (ByteString -> Column SqlBytea)
-> ToFields ByteString (Column SqlBytea)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ByteString -> Column SqlBytea
ByteString -> Field SqlBytea
T.sqlLazyByteString
instance D.Default ToFields SBS.ByteString (Column T.SqlBytea) where
def :: ToFields ByteString (Column SqlBytea)
def = (ByteString -> Column SqlBytea)
-> ToFields ByteString (Column SqlBytea)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ByteString -> Column SqlBytea
ByteString -> Field SqlBytea
T.sqlStrictByteString
instance D.Default ToFields ST.Text (Column T.SqlText) where
def :: ToFields Text (Column SqlText)
def = (Text -> Column SqlText) -> ToFields Text (Column SqlText)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Text -> Column SqlText
Text -> Field SqlText
T.sqlStrictText
instance D.Default ToFields LT.Text (Column T.SqlText) where
def :: ToFields Text (Column SqlText)
def = (Text -> Column SqlText) -> ToFields Text (Column SqlText)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Text -> Column SqlText
Text -> Field SqlText
T.sqlLazyText
instance D.Default ToFields Sci.Scientific (Column T.SqlNumeric) where
def :: ToFields Scientific (Column SqlNumeric)
def = (Scientific -> Column SqlNumeric)
-> ToFields Scientific (Column SqlNumeric)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Scientific -> Column SqlNumeric
Scientific -> Field SqlNumeric
T.sqlNumeric
instance D.Default ToFields Int (Column T.SqlInt4) where
def :: ToFields Int (Column SqlInt4)
def = (Int -> Column SqlInt4) -> ToFields Int (Column SqlInt4)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Int -> Column SqlInt4
Int -> Field SqlInt4
T.sqlInt4
instance D.Default ToFields Int.Int32 (Column T.SqlInt4) where
def :: ToFields Int32 (Column SqlInt4)
def = (Int32 -> Column SqlInt4) -> ToFields Int32 (Column SqlInt4)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ((Int32 -> Column SqlInt4) -> ToFields Int32 (Column SqlInt4))
-> (Int32 -> Column SqlInt4) -> ToFields Int32 (Column SqlInt4)
forall a b. (a -> b) -> a -> b
$ Int -> Column SqlInt4
Int -> Field SqlInt4
T.sqlInt4 (Int -> Column SqlInt4)
-> (Int32 -> Int) -> Int32 -> Column SqlInt4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance D.Default ToFields Int.Int64 (Column T.SqlInt8) where
def :: ToFields Int64 (Column SqlInt8)
def = (Int64 -> Column SqlInt8) -> ToFields Int64 (Column SqlInt8)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Int64 -> Column SqlInt8
Int64 -> Field SqlInt8
T.sqlInt8
instance D.Default ToFields Double (Column T.SqlFloat8) where
def :: ToFields Double (Column SqlFloat8)
def = (Double -> Column SqlFloat8) -> ToFields Double (Column SqlFloat8)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Double -> Column SqlFloat8
Double -> Field SqlFloat8
T.sqlDouble
instance D.Default ToFields Bool (Column T.SqlBool) where
def :: ToFields Bool (Column SqlBool)
def = (Bool -> Column SqlBool) -> ToFields Bool (Column SqlBool)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Bool -> Column SqlBool
Bool -> Field SqlBool
T.sqlBool
instance D.Default ToFields UUID.UUID (Column T.SqlUuid) where
def :: ToFields UUID (Column SqlUuid)
def = (UUID -> Column SqlUuid) -> ToFields UUID (Column SqlUuid)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields UUID -> Column SqlUuid
UUID -> Field SqlUuid
T.sqlUUID
instance D.Default ToFields Time.Day (Column T.SqlDate) where
def :: ToFields Day (Column SqlDate)
def = (Day -> Column SqlDate) -> ToFields Day (Column SqlDate)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Day -> Column SqlDate
Day -> Field SqlDate
T.sqlDay
instance D.Default ToFields Time.UTCTime (Column T.SqlTimestamptz) where
def :: ToFields UTCTime (Column SqlTimestamptz)
def = (UTCTime -> Column SqlTimestamptz)
-> ToFields UTCTime (Column SqlTimestamptz)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields UTCTime -> Column SqlTimestamptz
UTCTime -> Field SqlTimestamptz
T.sqlUTCTime
instance D.Default ToFields Time.LocalTime (Column T.SqlTimestamp) where
def :: ToFields LocalTime (Column SqlTimestamp)
def = (LocalTime -> Column SqlTimestamp)
-> ToFields LocalTime (Column SqlTimestamp)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields LocalTime -> Column SqlTimestamp
LocalTime -> Field SqlTimestamp
T.sqlLocalTime
instance D.Default ToFields Time.ZonedTime (Column T.SqlTimestamptz) where
def :: ToFields ZonedTime (Column SqlTimestamptz)
def = (ZonedTime -> Column SqlTimestamptz)
-> ToFields ZonedTime (Column SqlTimestamptz)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ZonedTime -> Column SqlTimestamptz
ZonedTime -> Field SqlTimestamptz
T.sqlZonedTime
instance D.Default ToFields Time.TimeOfDay (Column T.SqlTime) where
def :: ToFields TimeOfDay (Column SqlTime)
def = (TimeOfDay -> Column SqlTime)
-> ToFields TimeOfDay (Column SqlTime)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields TimeOfDay -> Column SqlTime
TimeOfDay -> Field SqlTime
T.sqlTimeOfDay
instance D.Default ToFields (CI.CI ST.Text) (Column T.SqlCitext) where
def :: ToFields (CI Text) (Column SqlCitext)
def = (CI Text -> Column SqlCitext)
-> ToFields (CI Text) (Column SqlCitext)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields CI Text -> Column SqlCitext
CI Text -> Field SqlCitext
T.sqlCiStrictText
instance D.Default ToFields (CI.CI LT.Text) (Column T.SqlCitext) where
def :: ToFields (CI Text) (Column SqlCitext)
def = (CI Text -> Column SqlCitext)
-> ToFields (CI Text) (Column SqlCitext)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields CI Text -> Column SqlCitext
CI Text -> Field SqlCitext
T.sqlCiLazyText
instance D.Default ToFields SBS.ByteString (Column T.SqlJson) where
def :: ToFields ByteString (Column SqlJson)
def = (ByteString -> Column SqlJson)
-> ToFields ByteString (Column SqlJson)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ByteString -> Column SqlJson
ByteString -> Field SqlJson
T.sqlStrictJSON
instance D.Default ToFields LBS.ByteString (Column T.SqlJson) where
def :: ToFields ByteString (Column SqlJson)
def = (ByteString -> Column SqlJson)
-> ToFields ByteString (Column SqlJson)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ByteString -> Column SqlJson
ByteString -> Field SqlJson
T.sqlLazyJSON
instance D.Default ToFields Ae.Value (Column T.SqlJson) where
def :: ToFields Value (Column SqlJson)
def = (Value -> Column SqlJson) -> ToFields Value (Column SqlJson)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Value -> Column SqlJson
forall a. ToJSON a => a -> Field SqlJson
T.sqlValueJSON
instance D.Default ToFields SBS.ByteString (Column T.SqlJsonb) where
def :: ToFields ByteString (Column SqlJsonb)
def = (ByteString -> Column SqlJsonb)
-> ToFields ByteString (Column SqlJsonb)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ByteString -> Column SqlJsonb
ByteString -> Field SqlJsonb
T.sqlStrictJSONB
instance D.Default ToFields LBS.ByteString (Column T.SqlJsonb) where
def :: ToFields ByteString (Column SqlJsonb)
def = (ByteString -> Column SqlJsonb)
-> ToFields ByteString (Column SqlJsonb)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ByteString -> Column SqlJsonb
ByteString -> Field SqlJsonb
T.sqlLazyJSONB
instance D.Default ToFields Ae.Value (Column T.SqlJsonb) where
def :: ToFields Value (Column SqlJsonb)
def = (Value -> Column SqlJsonb) -> ToFields Value (Column SqlJsonb)
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields Value -> Column SqlJsonb
forall a. ToJSON a => a -> Field SqlJsonb
T.sqlValueJSONB
instance D.Default ToFields haskell (Column sql) => D.Default ToFields (Maybe haskell) (Maybe (Column sql)) where
def :: ToFields (Maybe haskell) (Maybe (Column sql))
def = (Maybe haskell -> Maybe (Column sql))
-> ToFields (Maybe haskell) (Maybe (Column sql))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields (haskell -> Column sql
forall haskells fields.
Default ToFields haskells fields =>
haskells -> fields
constant (haskell -> Column sql) -> Maybe haskell -> Maybe (Column sql)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)
instance (D.Default ToFields a (Column b), T.IsSqlType b)
=> D.Default ToFields [a] (Column (T.SqlArray b)) where
def :: ToFields [a] (Column (SqlArray b))
def = ([a] -> Column (SqlArray b)) -> ToFields [a] (Column (SqlArray b))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ((a -> Field b) -> [a] -> Field (SqlArray b)
forall b a.
IsSqlType b =>
(a -> Field b) -> [a] -> Field (SqlArray b)
T.sqlArray (ToFields a (Column b) -> a -> Column b
forall haskells fields.
ToFields haskells fields -> haskells -> fields
constantExplicit ToFields a (Column b)
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def))
instance D.Default ToFields (R.PGRange Int.Int) (Column (T.SqlRange T.SqlInt4)) where
def :: ToFields (PGRange Int) (Column (SqlRange SqlInt4))
def = (PGRange Int -> Column (SqlRange SqlInt4))
-> ToFields (PGRange Int) (Column (SqlRange SqlInt4))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ((PGRange Int -> Column (SqlRange SqlInt4))
-> ToFields (PGRange Int) (Column (SqlRange SqlInt4)))
-> (PGRange Int -> Column (SqlRange SqlInt4))
-> ToFields (PGRange Int) (Column (SqlRange SqlInt4))
forall a b. (a -> b) -> a -> b
$ \(R.PGRange RangeBound Int
a RangeBound Int
b) -> (Int -> Field SqlInt4)
-> RangeBound Int -> RangeBound Int -> Field (SqlRange SqlInt4)
forall b a.
IsRangeType b =>
(a -> Field b)
-> RangeBound a -> RangeBound a -> Field (SqlRange b)
T.sqlRange Int -> Field SqlInt4
T.sqlInt4 RangeBound Int
a RangeBound Int
b
instance D.Default ToFields (R.PGRange Int.Int64) (Column (T.SqlRange T.SqlInt8)) where
def :: ToFields (PGRange Int64) (Column (SqlRange SqlInt8))
def = (PGRange Int64 -> Column (SqlRange SqlInt8))
-> ToFields (PGRange Int64) (Column (SqlRange SqlInt8))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ((PGRange Int64 -> Column (SqlRange SqlInt8))
-> ToFields (PGRange Int64) (Column (SqlRange SqlInt8)))
-> (PGRange Int64 -> Column (SqlRange SqlInt8))
-> ToFields (PGRange Int64) (Column (SqlRange SqlInt8))
forall a b. (a -> b) -> a -> b
$ \(R.PGRange RangeBound Int64
a RangeBound Int64
b) -> (Int64 -> Field SqlInt8)
-> RangeBound Int64 -> RangeBound Int64 -> Field (SqlRange SqlInt8)
forall b a.
IsRangeType b =>
(a -> Field b)
-> RangeBound a -> RangeBound a -> Field (SqlRange b)
T.sqlRange Int64 -> Field SqlInt8
T.sqlInt8 RangeBound Int64
a RangeBound Int64
b
instance D.Default ToFields (R.PGRange Sci.Scientific) (Column (T.SqlRange T.SqlNumeric)) where
def :: ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric))
def = (PGRange Scientific -> Column (SqlRange SqlNumeric))
-> ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ((PGRange Scientific -> Column (SqlRange SqlNumeric))
-> ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric)))
-> (PGRange Scientific -> Column (SqlRange SqlNumeric))
-> ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric))
forall a b. (a -> b) -> a -> b
$ \(R.PGRange RangeBound Scientific
a RangeBound Scientific
b) -> (Scientific -> Field SqlNumeric)
-> RangeBound Scientific
-> RangeBound Scientific
-> Field (SqlRange SqlNumeric)
forall b a.
IsRangeType b =>
(a -> Field b)
-> RangeBound a -> RangeBound a -> Field (SqlRange b)
T.sqlRange Scientific -> Field SqlNumeric
T.sqlNumeric RangeBound Scientific
a RangeBound Scientific
b
instance D.Default ToFields (R.PGRange Time.LocalTime) (Column (T.SqlRange T.SqlTimestamp)) where
def :: ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp))
def = (PGRange LocalTime -> Column (SqlRange SqlTimestamp))
-> ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ((PGRange LocalTime -> Column (SqlRange SqlTimestamp))
-> ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp)))
-> (PGRange LocalTime -> Column (SqlRange SqlTimestamp))
-> ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp))
forall a b. (a -> b) -> a -> b
$ \(R.PGRange RangeBound LocalTime
a RangeBound LocalTime
b) -> (LocalTime -> Field SqlTimestamp)
-> RangeBound LocalTime
-> RangeBound LocalTime
-> Field (SqlRange SqlTimestamp)
forall b a.
IsRangeType b =>
(a -> Field b)
-> RangeBound a -> RangeBound a -> Field (SqlRange b)
T.sqlRange LocalTime -> Field SqlTimestamp
T.sqlLocalTime RangeBound LocalTime
a RangeBound LocalTime
b
instance D.Default ToFields (R.PGRange Time.UTCTime) (Column (T.SqlRange T.SqlTimestamptz)) where
def :: ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz))
def = (PGRange UTCTime -> Column (SqlRange SqlTimestamptz))
-> ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ((PGRange UTCTime -> Column (SqlRange SqlTimestamptz))
-> ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)))
-> (PGRange UTCTime -> Column (SqlRange SqlTimestamptz))
-> ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz))
forall a b. (a -> b) -> a -> b
$ \(R.PGRange RangeBound UTCTime
a RangeBound UTCTime
b) -> (UTCTime -> Field SqlTimestamptz)
-> RangeBound UTCTime
-> RangeBound UTCTime
-> Field (SqlRange SqlTimestamptz)
forall b a.
IsRangeType b =>
(a -> Field b)
-> RangeBound a -> RangeBound a -> Field (SqlRange b)
T.sqlRange UTCTime -> Field SqlTimestamptz
T.sqlUTCTime RangeBound UTCTime
a RangeBound UTCTime
b
instance D.Default ToFields (R.PGRange Time.Day) (Column (T.SqlRange T.SqlDate)) where
def :: ToFields (PGRange Day) (Column (SqlRange SqlDate))
def = (PGRange Day -> Column (SqlRange SqlDate))
-> ToFields (PGRange Day) (Column (SqlRange SqlDate))
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
toToFields ((PGRange Day -> Column (SqlRange SqlDate))
-> ToFields (PGRange Day) (Column (SqlRange SqlDate)))
-> (PGRange Day -> Column (SqlRange SqlDate))
-> ToFields (PGRange Day) (Column (SqlRange SqlDate))
forall a b. (a -> b) -> a -> b
$ \(R.PGRange RangeBound Day
a RangeBound Day
b) -> (Day -> Field SqlDate)
-> RangeBound Day -> RangeBound Day -> Field (SqlRange SqlDate)
forall b a.
IsRangeType b =>
(a -> Field b)
-> RangeBound a -> RangeBound a -> Field (SqlRange b)
T.sqlRange Day -> Field SqlDate
T.sqlDay RangeBound Day
a RangeBound Day
b
instance Functor (ToFields a) where
fmap :: (a -> b) -> ToFields a a -> ToFields a b
fmap a -> b
f (ToFields a -> a
g) = (a -> b) -> ToFields a b
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields ((a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f a -> a
g)
instance Applicative (ToFields a) where
pure :: a -> ToFields a a
pure = (a -> a) -> ToFields a a
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields ((a -> a) -> ToFields a a) -> (a -> a -> a) -> a -> ToFields a a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
ToFields a -> a -> b
f <*> :: ToFields a (a -> b) -> ToFields a a -> ToFields a b
<*> ToFields a -> a
x = (a -> b) -> ToFields a b
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields (a -> a -> b
f (a -> a -> b) -> (a -> a) -> a -> b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> a
x)
instance P.Profunctor ToFields where
dimap :: (a -> b) -> (c -> d) -> ToFields b c -> ToFields a d
dimap a -> b
f c -> d
g (ToFields b -> c
h) = (a -> d) -> ToFields a d
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields ((a -> b) -> (c -> d) -> (b -> c) -> a -> d
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
P.dimap a -> b
f c -> d
g b -> c
h)
instance PP.ProductProfunctor ToFields where
empty :: ToFields () ()
empty = (() -> ()) -> ToFields () ()
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields () -> ()
forall (p :: * -> * -> *). ProductProfunctor p => p () ()
empty
ToFields a -> b
f ***! :: ToFields a b -> ToFields a' b' -> ToFields (a, a') (b, b')
***! ToFields a' -> b'
g = ((a, a') -> (b, b')) -> ToFields (a, a') (b, b')
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields (a -> b
f (a -> b) -> (a' -> b') -> (a, a') -> (b, b')
forall (p :: * -> * -> *) a b a' b'.
ProductProfunctor p =>
p a b -> p a' b' -> p (a, a') (b, b')
***! a' -> b'
g)
instance PP.SumProfunctor ToFields where
ToFields a -> b
f +++! :: ToFields a b
-> ToFields a' b' -> ToFields (Either a a') (Either b b')
+++! ToFields a' -> b'
g = (Either a a' -> Either b b')
-> ToFields (Either a a') (Either b b')
forall haskells fields.
(haskells -> fields) -> ToFields haskells fields
ToFields (a -> b
f (a -> b) -> (a' -> b') -> Either a a' -> Either b b'
forall (p :: * -> * -> *) a b a' b'.
SumProfunctor p =>
p a b -> p a' b' -> p (Either a a') (Either b b')
+++! a' -> b'
g)