beam
beam copied to clipboard
Problematic `Nullable` for sub beams
When using a sub-beam that can be made null as a whole, it generates several problems, for example
type Foo = FooT Identity
data FooT = Foo
{ _inside :: Inside (Nullable f)
} deriving(Generic)
type Inside = InsideT Identity
data InsideT = Inside
{ _moo :: C f Int
} deriving(Generic)
instance Beamable FooT
instance Beamable InsideT
deriving instance Show Inside
deriving instance Show Foo <----------- WON'T COMPILE, no Show instance for `InsideT (Nullable Identity)`
...
update fooTable
( \FooT{..} ->
[ _inside <-. val_ (Just moo) <------------ WON'T COMPILE, Couldn't match type `ReceiptValueT (Nullable Identity)`
] with `Maybe ReceiptValue`
)
( \FooT{..} -> val_ True
)
There are workarounds to these problems, but they are messy or require boilerplate (or maybe am I missing something?).
Maybe using a type function Columns (Cs), similar to Columnar, could help to fix/ease these issues?
Haven't checked, but something like:
type family Columns where
Columns (Nullable Identity) a = Maybe (a Identity)
Columns f a = a f
? (That wouldn't fix the second problem though)
Maybe if Columns looks too similar to Column, it could be name ColumnGroup (CG) instead.
What are your thoughts on this?
The proposed type family doesn't quite capture SQL semantics though. In particular, we use embedded beamable to do things like specify the column names of the embedded table. In your proposed type family, you would be able to ignore these columns for embedded Beamables by supplying Nothing.
If you want to avoid having to specify Show instances, you can write the larger show instance:
deriving instance ( Show (Columnar f Int) ) => Show (InsideT f)
deriving instance (Show (Columnar f Int)) => Show (FooT f)
For the last example, you should use just_ (val_ ...), in general, prefer the just_ and nothing_ from beam over the Haskell constructors when making beam queries.
If you want to avoid having to specify Show instances, you can write the larger show instance:
thanks for the hint! I'll use it.
For the last example, you should use just_ (val_ ...), in general, prefer the just_ and nothing_ from beam over the Haskell constructors when making beam queries.
but then one would need to write maybe nothing_ (just_ . val_) moo instead of plain
just val_ moo (where moo :: Maybe Int) wouldn't it?.
Another issue I found myself, even though ExampleT Nullable Identity is similar to Maybe Example, the compiler can not figure this out, and one needs to "convince him", like in:
converse :: ExampleT Nullable Identity -> Maybe Example
converse Example{..} = Example{..}
It is possible to create a generic function converse :: (..) => f Nullable Identity -> Maybe (f Identity), though it would be much nicer to find a way so this could be transparent to the user.
The proposed type family doesn't quite capture SQL semantics though...
I didn't mean to use Columns (or better maybe named ColumnarGroup) as a substitution of Columnar, but in addition to. So for each case different than Nullable Identity, it will pass f to the sub-beam where it would eventually use Columnar and behave as usual. As an example:
type Foo = FooT Identity
data FooT = Foo
{ _inside :: ColumnarGroup (Nullable f) Inside
} deriving(Generic)
type Inside = InsideT Identity
data InsideT = Inside
{ _moo :: Columnar f Int
} deriving(Generic)
That said, the proposition would not work as it is, for example, it would break QExprToIdentity, and there might be other problems I'm not aware of yet; but maybe after some further changes, I could make it work. Would it be interesting a PR based on this approach?
Another potential benefit of explicitly marking beams as a group of columns is that, eventually in a future, they could get enhanced with further information, as some potential example:
-- | the subtable is stored within the same table
type ColumnarGroup subtable = SubBeam Embedded subtable
-- | the subtable is stored as a reference to another table
type ReferencedColumnarGroup subtable = SubBeam Referenced subtable
-- | A list of tables referencing the main table's primary key.
type BeamListOf subtable = SubBeam AsList subtable
-- | an either implemented as 2 nullable referencing columns to 2 tables, plus a constraint that at least one of those is not null
type ColumnarEither subtableA subtableB
-- ... etc
though these examples would be more challening to implement or not even a good idea...
I'd be happy to take a look at any proposals, but I'd have to think through these all in more depth before merging anything.
I'm not sure if this is quite the same issue, but here's something that I'm playing with. This introduces a new type MaybeTable, which is used to represent an entire table that might be null. This brings in an extra magic column which is known to not be null when the table is successfully joined - I just add an artificial bool column. This solves the problem of Maybe (Maybe a) being meaningless. MaybeTable provides the $? operator, which is like $, but allows access through Maybe:
($?) :: (a -> QExpr b) -> MaybeTable a -> QExpr (Maybe b)
This works comes out of rel8 and has worked out very well at CircuitHub.
The usage is something like:
data Tables f =
Tables { tableA :: TableA f, tableB :: OuterJoin f TableB }
OuterJoin QExpr ~ MaybeTable, but OuterJoin Identity ~ Maybe.
{-# language FlexibleContexts #-}
{-# language KindSignatures #-}
{-# language TypeApplications #-}
{-# language TypeFamilies #-}
module Database.Beam.Extra where
import Database.Beam
import Database.Beam.Backend.SQL
import Database.Beam.Postgres
import Database.Beam.Postgres.Syntax
import Database.Beam.Query
import Database.Beam.Query.Internal
import Database.Beam.Schema.Tables
type family OuterJoin f a :: * where
OuterJoin Identity a =
Maybe a
OuterJoin ( QGenExpr context syntax s ) a =
MaybeTable ( QGenExpr context syntax s ) ( QGenExpr context syntax s a )
data MaybeTable expr a =
MaybeTable ( expr ( Maybe Bool ) ) a
leftJoin2
:: ( ProjectibleWithPredicate AnyType PgExpressionSyntax r
, ThreadRewritable ( QNested s ) r
, Retaggable
( QGenExpr QValueContext PgExpressionSyntax s )
( WithRewrittenThread ( QNested s ) s r )
)
=> Q PgSelectSyntax db ( QNested s ) r
-> ( WithRewrittenThread ( QNested s ) s r -> QExpr PgExpressionSyntax s Bool )
-> Q
PgSelectSyntax
db
s
( MaybeTable
( QGenExpr QValueContext PgExpressionSyntax s )
( Retag Nullable ( WithRewrittenThread ( QNested s ) s r ) )
)
leftJoin2 rel f = do
( tag, r ) <-
leftJoin_
( do
r <-
rel
return ( val_ @( QGenExpr _ _ _ Bool ) True, r )
)
( \( _tag, r ) -> f r )
return ( MaybeTable tag r )
($?)
:: ( a -> QExpr x y b )
-> MaybeTable tag a
-> Retag Nullable ( QExpr x y b )
f $? MaybeTable _ a =
retag
@_
@_
@Nullable
( \( Columnar' ( QExpr e ) ) -> Columnar' ( QExpr e ) )
( f a )
isTableNull
:: IsSql92ExpressionSyntax syntax
=> MaybeTable ( QGenExpr ctxt syntax s ) a
-> QGenExpr ctxt syntax s Bool
isTableNull ( MaybeTable tag _ ) =
isNothing_ tag
Ah shoot, I now see that you still can't derive Beamable with OuterJoin, so this isn't a complete solution.