/compiler/GHC/Utils/FV.hs

https://github.com/bgamari/ghc · Haskell · 199 lines · 59 code · 25 blank · 115 comment · 1 complexity · 59ce2342b6ba4323159bf08425e66167 MD5 · raw file

  1. {-
  2. (c) Bartosz Nitka, Facebook 2015
  3. -}
  4. {-# LANGUAGE BangPatterns #-}
  5. -- | Utilities for efficiently and deterministically computing free variables.
  6. module GHC.Utils.FV (
  7. -- * Deterministic free vars computations
  8. FV, InterestingVarFun,
  9. -- * Running the computations
  10. fvVarList, fvVarSet, fvDVarSet,
  11. -- ** Manipulating those computations
  12. unitFV,
  13. emptyFV,
  14. mkFVs,
  15. unionFV,
  16. unionsFV,
  17. delFV,
  18. delFVs,
  19. filterFV,
  20. mapUnionFV,
  21. ) where
  22. import GHC.Prelude
  23. import GHC.Types.Var
  24. import GHC.Types.Var.Set
  25. -- | Predicate on possible free variables: returns @True@ iff the variable is
  26. -- interesting
  27. type InterestingVarFun = Var -> Bool
  28. -- Note [Deterministic FV]
  29. -- ~~~~~~~~~~~~~~~~~~~~~~~
  30. -- When computing free variables, the order in which you get them affects
  31. -- the results of floating and specialization. If you use UniqFM to collect
  32. -- them and then turn that into a list, you get them in nondeterministic
  33. -- order as described in Note [Deterministic UniqFM] in GHC.Types.Unique.DFM.
  34. -- A naive algorithm for free variables relies on merging sets of variables.
  35. -- Merging costs O(n+m) for UniqFM and for UniqDFM there's an additional log
  36. -- factor. It's cheaper to incrementally add to a list and use a set to check
  37. -- for duplicates.
  38. type FV = InterestingVarFun -- Used for filtering sets as we build them
  39. -> VarSet -- Locally bound variables
  40. -> VarAcc -- Accumulator
  41. -> VarAcc
  42. type VarAcc = ([Var], VarSet) -- List to preserve ordering and set to check for membership,
  43. -- so that the list doesn't have duplicates
  44. -- For explanation of why using `VarSet` is not deterministic see
  45. -- Note [Deterministic UniqFM] in GHC.Types.Unique.DFM.
  46. -- Note [FV naming conventions]
  47. -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  48. -- To get the performance and determinism that FV provides, FV computations
  49. -- need to built up from smaller FV computations and then evaluated with
  50. -- one of `fvVarList`, `fvDVarSet` That means the functions
  51. -- returning FV need to be exported.
  52. --
  53. -- The conventions are:
  54. --
  55. -- a) non-deterministic functions:
  56. -- * a function that returns VarSet
  57. -- e.g. `tyVarsOfType`
  58. -- b) deterministic functions:
  59. -- * a worker that returns FV
  60. -- e.g. `tyFVsOfType`
  61. -- * a function that returns [Var]
  62. -- e.g. `tyVarsOfTypeList`
  63. -- * a function that returns DVarSet
  64. -- e.g. `tyVarsOfTypeDSet`
  65. --
  66. -- Where tyVarsOfType, tyVarsOfTypeList, tyVarsOfTypeDSet are implemented
  67. -- in terms of the worker evaluated with fvVarSet, fvVarList, fvDVarSet
  68. -- respectively.
  69. -- | Run a free variable computation, returning a list of distinct free
  70. -- variables in deterministic order and a non-deterministic set containing
  71. -- those variables.
  72. fvVarAcc :: FV -> ([Var], VarSet)
  73. fvVarAcc fv = fv (const True) emptyVarSet ([], emptyVarSet)
  74. -- | Run a free variable computation, returning a list of distinct free
  75. -- variables in deterministic order.
  76. fvVarList :: FV -> [Var]
  77. fvVarList = fst . fvVarAcc
  78. -- | Run a free variable computation, returning a deterministic set of free
  79. -- variables. Note that this is just a wrapper around the version that
  80. -- returns a deterministic list. If you need a list you should use
  81. -- `fvVarList`.
  82. fvDVarSet :: FV -> DVarSet
  83. fvDVarSet = mkDVarSet . fvVarList
  84. -- | Run a free variable computation, returning a non-deterministic set of
  85. -- free variables. Don't use if the set will be later converted to a list
  86. -- and the order of that list will impact the generated code.
  87. fvVarSet :: FV -> VarSet
  88. fvVarSet = snd . fvVarAcc
  89. -- Note [FV eta expansion]
  90. -- ~~~~~~~~~~~~~~~~~~~~~~~
  91. -- Let's consider an eta-reduced implementation of freeVarsOf using FV:
  92. --
  93. -- freeVarsOf (App a b) = freeVarsOf a `unionFV` freeVarsOf b
  94. --
  95. -- If GHC doesn't eta-expand it, after inlining unionFV we end up with
  96. --
  97. -- freeVarsOf = \x ->
  98. -- case x of
  99. -- App a b -> \fv_cand in_scope acc ->
  100. -- freeVarsOf a fv_cand in_scope $! freeVarsOf b fv_cand in_scope $! acc
  101. --
  102. -- which has to create a thunk, resulting in more allocations.
  103. --
  104. -- On the other hand if it is eta-expanded:
  105. --
  106. -- freeVarsOf (App a b) fv_cand in_scope acc =
  107. -- (freeVarsOf a `unionFV` freeVarsOf b) fv_cand in_scope acc
  108. --
  109. -- after inlining unionFV we have:
  110. --
  111. -- freeVarsOf = \x fv_cand in_scope acc ->
  112. -- case x of
  113. -- App a b ->
  114. -- freeVarsOf a fv_cand in_scope $! freeVarsOf b fv_cand in_scope $! acc
  115. --
  116. -- which saves allocations.
  117. --
  118. -- GHC when presented with knowledge about all the call sites, correctly
  119. -- eta-expands in this case. Unfortunately due to the fact that freeVarsOf gets
  120. -- exported to be composed with other functions, GHC doesn't have that
  121. -- information and has to be more conservative here.
  122. --
  123. -- Hence functions that get exported and return FV need to be manually
  124. -- eta-expanded. See also #11146.
  125. -- | Add a variable - when free, to the returned free variables.
  126. -- Ignores duplicates and respects the filtering function.
  127. unitFV :: Id -> FV
  128. unitFV var fv_cand in_scope acc@(have, haveSet)
  129. | var `elemVarSet` in_scope = acc
  130. | var `elemVarSet` haveSet = acc
  131. | fv_cand var = (var:have, extendVarSet haveSet var)
  132. | otherwise = acc
  133. {-# INLINE unitFV #-}
  134. -- | Return no free variables.
  135. emptyFV :: FV
  136. emptyFV _ _ acc = acc
  137. {-# INLINE emptyFV #-}
  138. -- | Union two free variable computations.
  139. unionFV :: FV -> FV -> FV
  140. unionFV fv1 fv2 fv_cand in_scope acc =
  141. fv1 fv_cand in_scope $! fv2 fv_cand in_scope $! acc
  142. {-# INLINE unionFV #-}
  143. -- | Mark the variable as not free by putting it in scope.
  144. delFV :: Var -> FV -> FV
  145. delFV var fv fv_cand !in_scope acc =
  146. fv fv_cand (extendVarSet in_scope var) acc
  147. {-# INLINE delFV #-}
  148. -- | Mark many free variables as not free.
  149. delFVs :: VarSet -> FV -> FV
  150. delFVs vars fv fv_cand !in_scope acc =
  151. fv fv_cand (in_scope `unionVarSet` vars) acc
  152. {-# INLINE delFVs #-}
  153. -- | Filter a free variable computation.
  154. filterFV :: InterestingVarFun -> FV -> FV
  155. filterFV fv_cand2 fv fv_cand1 in_scope acc =
  156. fv (\v -> fv_cand1 v && fv_cand2 v) in_scope acc
  157. {-# INLINE filterFV #-}
  158. -- | Map a free variable computation over a list and union the results.
  159. mapUnionFV :: (a -> FV) -> [a] -> FV
  160. mapUnionFV _f [] _fv_cand _in_scope acc = acc
  161. mapUnionFV f (a:as) fv_cand in_scope acc =
  162. mapUnionFV f as fv_cand in_scope $! f a fv_cand in_scope $! acc
  163. {-# INLINABLE mapUnionFV #-}
  164. -- | Union many free variable computations.
  165. unionsFV :: [FV] -> FV
  166. unionsFV fvs fv_cand in_scope acc = mapUnionFV id fvs fv_cand in_scope acc
  167. {-# INLINE unionsFV #-}
  168. -- | Add multiple variables - when free, to the returned free variables.
  169. -- Ignores duplicates and respects the filtering function.
  170. mkFVs :: [Var] -> FV
  171. mkFVs vars fv_cand in_scope acc =
  172. mapUnionFV unitFV vars fv_cand in_scope acc
  173. {-# INLINE mkFVs #-}