> {-# LANGUAGE FlexibleContexts #-} > module DefaultExplanation where > > import Opaleye (Field, FieldNullable, FromFields, Select, > SqlInt4, SqlBool, SqlText, SqlFloat4) > import qualified Opaleye as O > import qualified Opaleye.Adaptors as Adaptors > import Opaleye.Adaptors (Binaryspec) > > import Data.Profunctor.Product ((***!), p4) > import Data.Profunctor.Product.Default (Default, def) > import qualified Database.PostgreSQL.Simple as SQL Introduction ============ Instances of `ProductProfunctor` are very common in Opaleye. They are first-class representations of various transformations that need to occur in certain places. The `Default` typeclass from product-profunctors is used throughout Opaleye to avoid API users having to write a lot of automatically derivable code, and it deserves a thorough explanation. Example ======= By way of example we will consider the Binaryspec product-profunctor and how it is used with the `unionAll` operation. The version of `unionAll` that does not have a Default constraint is called `unionAllExplicit` and has the following type. > unionAllExplicit :: Binaryspec a b -> Select a -> Select a -> Select b > unionAllExplicit = O.unionAllExplicit What is the `Binaryspec` used for here? Let's take a simple case where we want to union two queries of type `Select (Field SqlInt4, Field SqlText)` > mySelect1 :: Select (Field SqlInt4, Field SqlText) > mySelect1 = undefined -- We won't actually need specific implementations here > > mySelect2 :: Select (Field SqlInt4, Field SqlText) > mySelect2 = undefined That means we will be using unionAll at the type > unionAllExplicit' :: Binaryspec (Field SqlInt4, Field SqlText) (Field SqlInt4, Field SqlText) > -> Select (Field SqlInt4, Field SqlText) > -> Select (Field SqlInt4, Field SqlText) > -> Select (Field SqlInt4, Field SqlText) > unionAllExplicit' = unionAllExplicit Since every `Field` is actually just a string containing an SQL expression, `(Field SqlInt4, Field SqlText)` is a pair of expressions. When we generate the SQL we need to take the two pairs of expressions, generate new unique names that refer to them and produce these new unique names in another value of type `(Field SqlInt4, Field SqlText)`. This is exactly what a value of type Binaryspec (Field SqlInt4, Field SqlText) (Field SqlInt4, Field SqlText) allows us to do. So the next question is, how do we get our hands on a value of that type? Well, we have `binaryspecField` which is a value that allows us to access the field name within a single field. > binaryspecField :: Binaryspec (Field a) (Field a) > binaryspecField = Adaptors.binaryspecField `Binaryspec` is a `ProductProfunctor` so we can combine two of them to work on a pair. > binaryspecField2 :: Binaryspec (Field a, Field b) (Field a, Field b) > binaryspecField2 = binaryspecField ***! binaryspecField Then we can use `binaryspecField2` in `unionAllExplicit`. > theUnionAll :: Select (Field SqlInt4, Field SqlText) > theUnionAll = unionAllExplicit binaryspecField2 mySelect1 mySelect2 Now suppose that we wanted to take a union of two queries with fields in a tuple of size four. We can make a suitable `Binaryspec` like this: > binaryspecField4 :: Binaryspec (Field a, Field b, Field c, Field d) > (Field a, Field b, Field c, Field d) > binaryspecField4 = p4 (binaryspecField, binaryspecField, > binaryspecField, binaryspecField) Then we can pass this `Binaryspec` to `unionAllExplicit`. The problem and 'Default' is the solution ========================================= Constructing these `Binaryspec`s explicitly will become very tedious very fast. Furthermore it is completely pointless to construct them explicitly because the correct `Binaryspec` can automatically be deduced. This is where the `Default` typeclass comes in. `Opaleye.Internal.Binary` contains the `Default` instance instance Default Binaryspec (Field a) (Field a) where def = binaryspecField That means that we know the "default" way of getting a Binaryspec (Field a) (Field a) However, if we have a default way of getting one of these, we also have a default way of getting a Binaryspec (Field a, Field b) (Field a, Field b) just by using the `ProductProfunctor` product operation `(***!)`. And in the general case for a product type `T` with n type parameters we can automatically deduce the correct value of type Binaryspec (T a1 ... an) (T a1 ... an) (This requires the `Default` instance for `T` as generated by `Data.Profunctor.Product.TH.makeAdaptorAndInstance`, or an equivalent instance defined by hand). It means we don't have to explicitly specify the `Binaryspec` value. Instead of writing `theUnionAll` as above, providing the `Binaryspec` explicitly, we can instead use a version of `unionAll` which automatically uses the default `Binaryspec` so we don't have to provide it. This is exactly what `Opaleye.Binary.unionAll` does. > unionAll :: Default Binaryspec a b > => Select a -> Select a -> Select b > unionAll = O.unionAllExplicit def > > theUnionAll' :: Select (Field SqlInt4, Field SqlText) > theUnionAll' = unionAll mySelect1 mySelect2 In the long run this prevents writing a huge amount of boilerplate code. A further example: `FromFields` ============================== A `FromFields a b` is the product-profunctor which represents how to turn run a `Select a` (currently on Postgres) and return you a list of rows, each row of type `b`. The function which is responsible for this is `runSelect` > runSelectExplicit :: FromFields a b -> SQL.Connection -> Select a -> IO [b] > runSelectExplicit = O.runSelectExplicit Basic values of `FromFields` will have the following types > intRunner :: FromFields (Field SqlInt4) Int > intRunner = undefined -- The implementation is not important here > > doubleRunner :: FromFields (Field SqlFloat4) Double > doubleRunner = undefined > > stringRunner :: FromFields (Field SqlText) String > stringRunner = undefined > > boolRunner :: FromFields (Field SqlBool) Bool > boolRunner = undefined Furthermore we will have basic ways of running queries which return `Nullable` values, for example > nullableIntRunner :: FromFields (FieldNullable SqlInt4) (Maybe Int) > nullableIntRunner = undefined If I have a very simple select with a single field of `SqlInt4` then I can run it using the `intRunner`. > mySelect3 :: Select (Field SqlInt4) > mySelect3 = undefined -- The implementation is not important > > runTheSelect :: SQL.Connection -> IO [Int] > runTheSelect c = runSelectExplicit intRunner c mySelect3 If my select has several fields of different types I need to build up a larger `FromFields`. > mySelect4 :: Select (Field SqlInt4, Field SqlText, Field SqlBool, FieldNullable SqlInt4) > mySelect4 = undefined > > largerSelectRunner :: FromFields > (Field SqlInt4, Field SqlText, Field SqlBool, FieldNullable SqlInt4) > (Int, String, Bool, Maybe Int) > largerSelectRunner = p4 (intRunner, stringRunner, boolRunner, nullableIntRunner) > > runTheBiggerSelect :: SQL.Connection -> IO [(Int, String, Bool, Maybe Int)] > runTheBiggerSelect c = runSelectExplicit largerSelectRunner c mySelect4 But having to build up `largerSelectRunner` was a pain and completely redundant! Like the `Binaryspec` it can be automatically deduced. `Opaleye.RunSelect` already gives us `Default` instances for the following types (plus many others, of course!). * `FromFields (Field SqlInt4) Int` * `FromFields (Field SqlText) String` * `FromFields (Field Bool) Bool` * `FromFields (Field (Nullable Int)) (Maybe Int)` Then the `Default` typeclass machinery automatically deduces the correct value of the type we want. > largerSelectRunner' :: FromFields > (Field SqlInt4, Field SqlText, Field SqlBool, FieldNullable SqlInt4) > (Int, String, Bool, Maybe Int) > largerSelectRunner' = def And we can produce a version of `runSelect` which allows us to write our select without explicitly passing the product-profunctor value. > runSelect :: Default FromFields a b => SQL.Connection -> Select a -> IO [b] > runSelect = O.runSelectExplicit def > > runTheBiggerSelect' :: SQL.Connection -> IO [(Int, String, Bool, Maybe Int)] > runTheBiggerSelect' c = runSelect c mySelect4 Conclusion ========== Much of the functionality of Opaleye depends on product-profunctors and many of the values of the product-profunctors are automatically derivable from some base collection. The `Default` typeclass and its associated instance derivations are the mechanism through which this happens.