[prev in list] [next in list] [prev in thread] [next in thread] 

List:       haskell-jhc
Subject:    [jhc] darcs patch: fix bug where the static argument transf... (and
From:       John Meacham <john () repetae ! net>
Date:       2010-12-07 3:43:10
Message-ID: 20101207034310.F02FB1C002 () sliver ! repetae ! net
[Download RAW message or body]

Mon Dec  6 19:15:57 PST 2010  John Meacham <john@repetae.net>
  * fix bug where the static argument transformation would clear rules. cle=
an up a lot of code.

Mon Dec  6 19:33:58 PST 2010  John Meacham <john@repetae.net>
  * remove quadratic behavior in programSetDs'

["fix-bug-where-the-static-argument-transformation-would-clear-rules_-clean-up-a-lot-of-code_.dpatch" (text/x-darcs-patch)]

New patches:

[fix bug where the static argument transformation would clear rules. clean up a lot \
of code. John Meacham <john@repetae.net>**20101207031557
 Ignore-this: a78a8819ac6728d331b9a01e9a665152
] hunk ./src/E/Inline.hs 6
     programMapRecGroups,
     forceInline,
     programDecomposedDs,
+    programDecomposedCombs,
     programMapProgGroups,
     forceNoinline,
     baseInlinability
hunk ./src/E/Inline.hs 29
 import Util.SetLike
 import qualified FlagOpts as FO
 
-
-
-
-
 -- | higher numbers mean we want to inline it more
 baseInlinability t e
     | forceNoinline t = -15
hunk ./src/E/LambdaLift.hs 48
 
 staticArgumentTransform :: Program -> Program
 staticArgumentTransform prog = ans where
-    ans = programSetDs (concat ds') prog { progStats = progStats prog `mappend` \
                nstat }
-    (ds',nstat) = runStatM $ mapM (f True) (programDecomposedDs prog)
+    ans = progCombinators_s (concat ds') prog { progStats = progStats prog `mappend` \
nstat } +    (ds',nstat) = runStatM $ mapM h (programDecomposedCombs prog)
+    h (True,[comb]) = do [(_,nb)] <- f True (Right [(combHead comb, combBody \
comb)]); return [combBody_s nb comb] +    h (_,cs) = do
+        forM cs $ \ c -> do
+            e' <- g (combBody c)
+            return (combBody_s e' c)
     f _ (Left (t,e)) = gds [(t,e)]
     f always (Right [(t,v@ELam {})]) | not (null collectApps), always || dropArgs > \
0 = ans where  nname = annotateId "R@" (tvrIdent t)
hunk ./src/E/LambdaLift.hs 172
     fc <- newIORef []
     fm <- newIORef mempty
     statRef <- newIORef mempty
-    let z comb  = do      
+    let z comb  = do
             (n,as,v) <- return $ combTriple comb
             let ((v',(cs',rm)),stat) = runReader (runStatT $ execUniqT 1 $ \
runWriterT (f v)) S { funcName = mkFuncName (tvrIdent n), topVars = wp,isStrict = \
True, declEnv = [] }  modifyIORef statRef (mappend stat)
hunk ./src/E/Main.hs 87
         reRule comb = combRules_u f comb where
             f rs = List.union  rs [ x | x <- nrules, ruleHead x == combHead comb]
 
-    let finalVarMap = mappend (fromList [(tvrIdent tvr,Just $ EVar tvr) | tvr <- map \
                combHead $ values choCombs ]) (choVarMap accumho)
-        choCombs = sfilter (\(k,_) -> k /= emptyId) choCombinators'
+    let choCombs = sfilter (\(k,_) -> k /= emptyId) choCombinators'
     return $ updateChoHo mempty {
hunk ./src/E/Main.hs 89
-        choVarMap = finalVarMap,
         choExternalNames = choExternalNames accumho `mappend` (fromList . map \
                tvrIdent $ newTVrs),
         choCombinators = choCombs `mappend` fmap reRule (choCombinators accumho),
         choHoMap = Map.singleton (hoModuleGroup aho) aho `mappend` choHoMap accumho
hunk ./src/E/Main.hs 156
             Nothing -> c
             Just rs -> combRules_u (map ruleUpdate . List.union rs) c
     prog <- return $ progCombinators_u (map addRule) prog
-    cho <- return $ choCombinators_u (fmap addRule) cho
+    cho <- return $ updateChoHo $ choCombinators_u (fmap addRule) cho
 
     -- Here we substitute in all the original types, with rules and properties \
                defined in the current module included
     prog <- return $ runIdentity $ annotateProgram (choVarMap cho) (idann theProps) \
letann lamann prog hunk ./src/E/Main.hs 163
 
     lintCheckProgram (putErrLn "LintPostProcess") prog
 
-
-
     let entryPoints = fromList . execWriter $ programMapDs_ (\ (t,_) -> when \
(getProperty prop_EXPORTED t || getProperty prop_INSTANCE t || getProperty \
                prop_SPECIALIZATION t)  (tell [tvrIdent t])) prog
     prog <- return $ prog { progEntry = entryPoints `mappend` progSeasoning prog }
 
hunk ./src/E/Main.hs 170
 
     prog <- programPrune prog
 
-
     -- initial pass, performs
     -- eta expansion of definitons
     -- simplify
hunk ./src/E/Main.hs 201
         when coreMini $ putErrLn ("----\n" ++ names)
         let tparms = transformParms { transformPass = "Init", transformDumpProgress \
= coreMini }  
-
         lintCheckProgram onerrNone mprog
         mprog <- evaluate $ etaAnnotateProgram mprog
         lintCheckProgram onerrNone mprog
hunk ./src/E/Main.hs 211
         mprog <- transformProgram tparms { transformSkipNoStats = True, \
                transformCategory = "SimpleRecursive"
                                          , transformOperation = return . \
staticArgumentTransform } mprog  
+        mprog <- transformProgram tparms { transformCategory = "FloatOutward", \
                transformOperation = floatOutward } mprog
         mprog <- transformProgram tparms { transformCategory = "typeAnalyze", \
                transformPass = "PreInit"
                                          , transformOperation = typeAnalyze True } \
mprog  
hunk ./src/E/Main.hs 216
         mprog <- transformProgram tparms { transformCategory = "FloatOutward", \
transformOperation = floatOutward } mprog +
         -- perform another supersimplify in order to substitute the once used
         -- variables back in and replace the variable of case of variables with
         -- the default binding of the case statement.
hunk ./src/E/Main.hs 220
-
         mprog <- simplifyProgram sopt "Init-Two-FloatOutCleanup" coreMini mprog
         mprog <- transformProgram tparms { transformCategory = "typeAnalyze", \
transformOperation = typeAnalyze True } mprog  
hunk ./src/E/Main.hs 229
         mprog <- simplifyProgram sopt "Init-Three-AfterDemand" False mprog
         when miniCorePass $ printProgram mprog -- mapM_ (\ (v,lc) -> \
                printCheckName'' fullDataTable v lc) (programDs mprog)
         when miniCoreSteps $ Stats.printLStat (optStatLevel options) \
                ("InitialOptimize:" ++ names) (progStats mprog)
-        --wdump FD.Progress $ let SubProgram rec = progType mprog in  putErr (if rec \
                then "*" else ".")
         wdump FD.Progress $ let SubProgram isRec = progType mprog in  \
progressIOSteps pr_r (if isRec then "*" else ".")  return mprog
     lintCheckProgram onerrNone prog
hunk ./src/E/Main.hs 232
-    --putProgressLn "Initial optimization pass"
-
     prog <- programMapProgGroups mempty fint prog
 
     wdump FD.Stats $
hunk ./src/E/Main.hs 247
 
     prog <- Demand.analyzeProgram prog
     prog <- simplifyProgram' sopt "Init-Big-One" verbose (IterateMax 4) prog
+    putErrLn "-- ChoRulesPostSimp";
+    putErrLn "------------";
+    dumpRules (Rules $ fromList [ (combIdent x,combRules x) | x <- progCombinators \
prog, not $ null (combRules x) ])  
     wdump FD.Stats $
         Stats.printLStat (optStatLevel options) "Init-Big-One Stats" (progStats \
prog) hunk ./src/E/Main.hs 308
 
     prog <- programPrune prog
 
-
     lintCheckProgram (putErrLn "After the Opimization") prog
     wdump FD.Core $ printProgram prog
 
hunk ./src/E/Main.hs 320
     return (updateChoHo $ mempty {
         choHoMap = Map.singleton (hoModuleGroup ho') ho' { hoBuild = newHoBuild},
         choCombinators = fromList $ [ (combIdent c,c) | c <- progCombinators prog ],
-        choExternalNames = idMapToIdSet newMap,
-        choVarMap = newMap
+        choExternalNames = idMapToIdSet newMap
         } `mappend` cho,ho' { hoBuild = newHoBuild })
 
 coreMini = dump FD.CoreMini
hunk ./src/E/Rules.hs 47
 import Util.SetLike as S
 import qualified Util.Seq as Seq
 
-
-
-
 instance Show Rule where
     showsPrec _ r = shows $ ruleName r
 
hunk ./src/FrontEnd/FrontEnd.hs 21
 import qualified FlagDump as FD
 import qualified FrontEnd.Tc.Module as Tc
 
-
-
--- | Main entry point to front end
-
-{-
-parseFiles :: [Either Module String]      -- ^ List of files or modules to read
-               -> (CollectedHo -> Ho -> IO CollectedHo) -- ^ Process initial data \
                loaded from ho files
-               -> (CollectedHo -> Ho -> Tc.TiData -> IO (CollectedHo,Ho))  -- ^ \
routine which takes the global ho, the partial local ho and the output of the front \
                end, and returns the completed ho.
-               -> IO CollectedHo          -- ^ (the final combined ho,all the loaded \
                ho data)
-parseFiles fs ifunc func = do
-    wdump FD.Progress $ do
-        putErrLn $ "Compiling " ++ show fs
-    compileModules fs ifunc (doModules func)
-
--- Process modules found by Ho
-doModules :: (CollectedHo -> Ho -> Tc.TiData -> IO (CollectedHo,Ho)) -> CollectedHo \
                -> [HsModule] -> IO (CollectedHo,Ho)
-doModules func ho ms  = do
-    ms <- mapM modInfo ms
-    when (dump FD.Defs) $ flip mapM_ ms $ \m -> do
-         putStrLn $ " ---- Definitions for" <+> show (modInfoName m) <+> "----";
-         mapM_ print ( modInfoDefs m)
-    ms <- determineExports [ (x,y,z) | (x,(y,z)) <- Map.toList $ hoDefs $ hoTcInfo $ \
                choHo ho] (Map.toList $ hoExports $ hoTcInfo $ choHo ho) ms
-    --(ho',tiData) <- Tc.tiModules' ho ms
-    (htc,tiData) <- Tc.tiModules (hoTcInfo (choHo ho)) ms
-    func ho mempty { hoTcInfo = htc } tiData
--}
-
 -- Process modules found by Ho
 doModules' :: HoTcInfo -> [HsModule] -> IO  (HoTcInfo,Tc.TiData)
 doModules' htc ms  = do
hunk ./src/Ho/Build.hs 88
 -- LCOR - library map of module group name to CORE
 -- GRIN - compiled grin code
 
-
 {-
  - We separate the data into various chunks for logical layout as well as the \
                important property that
  - each chunk is individually compressed and accessable. What this means is
hunk ./src/Ho/Build.hs 97
  - serialization, we would have to parse all preceding information just to discard \
                it right away.
  - We also lay them out so that we can generate error messages quickly. for \
                instance, we can determine
  - if a symbol is undefined quickly, before it has to load the typechecking data.
- -
  -}
 
hunk ./src/Ho/Build.hs 99
--- | this should be updated every time the on-disk file format changes for a chunk. \
                It is independent of the
--- version number of the compiler.
-
-
 type LibraryName = PackedString
 
 findFirstFile :: String -> [(FilePath,a)] -> IO (LBS.ByteString,FilePath,a)
hunk ./src/Ho/Build.hs 107
     bs <- LBS.readFile x
     return (bs,x,a)
 
-
 data ModDone
     = ModNotFound
     | ModLibrary Bool ModuleGroup Library
hunk ./src/Ho/Build.hs 122
     }
     {-! derive: update !-}
 
-
 replaceSuffix suffix fp = reverse (dropWhile ('.' /=) (reverse fp)) ++ suffix
 
 hoFile :: Maybe FilePath -> FilePath -> Maybe Module -> SourceHash -> FilePath
hunk ./src/Ho/Build.hs 149
                 modifyIORef done_ref (hosEncountered_u $ Map.insert (hohHash hoh) \
(honame,hoh,hidep,ho))  return (True,honame)
 
-
-
 onErr :: IO a -> IO b -> (b -> IO a) -> IO a
 onErr err good cont = catch (good >>= \c -> return (cont c)) (\_ -> return err) >>= \
id  
hunk ./src/Ho/Build.hs 198
         Just _ -> return ()
         Nothing -> fetchSource done_ref (map fst $ searchPaths (show m)) (Just m) >> \
return ()  
-
 type LibInfo = (Map.Map Module ModuleGroup, Map.Map ModuleGroup [ModuleGroup], \
Set.Set Module,Map.Map ModuleGroup HoBuild,Map.Map ModuleGroup HoTcInfo)  
 data CompNode = CompNode !HoHash [CompNode] {-# UNPACK #-} !(IORef CompLink)
hunk ./src/Ho/Build.hs 261
     = SourceParsed     { sourceInfo :: !SourceInfo, sourceModule :: HsModule }
     | SourceRaw        { sourceInfo :: !SourceInfo, sourceLBS :: LBS.ByteString }
 
-
 sourceIdent sp = show . sourceModName $ sourceInfo sp
 
 class ProvidesModules a where
hunk ./src/Ho/Collected.hs 43
         choHoMap = Map.singleton primModule pho,
         choCombinators = mempty,
         choHo = error "choHo-a",
-        choVarMap = mempty,
+        choVarMap = error "choVarMap-a",
         choLibDeps = mempty
         } where pho = mempty { hoBuild = mempty { hoDataTable = dataTablePrims } }
     a `mappend` b = updateChoHo CollectedHo {
hunk ./src/Ho/Collected.hs 48
         choExternalNames = choExternalNames a `mappend` choExternalNames b,
-        choVarMap = choVarMap a `mergeChoVarMaps` choVarMap b,
+        choVarMap = error "choVarMap-b",
         choOrphanRules = choOrphanRules a `mappend` choOrphanRules b,
         choCombinators = choCombinators a `mergeChoCombinators` choCombinators b,
         choLibDeps = choLibDeps a `mappend` choLibDeps b,
hunk ./src/Ho/Collected.hs 56
         choHoMap = Map.union (choHoMap a) (choHoMap b)
         }
 
-updateChoHo cho = cho { choHo = ho } where
+updateChoHo cho = cho { choHo = ho, choVarMap = varMap } where
     ho = hoBuild_u (hoEs_u f) . mconcat . Map.elems $ choHoMap cho
     f ds = runIdentity $ annotateDs mmap  (\_ -> return) (\_ -> return) (\_ -> \
return) (map g ds) where hunk ./src/Ho/Collected.hs 59
-        mmap = sfilter (\(k,_) -> (k `notElem` (map (tvrIdent . fst) ds))) \
                (choVarMap cho)
-    g (t,e) = case mlookup (tvrIdent t) (choVarMap cho) of
+        mmap = sfilter (\(k,_) -> (k `notElem` (map (tvrIdent . fst) ds))) varMap
+    g (t,e) = case mlookup (tvrIdent t) varMap of
         Just (Just (EVar t')) -> (t',e)
         _ -> (t,e)
hunk ./src/Ho/Collected.hs 63
- --   ae = runIdentity . annotate (choVarMap cho) (\_ -> return) (\_ -> return) (\_ \
                -> return)
-
--- this will have to merge rules and properties.
-mergeChoVarMaps :: IdMap (Maybe E) -> IdMap (Maybe E) -> IdMap (Maybe E)
-mergeChoVarMaps x y = unionWith f x y where
-    f (Just (EVar x)) (Just (EVar y)) = Just . EVar $ merge x y
-    f x y = error "mergeChoVarMaps: bad merge."
-    merge ta tb = ta { tvrInfo = minfo' }   where
-        minfo = tvrInfo ta `mappend` tvrInfo tb
-        minfo' = dex (undefined :: Properties) $ minfo
-        dex dummy y = g (Info.lookup (tvrInfo tb) `asTypeOf` Just dummy) where
-            g Nothing = y
-            g (Just x) = Info.insertWith mappend x y
+    varMap = fmap (\c -> Just (EVar $ combHead c)) $ choCombinators cho
 
 -- this will have to merge rules and properties.
 mergeChoCombinators :: IdMap Comb -> IdMap Comb -> IdMap Comb
hunk ./src/Ho/Collected.hs 68
 mergeChoCombinators x y = unionWith f x y where
-    f c1 c2 = combRules_s  (combRules c1 `Data.List.union`  combRules c2) . \
combHead_s (merge (combHead c1) (combHead c2)) $ c1 +    f c1 c2 = combRules_s \
(combRules c1 `Data.List.union` combRules c2) . combHead_s (merge (combHead c1) \
(combHead c2)) $ c1  merge ta tb = ta { tvrInfo = minfo' }   where
         minfo = tvrInfo ta `mappend` tvrInfo tb
         minfo' = dex (undefined :: Properties) $ minfo
hunk ./src/Ho/Type.hs 54
 data CollectedHo = CollectedHo {
     -- this is a list of external names that are valid but that we may not know
     -- anything else about it is used to recognize invalid ids.
-    choExternalNames :: IdSet, choCombinators  :: IdMap Comb,
-    -- this is a map of ids to their full TVrs with all rules and whatnot
-    -- attached.
-    choVarMap :: IdMap (Maybe E),
+    choExternalNames :: IdSet,
+    -- these are the functions in Comb form.
+    choCombinators  :: IdMap Comb,
     -- these are rules that may need to be retroactively applied to other
     -- modules
     choOrphanRules :: Rules,
hunk ./src/Ho/Type.hs 61
     -- the hos
-    choHo :: Ho, -- this is a cache, it must be updated whenever choHoMap is \
updated.  choHoMap :: Map.Map ModuleGroup Ho,
     -- libraries depended on
hunk ./src/Ho/Type.hs 63
-    choLibDeps :: Map.Map PackedString HoHash
+    choLibDeps :: Map.Map PackedString HoHash,
+    -- these are caches of pre-computed values
+    choHo :: Ho, -- ^ cache of combined and renamed ho
+    choVarMap :: IdMap (Maybe E) -- ^ cache of variable substitution map
     }
     {-! derive: update !-}
 
[remove quadratic behavior in programSetDs'
John Meacham <john@repetae.net>**20101207033358
 Ignore-this: d0a52945b310e2a599cc54510c18ea5b
] hunk ./src/E/Main.hs 247
 
     prog <- Demand.analyzeProgram prog
     prog <- simplifyProgram' sopt "Init-Big-One" verbose (IterateMax 4) prog
-    putErrLn "-- ChoRulesPostSimp";
-    putErrLn "------------";
-    dumpRules (Rules $ fromList [ (combIdent x,combRules x) | x <- progCombinators \
prog, not $ null (combRules x) ])  
     wdump FD.Stats $
         Stats.printLStat (optStatLevel options) "Init-Big-One Stats" (progStats \
prog) hunk ./src/E/Main.hs 251
 
-    pr_r <- progressIONew (length $ programDecomposedDs prog) 25 '.'
+    pr_r <- progressIONew (length $ programDecomposedCombs prog) 25 '.'
 
     -- This is the main function that optimizes the routines before writing them out
     let optWW mprog = do
hunk ./src/E/Program.hs 89
 
 programSetDs' :: [(TVr,E)] -> Program -> Program
 programSetDs' ds prog = progCombinators_s [ combRules_s (lupRules (tvrIdent t)) $ \
                bindComb (t,e) | (t,e) <- ds ] prog where
-    lupRules t = concat [ combRules c | c <- progCombinators prog, combIdent c == t]
+    lupRules t = case mlookup t (progCombMap prog) of
+        Just c -> combRules c
+        Nothing -> mempty
 
 programSetDs :: [(TVr,E)] -> Program -> Program
 programSetDs ds prog = progCombinators_s [ bindComb (t,e) | (t,e) <- ds ] prog

Context:

[clean ups and remove unused module, make selftest work with the new ghc
John Meacham <john@repetae.net>**20101206122555
 Ignore-this: 5b56d3dcd7186aeab6e3b42c57db0f99
] 
[fix type checker bug that occasionally reported false erros
John Meacham <john@repetae.net>**20101206120451
 Ignore-this: a34be6e294bde1e95ad7a9ca35b42055
] 
[fix pretty printing fixity of core to reduce ambiguity
John Meacham <john@repetae.net>**20101204231805
 Ignore-this: 8adc87b15e09134f673da1b438adc5a2
] 
[Fix a lot of compiler warnings, clean up dependencies.
John Meacham <john@repetae.net>**20101204035931
 Ignore-this: 7524be06d3ca6cd957316e50451b7208
] 
[show text of exception when dumping core.
John Meacham <john@repetae.net>**20100826091509
 Ignore-this: 859d57d2a6184698e97f0083482b3039
] 
[remove ePrettyEx
John Meacham <john@repetae.net>**20100812102458
 Ignore-this: 5ff9ed89d829f656c11012d75bab6f16
] 
[clean up warnings
John Meacham <john@repetae.net>**20100812102435
 Ignore-this: 582526a443397ee875d3530d892b704d
] 
[clean up E showing, get rid of -dhtml mode, get rid of ANSI color coding, dump \
jhc_core to files on error John Meacham <john@repetae.net>**20100812101452
 Ignore-this: ef81f8c50892ecfdda3b5a450d8fbac0
] 
[when let-shrinking a tail, be sure to optimize function bodies
John Meacham <john@repetae.net>**20100812054500
 Ignore-this: eb1b56f28287a98b67bcd9c29d50ba82
] 
[improve Grin Linting a little
John Meacham <john@repetae.net>**20100812054446
 Ignore-this: c7613a94c296e089a985904aa049d002
] 
[add imported ghc typechecking regression tests
John Meacham <john@repetae.net>**20100811014451
 Ignore-this: 7f625abf2f8d562bc76b71396a7e03f0
] 
[import ghc parsing regression tests
John Meacham <john@repetae.net>**20100811002607
 Ignore-this: 7a3676c7655fe26c52dd7eddd3c356dc
] 
[add 'skip' to regression options to skip certain tests
John Meacham <john@repetae.net>**20100811002445
 Ignore-this: 261b5e51fa22d7af25989ee078853590
] 
[allow unicode characters in haskell source
John Meacham <john@repetae.net>**20100810233304
 Ignore-this: dd54c632455bd0660ff7b5170d81c8ed
] 
[add regex-compat to dependencies
John Meacham <john@repetae.net>**20100810230216
 Ignore-this: e7c03b8e187802ab75dbcc574614eabc
] 
[accept empty class contexts
John Meacham <john@repetae.net>**20100810063832
 Ignore-this: 9dea1ec61b874fcb3537b79b74b345df
] 
[add 'transformers' package to included libraries
John Meacham <john@repetae.net>**20100810054906
 Ignore-this: e27f376331b3fac2e3414145bf17a1c0
] 
[fix desugaring of irrefutable lambda bindings
John Meacham <john@repetae.net>**20100810053944
 Ignore-this: 5c70934cbe42169850481562cd5b20f3
] 
[add some strictness annotations
John Meacham <john@repetae.net>**20100810053827
 Ignore-this: 15ed2e2fc90656cc418a841848e43107
] 
[clean ups
John Meacham <john@repetae.net>**20100806112820
 Ignore-this: 64c0ae0922073b65fc0dac4bd35ba968
] 
[speed up name choosing a little
John Meacham <john@repetae.net>**20100806111703
 Ignore-this: ac159eeb0d34a7d26ad74253d00386ae
] 
[further seperate out concrete types to speed up checking
John Meacham <john@repetae.net>**20100806092815
 Ignore-this: f992ced583042d3c7797d4de93e3e3a8
] 
[split type environment into concrete and mutable sets, to avoid retraversing the \
concrete imported types John Meacham <john@repetae.net>**20100806090349
 Ignore-this: c276618b4b968d9149e6b3dfc36d162a
] 
[create a better relation representation, speed up export chasing signifigantly
John Meacham <john@repetae.net>**20100806082622
 Ignore-this: 9f49871e33348bbfc4e8fd2ee9fa71b8
] 
[fix a few minor bugs in libraries found by better error reporting
John Meacham <john@repetae.net>**20100806045809
 Ignore-this: e7d43927c9e11b05de455a5d0ebd1017
] 
[check export lists for unknown names
John Meacham <john@repetae.net>**20100806045759
 Ignore-this: 4b3ff8381117f2acae34dd6b936c8e8d
] 
[ret rid of seperate subtable and errortable in favor of unified namemap
John Meacham <john@repetae.net>**20100806032455
 Ignore-this: 9e8fbd31f988d77614bd49fc23cefae
] 
[treat () the same as tuples when renaming
John Meacham <john@repetae.net>**20100806023948
 Ignore-this: defa66a11f1081a4582a5301cff217e4
] 
[move selector creation from desugar to renamer, detect multiply defined top level \
values and report an error properly. John Meacham <john@repetae.net>**20100806021241
 Ignore-this: 507bce69ec8ffe0085c3a72ffc0ec571
] 
[add initial version of jhc-prim
John Meacham <john@repetae.net>**20100806000900
 Ignore-this: 44a9f14db168b28d731fd750bba0fee9
] 
[clean up preprocessing a little
John Meacham <john@repetae.net>**20100803073754
 Ignore-this: c1064468bed864231c2d5fb3a68bbeaf
] 
[utilize preprocessor rather than ./configure to handle System.Info
John Meacham <john@repetae.net>**20100802100036
 Ignore-this: 76681affa5b0269621974deeccda019b
] 
[fix some warnings
John Meacham <john@repetae.net>**20100801083507
 Ignore-this: fd350fd02d0ad5a611ee1811de28bce5
] 
[fix build problem for tarball
John Meacham <john@repetae.net>**20100801082137
 Ignore-this: 33671b52398eef61afa670eb031ef575
] 
[update strictness and UNPACK annotations
John Meacham <john@repetae.net>**20100801080035
 Ignore-this: e598a6098143c1a62373a443865b3cfb
] 
[add announcement for 0.7.6
John Meacham <john@repetae.net>**20100731111353
 Ignore-this: 111c27548d94bdfe0042d61b02fe5728
] 
[TAG 0.7.6
John Meacham <john@repetae.net>**20100731104908
 Ignore-this: d5edc6edd6d300cbae451f0e056ee018
] 
Patch bundle hash:
760228adb4281458e5bbad095e4c81f0b3baf8a7



_______________________________________________
jhc mailing list
jhc@haskell.org
http://www.haskell.org/mailman/listinfo/jhc

.

[prev in list] [next in list] [prev in thread] [next in thread] 

Configure | About | News | Add a list | Sponsored by KoreLogic