/compiler/utils/FV.hs

http://github.com/ghc/ghc · Haskell · 199 lines · 57 code · 23 blank · 119 comment · 1 complexity · 3634357de4f72da1d7986e5d659796c2 MD5 · raw file

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