{-# LANGUAGE LambdaCase #-}

module Opaleye.Internal.Print where

import           Prelude hiding (product)

import qualified Opaleye.Internal.Sql as Sql
import           Opaleye.Internal.Sql (Select(SelectFrom,
                                              Table,
                                              RelExpr,
                                              SelectJoin,
                                              SelectSemijoin,
                                              SelectValues,
                                              SelectBinary,
                                              SelectLabel,
                                              SelectExists),
                                       From, Join, Semijoin, Values, Binary, Label, Exists)

import qualified Opaleye.Internal.PrimQuery as PQ
import qualified Opaleye.Internal.HaskellDB.PrimQuery as HPQ
import qualified Opaleye.Internal.HaskellDB.Sql as HSql
import qualified Opaleye.Internal.HaskellDB.Sql.Print as HPrint
import           Opaleye.Internal.HaskellDB.Sql.Print (ppAs)
import qualified Opaleye.Internal.Optimize as Op
import qualified Opaleye.Internal.Tag as T

import           Text.PrettyPrint.HughesPJ (Doc, ($$), (<+>), text, empty,
                                            parens)
import qualified Data.Char
import qualified Data.List.NonEmpty as NEL
import qualified Data.Text          as ST

type TableAlias = String

ppSql :: Select -> Doc
ppSql :: Select -> Doc
ppSql (SelectFrom From
s)     = From -> Doc
ppSelectFrom From
s
ppSql (Table SqlTable
table)      = SqlTable -> Doc
HPrint.ppTable SqlTable
table
ppSql (RelExpr SqlExpr
expr)     = SqlExpr -> Doc
HPrint.ppSqlExpr SqlExpr
expr
ppSql (SelectJoin Join
j)     = Join -> Doc
ppSelectJoin Join
j
ppSql (SelectSemijoin Semijoin
j) = Semijoin -> Doc
ppSelectSemijoin Semijoin
j
ppSql (SelectValues Values
v)   = Values -> Doc
ppSelectValues Values
v
ppSql (SelectBinary Binary
v)   = Binary -> Doc
ppSelectBinary Binary
v
ppSql (SelectLabel Label
v)    = Label -> Doc
ppSelectLabel Label
v
ppSql (SelectExists Exists
v)   = Exists -> Doc
ppSelectExists Exists
v

ppDistinctOn :: Maybe (NEL.NonEmpty HSql.SqlExpr) -> Doc
ppDistinctOn :: Maybe (NonEmpty SqlExpr) -> Doc
ppDistinctOn = Doc -> (NonEmpty SqlExpr -> Doc) -> Maybe (NonEmpty SqlExpr) -> Doc
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Doc
forall a. Monoid a => a
mempty ((NonEmpty SqlExpr -> Doc) -> Maybe (NonEmpty SqlExpr) -> Doc)
-> (NonEmpty SqlExpr -> Doc) -> Maybe (NonEmpty SqlExpr) -> Doc
forall a b. (a -> b) -> a -> b
$ \NonEmpty SqlExpr
nel ->
    String -> Doc
text String
"DISTINCT ON" Doc -> Doc -> Doc
<+>
        String -> Doc
text String
"(" Doc -> Doc -> Doc
$$ (SqlExpr -> Doc) -> [SqlExpr] -> Doc
forall a. (a -> Doc) -> [a] -> Doc
HPrint.commaV SqlExpr -> Doc
HPrint.ppSqlExpr (NonEmpty SqlExpr -> [SqlExpr]
forall a. NonEmpty a -> [a]
NEL.toList NonEmpty SqlExpr
nel) Doc -> Doc -> Doc
$$ String -> Doc
text String
")"

ppSelectFrom :: From -> Doc
ppSelectFrom :: From -> Doc
ppSelectFrom From
s = String -> Doc
text String
"SELECT"
                 Doc -> Doc -> Doc
<+> Maybe (NonEmpty SqlExpr) -> Doc
ppDistinctOn (From -> Maybe (NonEmpty SqlExpr)
Sql.distinctOn From
s)
                 Doc -> Doc -> Doc
$$  SelectAttrs -> Doc
ppAttrs (From -> SelectAttrs
Sql.attrs From
s)
                 Doc -> Doc -> Doc
$$  [(Lateral, Select)] -> Doc
ppTables (From -> [(Lateral, Select)]
Sql.tables From
s)
                 Doc -> Doc -> Doc
$$  [SqlExpr] -> Doc
HPrint.ppWhere (From -> [SqlExpr]
Sql.criteria From
s)
                 Doc -> Doc -> Doc
$$  Maybe (NonEmpty SqlExpr) -> Doc
ppGroupBy (From -> Maybe (NonEmpty SqlExpr)
Sql.groupBy From
s)
                 Doc -> Doc -> Doc
$$  [(SqlExpr, SqlOrder)] -> Doc
HPrint.ppOrderBy (From -> [(SqlExpr, SqlOrder)]
Sql.orderBy From
s)
                 Doc -> Doc -> Doc
$$  Maybe Int -> Doc
ppLimit (From -> Maybe Int
Sql.limit From
s)
                 Doc -> Doc -> Doc
$$  Maybe Int -> Doc
ppOffset (From -> Maybe Int
Sql.offset From
s)
                 Doc -> Doc -> Doc
$$  Maybe LockStrength -> Doc
ppFor (From -> Maybe LockStrength
Sql.for From
s)


ppSelectJoin :: Join -> Doc
ppSelectJoin :: Join -> Doc
ppSelectJoin Join
j = String -> Doc
text String
"SELECT *"
                 Doc -> Doc -> Doc
$$  String -> Doc
text String
"FROM"
                 Doc -> Doc -> Doc
$$  (Int, (Lateral, Select)) -> Doc
ppTable_tableAlias (Int
1, (Lateral, Select)
s1)
                 Doc -> Doc -> Doc
$$  JoinType -> Doc
ppJoinType (Join -> JoinType
Sql.jJoinType Join
j)
                 Doc -> Doc -> Doc
$$  (Int, (Lateral, Select)) -> Doc
ppTable_tableAlias (Int
2, (Lateral, Select)
s2)
                 Doc -> Doc -> Doc
$$  String -> Doc
text String
"ON"
                 Doc -> Doc -> Doc
$$  SqlExpr -> Doc
HPrint.ppSqlExpr (Join -> SqlExpr
Sql.jCond Join
j)
  where ((Lateral, Select)
s1, (Lateral, Select)
s2) = Join -> ((Lateral, Select), (Lateral, Select))
Sql.jTables Join
j

ppSelectSemijoin :: Semijoin -> Doc
ppSelectSemijoin :: Semijoin -> Doc
ppSelectSemijoin Semijoin
v =
  String -> Doc
text String
"SELECT *"
  Doc -> Doc -> Doc
$$  String -> Doc
text String
"FROM"
  Doc -> Doc -> Doc
$$  (String, Select) -> Doc
ppTable (Int -> Select -> (String, Select)
tableAlias Int
1 (Semijoin -> Select
Sql.sjTable Semijoin
v))
  Doc -> Doc -> Doc
$$  case Semijoin -> SemijoinType
Sql.sjType Semijoin
v of
        SemijoinType
Sql.Semi -> String -> Doc
text String
"WHERE EXISTS"
        SemijoinType
Sql.Anti -> String -> Doc
text String
"WHERE NOT EXISTS"
  Doc -> Doc -> Doc
$$ Doc -> Doc
parens (Select -> Doc
ppSql (Semijoin -> Select
Sql.sjCriteria Semijoin
v))

ppSelectValues :: Values -> Doc
ppSelectValues :: Values -> Doc
ppSelectValues Values
v = String -> Doc
text String
"SELECT"
                   Doc -> Doc -> Doc
<+> SelectAttrs -> Doc
ppAttrs (Values -> SelectAttrs
Sql.vAttrs Values
v)
                   Doc -> Doc -> Doc
$$  String -> Doc
text String
"FROM"
                   Doc -> Doc -> Doc
$$  [[SqlExpr]] -> Doc
ppValues (Values -> [[SqlExpr]]
Sql.vValues Values
v)

ppSelectBinary :: Binary -> Doc
ppSelectBinary :: Binary -> Doc
ppSelectBinary Binary
b = Select -> Doc
ppSql (Binary -> Select
Sql.bSelect1 Binary
b)
                   Doc -> Doc -> Doc
$$ BinOp -> Doc
ppBinOp (Binary -> BinOp
Sql.bOp Binary
b)
                   Doc -> Doc -> Doc
$$ Select -> Doc
ppSql (Binary -> Select
Sql.bSelect2 Binary
b)

ppSelectLabel :: Label -> Doc
ppSelectLabel :: Label -> Doc
ppSelectLabel Label
l = String -> Doc
text String
"/*" Doc -> Doc -> Doc
<+> String -> Doc
text (String -> String
preprocess (Label -> String
Sql.lLabel Label
l)) Doc -> Doc -> Doc
<+> String -> Doc
text String
"*/"
                  Doc -> Doc -> Doc
$$ Select -> Doc
ppSql (Label -> Select
Sql.lSelect Label
l)
  where
    preprocess :: String -> String
preprocess = String -> String
defuseComments (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
filter Char -> Bool
Data.Char.isPrint
    defuseComments :: String -> String
defuseComments = Text -> String
ST.unpack
                   (Text -> String) -> (String -> Text) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
ST.replace (String -> Text
ST.pack String
"--") (String -> Text
ST.pack String
" - - ")
                   (Text -> Text) -> (String -> Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
ST.replace (String -> Text
ST.pack String
"/*") (String -> Text
ST.pack String
" / * ")
                   (Text -> Text) -> (String -> Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
ST.replace (String -> Text
ST.pack String
"*/") (String -> Text
ST.pack String
" * / ")
                   (Text -> Text) -> (String -> Text) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
ST.pack

ppSelectExists :: Exists -> Doc
ppSelectExists :: Exists -> Doc
ppSelectExists Exists
e =
  String -> Doc
text String
"SELECT EXISTS"
  Doc -> Doc -> Doc
<+> (String, Select) -> Doc
ppTable (Symbol -> String
Sql.sqlSymbol (Exists -> Symbol
Sql.existsBinding Exists
e), Exists -> Select
Sql.existsTable Exists
e)

ppJoinType :: Sql.JoinType -> Doc
ppJoinType :: JoinType -> Doc
ppJoinType JoinType
Sql.LeftJoin = String -> Doc
text String
"LEFT OUTER JOIN"
ppJoinType JoinType
Sql.RightJoin = String -> Doc
text String
"RIGHT OUTER JOIN"
ppJoinType JoinType
Sql.FullJoin = String -> Doc
text String
"FULL OUTER JOIN"

ppAttrs :: Sql.SelectAttrs -> Doc
ppAttrs :: SelectAttrs -> Doc
ppAttrs SelectAttrs
Sql.Star                 = String -> Doc
text String
"*"
ppAttrs (Sql.SelectAttrs NonEmpty (SqlExpr, Maybe SqlColumn)
xs)     = (((SqlExpr, Maybe SqlColumn) -> Doc)
-> [(SqlExpr, Maybe SqlColumn)] -> Doc
forall a. (a -> Doc) -> [a] -> Doc
HPrint.commaV (SqlExpr, Maybe SqlColumn) -> Doc
nameAs ([(SqlExpr, Maybe SqlColumn)] -> Doc)
-> (NonEmpty (SqlExpr, Maybe SqlColumn)
    -> [(SqlExpr, Maybe SqlColumn)])
-> NonEmpty (SqlExpr, Maybe SqlColumn)
-> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty (SqlExpr, Maybe SqlColumn) -> [(SqlExpr, Maybe SqlColumn)]
forall a. NonEmpty a -> [a]
NEL.toList) NonEmpty (SqlExpr, Maybe SqlColumn)
xs
ppAttrs (Sql.SelectAttrsStar NonEmpty (SqlExpr, Maybe SqlColumn)
xs) =
  (Doc -> Doc) -> [Doc] -> Doc
forall a. (a -> Doc) -> [a] -> Doc
HPrint.commaV Doc -> Doc
forall a. a -> a
id ((((SqlExpr, Maybe SqlColumn) -> Doc)
-> [(SqlExpr, Maybe SqlColumn)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (SqlExpr, Maybe SqlColumn) -> Doc
nameAs ([(SqlExpr, Maybe SqlColumn)] -> [Doc])
-> (NonEmpty (SqlExpr, Maybe SqlColumn)
    -> [(SqlExpr, Maybe SqlColumn)])
-> NonEmpty (SqlExpr, Maybe SqlColumn)
-> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty (SqlExpr, Maybe SqlColumn) -> [(SqlExpr, Maybe SqlColumn)]
forall a. NonEmpty a -> [a]
NEL.toList) NonEmpty (SqlExpr, Maybe SqlColumn)
xs [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [String -> Doc
text String
"*"])

-- This is pretty much just nameAs from HaskellDB
nameAs :: (HSql.SqlExpr, Maybe HSql.SqlColumn) -> Doc
nameAs :: (SqlExpr, Maybe SqlColumn) -> Doc
nameAs (SqlExpr
expr, Maybe SqlColumn
name) = SqlExpr -> Doc
HPrint.ppSqlExpr SqlExpr
expr Doc -> Maybe String -> Doc
`ppAs` (SqlColumn -> String) -> Maybe SqlColumn -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SqlColumn -> String
unColumn Maybe SqlColumn
name
  where unColumn :: SqlColumn -> String
unColumn (HSql.SqlColumn String
s) = String
s

ppTables :: [(Sql.Lateral, Select)] -> Doc
ppTables :: [(Lateral, Select)] -> Doc
ppTables [] = Doc
empty
ppTables [(Lateral, Select)]
ts = String -> Doc
text String
"FROM" Doc -> Doc -> Doc
<+> ((Int, (Lateral, Select)) -> Doc)
-> [(Int, (Lateral, Select))] -> Doc
forall a. (a -> Doc) -> [a] -> Doc
HPrint.commaV (Int, (Lateral, Select)) -> Doc
ppTable_tableAlias ([Int] -> [(Lateral, Select)] -> [(Int, (Lateral, Select))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] [(Lateral, Select)]
ts)

ppTable_tableAlias :: (Int, (Sql.Lateral, Select)) -> Doc
ppTable_tableAlias :: (Int, (Lateral, Select)) -> Doc
ppTable_tableAlias (Int
i, (Lateral
lat, Select
select)) =
  Lateral -> Doc -> Doc
lateral Lateral
lat (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ (String, Select) -> Doc
ppTable (Int -> Select -> (String, Select)
tableAlias Int
i Select
select)
  where lateral :: Lateral -> Doc -> Doc
lateral = \case
          Lateral
Sql.NonLateral -> Doc -> Doc
forall a. a -> a
id
          Lateral
Sql.Lateral -> (String -> Doc
text String
"LATERAL" Doc -> Doc -> Doc
$$)

tableAlias :: Int -> Select -> (TableAlias, Select)
tableAlias :: Int -> Select -> (String, Select)
tableAlias Int
i Select
select = (String
"T" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i, Select
select)

-- TODO: duplication with ppSql
ppTable :: (TableAlias, Select) -> Doc
ppTable :: (String, Select) -> Doc
ppTable (String
alias, Select
select) = case Select
select of
  Table SqlTable
table           -> SqlTable -> Doc
HPrint.ppTable SqlTable
table
  RelExpr SqlExpr
expr          -> SqlExpr -> Doc
HPrint.ppSqlExpr SqlExpr
expr
  SelectFrom From
selectFrom -> Doc -> Doc
parens (From -> Doc
ppSelectFrom From
selectFrom)
  SelectJoin Join
slj        -> Doc -> Doc
parens (Join -> Doc
ppSelectJoin Join
slj)
  SelectSemijoin Semijoin
slj    -> Doc -> Doc
parens (Semijoin -> Doc
ppSelectSemijoin Semijoin
slj)
  SelectValues Values
slv      -> Doc -> Doc
parens (Values -> Doc
ppSelectValues Values
slv)
  SelectBinary Binary
slb      -> Doc -> Doc
parens (Binary -> Doc
ppSelectBinary Binary
slb)
  SelectLabel Label
sll       -> Doc -> Doc
parens (Label -> Doc
ppSelectLabel Label
sll)
  SelectExists Exists
saj      -> Doc -> Doc
parens (Exists -> Doc
ppSelectExists Exists
saj)
  Doc -> Maybe String -> Doc
`ppAs`
  String -> Maybe String
forall a. a -> Maybe a
Just String
alias

ppGroupBy :: Maybe (NEL.NonEmpty HSql.SqlExpr) -> Doc
ppGroupBy :: Maybe (NonEmpty SqlExpr) -> Doc
ppGroupBy Maybe (NonEmpty SqlExpr)
Nothing   = Doc
empty
ppGroupBy (Just NonEmpty SqlExpr
xs) = [SqlExpr] -> Doc
HPrint.ppGroupBy (NonEmpty SqlExpr -> [SqlExpr]
forall a. NonEmpty a -> [a]
NEL.toList NonEmpty SqlExpr
xs)

ppLimit :: Maybe Int -> Doc
ppLimit :: Maybe Int -> Doc
ppLimit Maybe Int
Nothing = Doc
empty
ppLimit (Just Int
n) = String -> Doc
text (String
"LIMIT " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n)

ppOffset :: Maybe Int -> Doc
ppOffset :: Maybe Int -> Doc
ppOffset Maybe Int
Nothing = Doc
empty
ppOffset (Just Int
n) = String -> Doc
text (String
"OFFSET " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n)

ppFor :: Maybe Sql.LockStrength -> Doc
ppFor :: Maybe LockStrength -> Doc
ppFor Maybe LockStrength
Nothing       = Doc
empty
ppFor (Just LockStrength
Sql.Update) = String -> Doc
text String
"FOR UPDATE"

ppValues :: [[HSql.SqlExpr]] -> Doc
ppValues :: [[SqlExpr]] -> Doc
ppValues [[SqlExpr]]
v = Doc -> Doc
parens ([[SqlExpr]] -> Doc
HPrint.ppValues_ [[SqlExpr]]
v) Doc -> Maybe String -> Doc
`ppAs` String -> Maybe String
forall a. a -> Maybe a
Just String
"V"

ppBinOp :: Sql.BinOp -> Doc
ppBinOp :: BinOp -> Doc
ppBinOp BinOp
o = String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ case BinOp
o of
  BinOp
Sql.Union        -> String
"UNION"
  BinOp
Sql.UnionAll     -> String
"UNION ALL"
  BinOp
Sql.Except       -> String
"EXCEPT"
  BinOp
Sql.ExceptAll    -> String
"EXCEPT ALL"
  BinOp
Sql.Intersect    -> String
"INTERSECT"
  BinOp
Sql.IntersectAll -> String
"INTERSECT ALL"

ppInsertReturning :: Sql.Returning HSql.SqlInsert -> Doc
ppInsertReturning :: Returning SqlInsert -> Doc
ppInsertReturning (Sql.Returning SqlInsert
insert NonEmpty SqlExpr
returnExprs) =
  SqlInsert -> Doc
HPrint.ppInsert SqlInsert
insert
  Doc -> Doc -> Doc
$$ String -> Doc
text String
"RETURNING"
  Doc -> Doc -> Doc
<+> (SqlExpr -> Doc) -> [SqlExpr] -> Doc
forall a. (a -> Doc) -> [a] -> Doc
HPrint.commaV SqlExpr -> Doc
HPrint.ppSqlExpr (NonEmpty SqlExpr -> [SqlExpr]
forall a. NonEmpty a -> [a]
NEL.toList NonEmpty SqlExpr
returnExprs)

ppUpdateReturning :: Sql.Returning HSql.SqlUpdate -> Doc
ppUpdateReturning :: Returning SqlUpdate -> Doc
ppUpdateReturning (Sql.Returning SqlUpdate
update NonEmpty SqlExpr
returnExprs) =
  SqlUpdate -> Doc
HPrint.ppUpdate SqlUpdate
update
  Doc -> Doc -> Doc
$$ String -> Doc
text String
"RETURNING"
  Doc -> Doc -> Doc
<+> (SqlExpr -> Doc) -> [SqlExpr] -> Doc
forall a. (a -> Doc) -> [a] -> Doc
HPrint.commaV SqlExpr -> Doc
HPrint.ppSqlExpr (NonEmpty SqlExpr -> [SqlExpr]
forall a. NonEmpty a -> [a]
NEL.toList NonEmpty SqlExpr
returnExprs)

ppDeleteReturning :: Sql.Returning HSql.SqlDelete -> Doc
ppDeleteReturning :: Returning SqlDelete -> Doc
ppDeleteReturning (Sql.Returning SqlDelete
delete NonEmpty SqlExpr
returnExprs) =
  SqlDelete -> Doc
HPrint.ppDelete SqlDelete
delete
  Doc -> Doc -> Doc
$$ String -> Doc
text String
"RETURNING"
  Doc -> Doc -> Doc
<+> (SqlExpr -> Doc) -> [SqlExpr] -> Doc
forall a. (a -> Doc) -> [a] -> Doc
HPrint.commaV SqlExpr -> Doc
HPrint.ppSqlExpr (NonEmpty SqlExpr -> [SqlExpr]
forall a. NonEmpty a -> [a]
NEL.toList NonEmpty SqlExpr
returnExprs)

-- * Bits from "Opaleye.Sql".  They don't really belong here but I
-- * have to put them somewhere.

formatAndShowSQL :: ([HPQ.PrimExpr], PQ.PrimQuery' a, T.Tag) -> Maybe String
formatAndShowSQL :: ([PrimExpr], PrimQuery' a, Tag) -> Maybe String
formatAndShowSQL = (([PrimExpr], PrimQuery' Void, Tag) -> String)
-> Maybe ([PrimExpr], PrimQuery' Void, Tag) -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Doc -> String
forall a. Show a => a -> String
show (Doc -> String)
-> (([PrimExpr], PrimQuery' Void, Tag) -> Doc)
-> ([PrimExpr], PrimQuery' Void, Tag)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Select -> Doc
ppSql (Select -> Doc)
-> (([PrimExpr], PrimQuery' Void, Tag) -> Select)
-> ([PrimExpr], PrimQuery' Void, Tag)
-> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([PrimExpr], PrimQuery' Void, Tag) -> Select
Sql.sql) (Maybe ([PrimExpr], PrimQuery' Void, Tag) -> Maybe String)
-> (([PrimExpr], PrimQuery' a, Tag)
    -> Maybe ([PrimExpr], PrimQuery' Void, Tag))
-> ([PrimExpr], PrimQuery' a, Tag)
-> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PrimQuery' a -> Maybe (PrimQuery' Void))
-> ([PrimExpr], PrimQuery' a, Tag)
-> Maybe ([PrimExpr], PrimQuery' Void, Tag)
forall (f :: * -> *) a b x y.
Functor f =>
(a -> f b) -> (x, a, y) -> f (x, b, y)
traverse2Of3 PrimQuery' a -> Maybe (PrimQuery' Void)
forall a b. PrimQuery' a -> Maybe (PrimQuery' b)
Op.removeEmpty
  where -- Just a lens
        traverse2Of3 :: Functor f => (a -> f b) -> (x, a, y) -> f (x, b, y)
        traverse2Of3 :: (a -> f b) -> (x, a, y) -> f (x, b, y)
traverse2Of3 a -> f b
f (x
x, a
y, y
z) = (b -> (x, b, y)) -> f b -> f (x, b, y)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\b
y' -> (x
x, b
y', y
z)) (a -> f b
f a
y)