[commit: ghc] master: Commets on flatten_args_tc (fda2ea5)

git at git.haskell.org git at git.haskell.org
Fri Aug 31 18:05:50 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/fda2ea5830176236380a6976dfd0d5802395c6a9/ghc

>---------------------------------------------------------------

commit fda2ea5830176236380a6976dfd0d5802395c6a9
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Aug 30 11:55:31 2018 +0100

    Commets on flatten_args_tc


>---------------------------------------------------------------

fda2ea5830176236380a6976dfd0d5802395c6a9
 compiler/typecheck/TcFlatten.hs | 15 +++++++++++----
 1 file changed, 11 insertions(+), 4 deletions(-)

diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs
index 79ffc4d..4129b87 100644
--- a/compiler/typecheck/TcFlatten.hs
+++ b/compiler/typecheck/TcFlatten.hs
@@ -1129,10 +1129,17 @@ TODO: a step-by-step replay of the refactor to analyze the performance.
 -}
 
 {-# INLINE flatten_args_tc #-}
-flatten_args_tc :: TyCon
-                -> [Role]
-                -> [Type]
-                -> FlatM ([Xi], [Coercion], CoercionN)
+flatten_args_tc
+  :: TyCon         -- T
+  -> [Role]        -- Role r
+  -> [Type]        -- Arg types [t1,..,tn]
+  -> FlatM ( [Xi]  -- List of flattened args [x1,..,xn]
+                   -- 1-1 corresp with [t1,..,tn]
+           , [Coercion]  -- List of arg coercions [co1,..,con]
+                         -- 1-1 corresp with [t1,..,tn]
+                         --    coi :: xi ~r ti
+           , CoercionN)  -- Result coercion, rco
+                         --    rco : (T t1..tn) ~N (T (x1 |> co1) .. (xn |> con))
 flatten_args_tc tc = flatten_args all_bndrs any_named_bndrs inner_ki emptyVarSet
   -- NB: TyCon kinds are always closed
   where



More information about the ghc-commits mailing list