{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} module Database.Esqueleto.Experimental.ToMaybe where import Database.Esqueleto.Internal.Internal hiding (From(..), from, on) import Database.Esqueleto.Internal.PersistentImport (Entity(..)) type family Nullable a where Nullable (Maybe a) = a Nullable a = a class ToMaybe a where type ToMaybeT a toMaybe :: a -> ToMaybeT a instance ToMaybe (SqlExpr (Maybe a)) where type ToMaybeT (SqlExpr (Maybe a)) = SqlExpr (Maybe a) toMaybe :: SqlExpr (Maybe a) -> ToMaybeT (SqlExpr (Maybe a)) toMaybe = forall a. a -> a id instance ToMaybe (SqlExpr (Entity a)) where type ToMaybeT (SqlExpr (Entity a)) = SqlExpr (Maybe (Entity a)) toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a)) toMaybe (ERaw SqlExprMeta f NeedParens -> IdentInfo -> (Builder, [PersistValue]) m) = (forall a. SqlExprMeta -> (NeedParens -> IdentInfo -> (Builder, [PersistValue])) -> SqlExpr a ERaw SqlExprMeta f NeedParens -> IdentInfo -> (Builder, [PersistValue]) m) instance ToMaybe (SqlExpr (Value a)) where type ToMaybeT (SqlExpr (Value a)) = SqlExpr (Value (Maybe (Nullable a))) toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) toMaybe = forall a b. SqlExpr (Value a) -> SqlExpr (Value b) veryUnsafeCoerceSqlExprValue instance (ToMaybe a, ToMaybe b) => ToMaybe (a,b) where type ToMaybeT (a, b) = (ToMaybeT a, ToMaybeT b) toMaybe :: (a, b) -> ToMaybeT (a, b) toMaybe (a a, b b) = (forall a. ToMaybe a => a -> ToMaybeT a toMaybe a a, forall a. ToMaybe a => a -> ToMaybeT a toMaybe b b) instance ( ToMaybe a , ToMaybe b , ToMaybe c) => ToMaybe (a,b,c) where type ToMaybeT (a, b, c) = (ToMaybeT a, ToMaybeT b, ToMaybeT c) toMaybe :: (a, b, c) -> ToMaybeT (a, b, c) toMaybe = forall a b c. ((a, b), c) -> (a, b, c) to3 forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. ToMaybe a => a -> ToMaybeT a toMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b c. (a, b, c) -> ((a, b), c) from3 instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d) => ToMaybe (a,b,c,d) where type ToMaybeT (a, b, c, d) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d) toMaybe :: (a, b, c, d) -> ToMaybeT (a, b, c, d) toMaybe = forall a b c d. ((a, b), (c, d)) -> (a, b, c, d) to4 forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. ToMaybe a => a -> ToMaybeT a toMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b c d. (a, b, c, d) -> ((a, b), (c, d)) from4 instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d , ToMaybe e) => ToMaybe (a,b,c,d,e) where type ToMaybeT (a, b, c, d, e) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e) toMaybe :: (a, b, c, d, e) -> ToMaybeT (a, b, c, d, e) toMaybe = forall a b c d e. ((a, b), (c, d), e) -> (a, b, c, d, e) to5 forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. ToMaybe a => a -> ToMaybeT a toMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b c d e. (a, b, c, d, e) -> ((a, b), (c, d), e) from5 instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d , ToMaybe e , ToMaybe f ) => ToMaybe (a,b,c,d,e,f) where type ToMaybeT (a, b, c, d, e, f) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f) toMaybe :: (a, b, c, d, e, f) -> ToMaybeT (a, b, c, d, e, f) toMaybe = forall a b c d e f. ((a, b), (c, d), (e, f)) -> (a, b, c, d, e, f) to6 forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. ToMaybe a => a -> ToMaybeT a toMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b c d e f. (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f)) from6 instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d , ToMaybe e , ToMaybe f , ToMaybe g ) => ToMaybe (a,b,c,d,e,f,g) where type ToMaybeT (a, b, c, d, e, f, g) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g) toMaybe :: (a, b, c, d, e, f, g) -> ToMaybeT (a, b, c, d, e, f, g) toMaybe = forall a b c d e f g. ((a, b), (c, d), (e, f), g) -> (a, b, c, d, e, f, g) to7 forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. ToMaybe a => a -> ToMaybeT a toMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b c d e f g. (a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g) from7 instance ( ToMaybe a , ToMaybe b , ToMaybe c , ToMaybe d , ToMaybe e , ToMaybe f , ToMaybe g , ToMaybe h ) => ToMaybe (a,b,c,d,e,f,g,h) where type ToMaybeT (a, b, c, d, e, f, g, h) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g, ToMaybeT h) toMaybe :: (a, b, c, d, e, f, g, h) -> ToMaybeT (a, b, c, d, e, f, g, h) toMaybe = forall a b c d e f g h. ((a, b), (c, d), (e, f), (g, h)) -> (a, b, c, d, e, f, g, h) to8 forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. ToMaybe a => a -> ToMaybeT a toMaybe forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b c d e f g h. (a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h)) from8