Skip to content

Commit

Permalink
Remove unnecessary type parameter and langauge extension
Browse files Browse the repository at this point in the history
Summary: Just some house cleaning.

Reviewed By: phlalx

Differential Revision: D59472179

fbshipit-source-id: a73787c4ebbf6894d19c76e2d51d74c6cb09d701
  • Loading branch information
Josef Svenningsson authored and facebook-github-bot committed Jul 9, 2024
1 parent 806b567 commit b11c19e
Showing 1 changed file with 10 additions and 10 deletions.
20 changes: 10 additions & 10 deletions glean/db/Glean/Query/Codegen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
LICENSE file in the root directory of this source tree.
-}

{-# LANGUAGE RecursiveDo, DeriveTraversable #-}
{-# LANGUAGE RecursiveDo #-}
module Glean.Query.Codegen
( compileQuery
, compileQueryFacts
Expand Down Expand Up @@ -409,10 +409,10 @@ compileTermGen term vars maybeReg andThen = do
andThen

compileStatements
:: forall a s
:: forall a
. QueryTransformations
-> Boundaries
-> QueryRegs s
-> QueryRegs
-> [CgStatement]
-> Vector (Register 'Word) -- ^ registers for variables
-> Code a -- ^ @andThen@: code to insert after
Expand All @@ -421,7 +421,7 @@ compileStatements
compileStatements
qtrans
bounds
regs@(QueryRegs{..} :: QueryRegs s)
regs@QueryRegs{..}
stmts
vars
andThen =
Expand Down Expand Up @@ -909,10 +909,10 @@ matchDef fail ty pat =
matchPat (Bytes start end) fail (preProcessPat pat)

compileFactGenerator
:: forall a s
:: forall a
. Maybe PredicateTransformation
-> Boundaries
-> QueryRegs s
-> QueryRegs
-> Vector (Register 'Word) -- ^ registers for variables
-> Pid
-> Pat
Expand All @@ -921,7 +921,7 @@ compileFactGenerator
-> Maybe (Register 'Word)
-> Code a
-> Code a
compileFactGenerator mtrans bounds (QueryRegs{..} :: QueryRegs s)
compileFactGenerator mtrans bounds QueryRegs{..}
vars pid kpat vpat section maybeReg inner = mdo
let etrans = maybe (Left pid) Right mtrans
withPatterns etrans vars kpat vpat $
Expand Down Expand Up @@ -1343,7 +1343,7 @@ withTerm vars term action = do
-- for as long as it keeps adding facts to the Define.
--
recursive
:: QueryRegs s
:: QueryRegs
-> (forall a. Code a -> Code a) -- ^ code for first run
-> (forall a. Code a -> Code a) -- ^ code to evaluate repeatedly
-> Code b -- ^ code to insert after
Expand Down Expand Up @@ -1544,7 +1544,7 @@ compileQueryFacts facts = do
-- IF YOU ALSO BREAK FORWARD COMPATIBILITY, BUMP latestSupportedVersion AS WELL
--

data QueryRegs s = QueryRegs
data QueryRegs = QueryRegs
{
-- | Start a new traversal of facts beginning with a given prefix
seek
Expand Down Expand Up @@ -1632,7 +1632,7 @@ data QueryRegs s = QueryRegs
}

generateQueryCode
:: (forall s . QueryRegs s -> Code ())
:: (QueryRegs -> Code ())
-> IO (Meta, Subroutine CompiledQuery)
generateQueryCode f = generate Optimised $
\ seek_ seekWithinSection_ currentSeek_ endSeek_ next_
Expand Down

0 comments on commit b11c19e

Please sign in to comment.