/compiler/Eta/Utils/FV.hs

https://github.com/typelead/eta · Haskell · 210 lines · 66 code · 24 blank · 120 comment · 1 complexity · 15dba1a7dbcd917d39a86481e4cf31f9 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 Eta.Utils.FV (
  7. -- * Deterministic free vars computations
  8. FV, InterestingVarFun,
  9. -- * Running the computations
  10. fvVarListVarSet, fvVarList, fvVarSet, fvDVarSet,
  11. -- ** Manipulating those computations
  12. oneVar,
  13. unitFV,
  14. emptyFV,
  15. mkFVs,
  16. unionFV,
  17. unionsFV,
  18. delFV,
  19. delFVs,
  20. filterFV,
  21. mapUnionFV,
  22. ) where
  23. import Eta.BasicTypes.Var
  24. import Eta.BasicTypes.VarSet
  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 UniqDFM.
  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
  39. -- Used for filtering sets as we build them
  40. -> VarSet
  41. -- Locally bound variables
  42. -> ([Var], VarSet)
  43. -- List to preserve ordering and set to check for membership,
  44. -- so that the list doesn't have duplicates
  45. -- For explanation of why using `VarSet` is not deterministic see
  46. -- Note [Deterministic UniqFM] in UniqDFM.
  47. -> ([Var], VarSet)
  48. -- Note [FV naming conventions]
  49. -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  50. -- To get the performance and determinism that FV provides, FV computations
  51. -- need to built up from smaller FV computations and then evaluated with
  52. -- one of `fvVarList`, `fvDVarSet`, `fvVarListVarSet`. That means the functions
  53. -- returning FV need to be exported.
  54. --
  55. -- The conventions are:
  56. --
  57. -- a) non-deterministic functions:
  58. -- * a function that returns VarSet
  59. -- e.g. `tyVarsOfType`
  60. -- b) deterministic functions:
  61. -- * a worker that returns FV
  62. -- e.g. `tyFVsOfType`
  63. -- * a function that returns [Var]
  64. -- e.g. `tyVarsOfTypeList`
  65. -- * a function that returns DVarSet
  66. -- e.g. `tyVarsOfTypeDSet`
  67. --
  68. -- Where tyVarsOfType, tyVarsOfTypeList, tyVarsOfTypeDSet are implemented
  69. -- in terms of the worker evaluated with fvVarSet, fvVarList, fvDVarSet
  70. -- respectively.
  71. -- | Run a free variable computation, returning a list of distinct free
  72. -- variables in deterministic order and a non-deterministic set containing
  73. -- those variables.
  74. fvVarListVarSet :: FV -> ([Var], VarSet)
  75. fvVarListVarSet fv = fv (const True) emptyVarSet ([], emptyVarSet)
  76. -- | Run a free variable computation, returning a list of distinct free
  77. -- variables in deterministic order.
  78. fvVarList :: FV -> [Var]
  79. fvVarList = fst . fvVarListVarSet
  80. -- | Run a free variable computation, returning a deterministic set of free
  81. -- variables. Note that this is just a wrapper around the version that
  82. -- returns a deterministic list. If you need a list you should use
  83. -- `fvVarList`.
  84. fvDVarSet :: FV -> DVarSet
  85. fvDVarSet = mkDVarSet . fst . fvVarListVarSet
  86. -- | Run a free variable computation, returning a non-deterministic set of
  87. -- free variables. Don't use if the set will be later converted to a list
  88. -- and the order of that list will impact the generated code.
  89. fvVarSet :: FV -> VarSet
  90. fvVarSet = snd . fvVarListVarSet
  91. -- Note [FV eta expansion]
  92. -- ~~~~~~~~~~~~~~~~~~~~~~~
  93. -- Let's consider an eta-reduced implementation of freeVarsOf using FV:
  94. --
  95. -- freeVarsOf (App a b) = freeVarsOf a `unionFV` freeVarsOf b
  96. --
  97. -- If GHC doesn't eta-expand it, after inlining unionFV we end up with
  98. --
  99. -- freeVarsOf = \x ->
  100. -- case x of
  101. -- App a b -> \fv_cand in_scope acc ->
  102. -- freeVarsOf a fv_cand in_scope $! freeVarsOf b fv_cand in_scope $! acc
  103. --
  104. -- which has to create a thunk, resulting in more allocations.
  105. --
  106. -- On the other hand if it is eta-expanded:
  107. --
  108. -- freeVarsOf (App a b) fv_cand in_scope acc =
  109. -- (freeVarsOf a `unionFV` freeVarsOf b) fv_cand in_scope acc
  110. --
  111. -- after inlining unionFV we have:
  112. --
  113. -- freeVarsOf = \x fv_cand in_scope acc ->
  114. -- case x of
  115. -- App a b ->
  116. -- freeVarsOf a fv_cand in_scope $! freeVarsOf b fv_cand in_scope $! acc
  117. --
  118. -- which saves allocations.
  119. --
  120. -- GHC when presented with knowledge about all the call sites, correctly
  121. -- eta-expands in this case. Unfortunately due to the fact that freeVarsOf gets
  122. -- exported to be composed with other functions, GHC doesn't have that
  123. -- information and has to be more conservative here.
  124. --
  125. -- Hence functions that get exported and return FV need to be manually
  126. -- eta-expanded. See also #11146.
  127. -- | Add a variable - when free, to the returned free variables.
  128. -- Ignores duplicates and respects the filtering function.
  129. unitFV :: Id -> FV
  130. unitFV var fv_cand in_scope acc@(have, haveSet)
  131. | var `elemVarSet` in_scope = acc
  132. | var `elemVarSet` haveSet = acc
  133. | fv_cand var = (var:have, extendVarSet haveSet var)
  134. | otherwise = acc
  135. {-# INLINE unitFV #-}
  136. -- | Return no free variables.
  137. emptyFV :: FV
  138. emptyFV _ _ acc = acc
  139. {-# INLINE emptyFV #-}
  140. -- | Union two free variable computations.
  141. unionFV :: FV -> FV -> FV
  142. unionFV fv1 fv2 fv_cand in_scope acc =
  143. fv1 fv_cand in_scope $! fv2 fv_cand in_scope $! acc
  144. {-# INLINE unionFV #-}
  145. -- | Mark the variable as not free by putting it in scope.
  146. delFV :: Var -> FV -> FV
  147. delFV var fv fv_cand !in_scope acc =
  148. fv fv_cand (extendVarSet in_scope var) acc
  149. {-# INLINE delFV #-}
  150. -- | Mark many free variables as not free.
  151. delFVs :: VarSet -> FV -> FV
  152. delFVs vars fv fv_cand !in_scope acc =
  153. fv fv_cand (in_scope `unionVarSet` vars) acc
  154. {-# INLINE delFVs #-}
  155. -- | Filter a free variable computation.
  156. filterFV :: InterestingVarFun -> FV -> FV
  157. filterFV fv_cand2 fv fv_cand1 in_scope acc =
  158. fv (\v -> fv_cand1 v && fv_cand2 v) in_scope acc
  159. {-# INLINE filterFV #-}
  160. -- | Map a free variable computation over a list and union the results.
  161. mapUnionFV :: (a -> FV) -> [a] -> FV
  162. mapUnionFV _f [] _fv_cand _in_scope acc = acc
  163. mapUnionFV f (a:as) fv_cand in_scope acc =
  164. mapUnionFV f as fv_cand in_scope $! f a fv_cand in_scope $! acc
  165. {-# INLINABLE mapUnionFV #-}
  166. -- | Union many free variable computations.
  167. unionsFV :: [FV] -> FV
  168. unionsFV fvs fv_cand in_scope acc = mapUnionFV id fvs fv_cand in_scope acc
  169. {-# INLINE unionsFV #-}
  170. -- | Add multiple variables - when free, to the returned free variables.
  171. -- Ignores duplicates and respects the filtering function.
  172. mkFVs :: [Var] -> FV
  173. mkFVs vars fv_cand in_scope acc =
  174. mapUnionFV unitFV vars fv_cand in_scope acc
  175. {-# INLINE mkFVs #-}
  176. {-# INLINE oneVar #-}
  177. oneVar :: Id -> FV
  178. oneVar var fv_cand in_scope acc@(have, haveSet)
  179. = {- ASSERT( isId var ) probably not going to work -} fvs
  180. where
  181. fvs | var `elemVarSet` in_scope = acc
  182. | var `elemVarSet` haveSet = acc
  183. | fv_cand var = (var:have, extendVarSet haveSet var)
  184. | otherwise = acc