Skip to content

Commit

Permalink
Use makeAdaptorAndInstanceInferrable instead of makeAdaptorAndInstance
Browse files Browse the repository at this point in the history
The older one has inference problems, and causes confusion, for example

#605
  • Loading branch information
tomjaguarpaw committed Sep 27, 2024
1 parent ff3f463 commit 144ffe7
Show file tree
Hide file tree
Showing 11 changed files with 19 additions and 17 deletions.
2 changes: 1 addition & 1 deletion Doc/Tutorial/DefaultExplanation.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,7 @@ 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
`Data.Profunctor.Product.TH.makeAdaptorAndInstanceInferrable`, or an equivalent
instance defined by hand). It means we don't have to explicitly
specify the `Binaryspec` value.

Expand Down
14 changes: 8 additions & 6 deletions Doc/Tutorial/TutorialBasic.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE TemplateHaskell #-}
> {-# LANGUAGE TypeOperators #-}
> {-# LANGUAGE UndecidableInstances #-}
>
> module TutorialBasic where
>
Expand All @@ -19,7 +21,7 @@
>
> import Data.Profunctor.Product (p2, p3)
> import Data.Profunctor.Product.Default (Default)
> import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
> import Data.Profunctor.Product.TH (makeAdaptorAndInstanceInferrable)
> import Data.Time.Calendar (Day)
>
> import qualified Database.PostgreSQL.Simple as PGS
Expand Down Expand Up @@ -130,7 +132,7 @@ To get user defined types to work with the typeclass magic they must
have instances defined for them. The instances are derivable with
Template Haskell.
> $(makeAdaptorAndInstance "pBirthday" ''Birthday')
> $(makeAdaptorAndInstanceInferrable "pBirthday" ''Birthday')
You don't have to use Template Haskell, but it just saves us writing
things out by hand here. If you want to avoid Template Haskell see
Expand Down Expand Up @@ -569,7 +571,7 @@ this information with the following datatype.
> , quantity :: d
> , radius :: e }
>
> $(makeAdaptorAndInstance "pWidget" ''Widget)
> $(makeAdaptorAndInstanceInferrable "pWidget" ''Widget)
For the purposes of this example the style, color and location will be
strings, but in practice they might have been a different data type.
Expand Down Expand Up @@ -731,7 +733,7 @@ and integer quantity of goods.
> , wLocation :: b
> , wNumGoods :: c }
>
> $(makeAdaptorAndInstance "pWarehouse" ''Warehouse')
> $(makeAdaptorAndInstanceInferrable "pWarehouse" ''Warehouse')
We could represent the integer ID in Opaleye as a `SqlInt4`
Expand All @@ -755,7 +757,7 @@ it holds.
On the other hand we can make a newtype for the warehouse ID
> newtype WarehouseId' a = WarehouseId a
> $(makeAdaptorAndInstance "pWarehouseId" ''WarehouseId')
> $(makeAdaptorAndInstanceInferrable "pWarehouseId" ''WarehouseId')
>
> type WarehouseIdField = WarehouseId' (Field SqlInt4)
>
Expand Down Expand Up @@ -821,7 +823,7 @@ Maybes. We could run the select `selectTable employeeTable` like this.
> runEmployeesSelect = runSelect
Newtypes are taken care of automatically by the typeclass instance
that was generated by `makeAdaptorAndInstance`. A `WarehouseId'
that was generated by `makeAdaptorAndInstanceInferrable`. A `WarehouseId'
(Field SqlInt4)` becomes a `WarehouseId' Int` when the select is run.
We could run the select `selectTable goodWarehouseTable` like this.
Expand Down
2 changes: 1 addition & 1 deletion src/Opaleye/Binary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@
-- -> S.Select (Field a, Field b)
-- @
--
-- Assuming the @makeAdaptorAndInstance@ splice has been run for the product type @Foo@:
-- Assuming the @makeAdaptorAndInstanceInferrable@ splice has been run for the product type @Foo@:
--
-- @
-- unionAll :: S.Select (Foo (Field a) (Field b) (Field c))
Expand Down
2 changes: 1 addition & 1 deletion src/Opaleye/Distinct.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Opaleye.Internal.Unpackspec (Unpackspec)
-- distinct :: Select (Field a, Field b) -> Select (Field a, Field b)
-- @
--
-- Assuming the @makeAdaptorAndInstance@ splice has been run for the product type @Foo@:
-- Assuming the @makeAdaptorAndInstanceInferrable@ splice has been run for the product type @Foo@:
--
-- @
-- distinct :: Select (Foo (Field a) (Field b) (Field c)) -> Select (Foo (Field a) (Field b) (Field c))
Expand Down
2 changes: 1 addition & 1 deletion src/Opaleye/Internal/Table.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ import qualified Control.Arrow as Arr
-- , quantity :: d
-- , radius :: e }
--
-- \$('Data.Profunctor.Product.TH.makeAdaptorAndInstance' \"pWidget\" ''Widget)
-- \$('Data.Profunctor.Product.TH.makeAdaptorAndInstanceInferrable' \"pWidget\" ''Widget)
--
-- widgetTable :: Table (Widget (Maybe (Field SqlInt4)) (Field SqlText) (Field SqlText)
-- (Field SqlInt4) (Field SqlFloat8))
Expand Down
2 changes: 1 addition & 1 deletion src/Opaleye/Internal/Unpackspec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ newtype Unpackspec fields fields' =
-- 'Default' instance of type @Foo (Field a) (Field b) (Field c)@
-- will allow you to manipulate or extract the three 'HPQ.PrimExpr's
-- contained therein (for a user-defined product type @Foo@, assuming
-- the @makeAdaptorAndInstance@ splice from
-- the @makeAdaptorAndInstanceInferrable@ splice from
-- @Data.Profunctor.Product.TH@ has been run).
--
-- Users should almost never need to create or manipulate
Expand Down
4 changes: 2 additions & 2 deletions src/Opaleye/Operators.hs
Original file line number Diff line number Diff line change
Expand Up @@ -188,14 +188,14 @@ infix 4 ./=

infix 4 .===
-- | A polymorphic equality operator that works for all types that you
-- have run `makeAdaptorAndInstance` on. This may be unified with
-- have run `makeAdaptorAndInstanceInferrable` on. This may be unified with
-- `.==` in a future version.
(.===) :: D.Default O.EqPP fields fields => fields -> fields -> F.Field T.SqlBool
(.===) = (O..==)

infix 4 ./==
-- | A polymorphic inequality operator that works for all types that
-- you have run `makeAdaptorAndInstance` on. This may be unified with
-- you have run `makeAdaptorAndInstanceInferrable` on. This may be unified with
-- `./=` in a future version.
(./==) :: D.Default O.EqPP fields fields => fields -> fields -> F.Field T.SqlBool
(./==) = Opaleye.Operators.not .: (O..==)
Expand Down
2 changes: 1 addition & 1 deletion src/Opaleye/RunSelect.hs
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,7 @@ declareCursorExplicit = RQ.declareCursorExplicit
-- runSelectI :: 'S.Select' ('Opaleye.Field.Field' 'Opaleye.SqlTypes.SqlInt4', 'Opaleye.Field.Field' 'Opaleye.SqlTypes.SqlText') -> IO [(Int, String)]
-- @
--
-- Assuming the @makeAdaptorAndInstance@ splice has been run for the product type @Foo@:
-- Assuming the @makeAdaptorAndInstanceInferrable@ splice has been run for the product type @Foo@:
--
-- @
-- runSelectI :: 'S.Select' (Foo ('Opaleye.Field.Field' 'Opaleye.SqlTypes.SqlInt4') ('Opaleye.Field.Field' 'Opaleye.SqlTypes.SqlText') ('Opaleye.Field.Field' 'Opaleye.SqlTypes.SqlBool')
Expand Down
2 changes: 1 addition & 1 deletion src/Opaleye/Sql.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ import qualified Data.Profunctor.Product.Default as D
-- showSql :: Select (Field a, Field b) -> Maybe String
-- @
--
-- Assuming the @makeAdaptorAndInstance@ splice has been run for the
-- Assuming the @makeAdaptorAndInstanceInferrable@ splice has been run for the
-- product type @Foo@:
--
-- @
Expand Down
2 changes: 1 addition & 1 deletion src/Opaleye/Table.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ import qualified Data.Profunctor.Product.Default as D
-- -> Select (Field a, Field b)
-- @
--
-- Assuming the @makeAdaptorAndInstance@ splice has been run for the
-- Assuming the @makeAdaptorAndInstanceInferrable@ splice has been run for the
-- product type @Foo@:
--
-- @
Expand Down
2 changes: 1 addition & 1 deletion src/Opaleye/Values.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Data.Profunctor.Product.Default (Default, def)
-- values :: [(Field a, Field b)] -> Select (Field a, Field b)
-- @
--
-- Assuming the @makeAdaptorAndInstance@ splice has been run for the
-- Assuming the @makeAdaptorAndInstanceInferrable@ splice has been run for the
-- product type @Foo@:
--
-- @
Expand Down

0 comments on commit 144ffe7

Please sign in to comment.